diff --git a/Makefile b/Makefile
index 6cc1c9d9543b3e36268e35077d9d3dab0bc9a596..1f4a169aa2532e6b58ddf5bcde556f789704e9c4 100644
--- a/Makefile
+++ b/Makefile
@@ -1,13 +1,13 @@
 # Makefile for LAKE model
 
  exec = lake.out
- #FC=ifort#mpif90
- FC=gfortran
+ FC=ifort#mpif90
+ #FC=gfortran
  check_keys = # -check bounds -check pointers
  debug_keys = #-g # debugger
 
  ifeq ($(FC),ifort)
-   opt_keys = -openmp #-O3
+   opt_keys = -qopenmp #-O3
  endif
  ifeq ($(FC),gfortran)
    opt_keys = -fopenmp #-O3
diff --git a/source/Makefile b/source/Makefile
index 812961617886d76d63fce72b7b6ca0ef3df4c034..875071eb31ca0bf9330b10c8ededba991833b6fe 100644
--- a/source/Makefile
+++ b/source/Makefile
@@ -1,7 +1,7 @@
 # Compiling source files of LAKE model
 
- #FC=ifort#mpif90
- FC=gfortran
+ FC=ifort#mpif90
+ #FC=gfortran
  EXEC = lake.out
 
  INCLPATHS = 
@@ -17,8 +17,8 @@
 
  ifeq ($(FC),ifort)
    PREPROCESS_KEY = -fpp
-   opt_keys = -openmp -O3 #-fp-model source
-   check_keys = #-g -traceback -check all -fpe-all=0
+   opt_keys = -qopenmp -O3 #-fp-model source
+   check_keys = -g -traceback -check all -fpe-all=0
  endif
  ifeq ($(FC),gfortran)
    PREPROCESS_KEY = -cpp
diff --git a/source/model/init.f90 b/source/model/init.f90
index 019e588becdc3996febac8a7e8cda81f02b20321..0d9888c40ef009dfcbb2bb0fa9ed30b7c912fa49 100644
--- a/source/model/init.f90
+++ b/source/model/init.f90
@@ -17,7 +17,7 @@
  use METH_OXYG_CONSTANTS, only : &
  & ngasb
  use RADIATION, only : RadWater, RadIce, RadDeepIce, &
- & fracbands, nbands
+ & fracbands, nbands, RAD_POINTERS
 
  implicit none
 
@@ -48,6 +48,7 @@
 
  ! Radiation group
  !allocate (fracbands(1:nbands))
+ call RAD_POINTERS()
  call RadWater  %RAD_INIT(nbands=nbands,nlevels=M+1,extCDOC=(carbon_model%par==2))
  call RadIce    %RAD_INIT(nbands=nbands,nlevels=Mice+1,extCDOC=.false.)
  call RadDeepIce%RAD_INIT(nbands=nbands,nlevels=Mice+1,extCDOC=.false.)
diff --git a/source/model/lake_modules.f90 b/source/model/lake_modules.f90
index e992c8735f6f76960259b46e696ee0c2b0ca163c..abc6914e0c9b031d17b2b34095baabe57c2e9b9e 100644
--- a/source/model/lake_modules.f90
+++ b/source/model/lake_modules.f90
@@ -312,12 +312,11 @@ type, public :: rad_type
   sequence
   integer(kind=iintegers) :: nbands, nlevels
   real(kind=ireals), allocatable       :: extinct(:,:), extinct_CDOC(:), flux(:,:), integr(:)
-  procedure(RAD_UPDATE), pointer, pass :: RAD_UPDATE => RAD_UPDATE
-  procedure(RAD_INIT)  , pointer, pass :: RAD_INIT   => RAD_INIT
+  procedure(RAD_UPDATE), pointer, pass :: RAD_UPDATE
+  procedure(RAD_INIT)  , pointer, pass :: RAD_INIT
 endtype rad_type
 type(rad_type) :: RadWater, RadIce, RadDeepIce
 
-
 !>@todo: check wavelength bound between "IR-A" and "IR-B", ext coefs and energy fractions
 integer(kind=iintegers), parameter :: nbands = 4 !wavebands: UV, PAR, NIR(IR-A), IR-B
 real(kind=ireals), parameter :: bandbounds(1:nbands+1) = (/280.,400.,700.,1000.,3000./) !Bounds between bands, nm
@@ -346,7 +345,6 @@ enddo
 forall(i=1:this%nlevels) this%integr(i) = sum(this%flux(i,1:this%nbands))
 END SUBROUTINE RAD_UPDATE
 
-
 !> Initializes the radiation variable structure
 SUBROUTINE RAD_INIT(this,nbands,nlevels,extCDOC)
 type(rad_type), intent(inout) :: this
@@ -362,6 +360,15 @@ endif
 allocate(this%integr (0:nlevels            ))
 END SUBROUTINE RAD_INIT
 
+SUBROUTINE RAD_POINTERS
+implicit none
+RadWater   % RAD_UPDATE => RAD_UPDATE
+RadWater   % RAD_INIT   => RAD_INIT
+RadIce     % RAD_UPDATE => RAD_UPDATE
+RadIce     % RAD_INIT   => RAD_INIT
+RadDeepIce % RAD_UPDATE => RAD_UPDATE
+RadDeepIce % RAD_INIT   => RAD_INIT
+END SUBROUTINE RAD_POINTERS
 
 END MODULE RADIATION
 
@@ -388,42 +395,40 @@ implicit none
  endtype waterstate_type
  type(waterstate_type) :: wst
 
- type, public :: intbal_type
-   sequence
-   real(kind=ireals), allocatable :: terms(:), termsdt(:)
-   real(kind=ireals) :: storage, storage0, dstorage, resid
-   integer(kind=iintegers) :: nterms
-   procedure(intbal_update), pointer, nopass :: intbal_update => INTBAL_UPDATE
- endtype intbal_type
- 
- contains
- 
-
- SUBROUTINE INTBAL_UPDATE(this,terms,storage1,storage2,dt)
- implicit none
- !Input/output variables
- type(intbal_type) :: this
- real(kind=ireals), intent(in), dimension(:) :: terms
- real(kind=ireals), intent(in) :: storage1, storage2, dt
- !Local variables
- logical, save :: firstcall = .true.
- integer(kind=iintegers) :: i
-
- if (firstcall) then
-   this%storage0 = storage1
- endif
-
- !do i = 1, this%nterms
- this%terms(:) = terms(:)
- this%termsdt(:) = this%termsdt(:) + terms(:)*dt
- this%storage = storage2
- this%dstorage = storage2 - this%storage0
- this%resid = this%dstorage - sum(this%termsdt(:))
- !enddo
-
- if (firstcall) firstcall = .false.
- END SUBROUTINE INTBAL_UPDATE
-
+ !type, public :: intbal_type
+ !  sequence
+ !  real(kind=ireals), allocatable :: terms(:), termsdt(:)
+ !  real(kind=ireals) :: storage, storage0, dstorage, resid
+ !  integer(kind=iintegers) :: nterms
+ !  procedure(intbal_update), pointer, nopass :: intbal_update => INTBAL_UPDATE
+ !endtype intbal_type
+ !
+ !contains
+ !
+ !SUBROUTINE INTBAL_UPDATE(this,terms,storage1,storage2,dt)
+ !implicit none
+ !!Input/output variables
+ !type(intbal_type) :: this
+ !real(kind=ireals), intent(in), dimension(:) :: terms
+ !real(kind=ireals), intent(in) :: storage1, storage2, dt
+ !!Local variables
+ !logical, save :: firstcall = .true.
+ !integer(kind=iintegers) :: i
+
+ !if (firstcall) then
+ !  this%storage0 = storage1
+ !endif
+
+ !!do i = 1, this%nterms
+ !this%terms(:) = terms(:)
+ !this%termsdt(:) = this%termsdt(:) + terms(:)*dt
+ !this%storage = storage2
+ !this%dstorage = storage2 - this%storage0
+ !this%resid = this%dstorage - sum(this%termsdt(:))
+ !!enddo
+
+ !if (firstcall) firstcall = .false.
+ !END SUBROUTINE INTBAL_UPDATE
 
 END MODULE ARRAYS_WATERSTATE
 
diff --git a/source/model/salinity_mod.f90 b/source/model/salinity_mod.f90
index 9cee7affd86bcd97db5882f90eddea41b555e0d0..c108749c3387be3982e47b6d6d5fafc097efe3fd 100644
--- a/source/model/salinity_mod.f90
+++ b/source/model/salinity_mod.f90
@@ -433,8 +433,8 @@ do j = 2, Mice
         &                    ', Tfr2=', MELTPNT(work2/(row0), &
         &                              pressure,nmeltpoint%par), &
         &                    j
-        !read*
-        exit ifadjust
+        read*
+        !exit ifadjust
       endif
     enddo
     work3  = 0.5*(work1 + work2)