Skip to content
Snippets Groups Projects
Commit e946206b authored by Victor Stepanenko's avatar Victor Stepanenko
Browse files

The code adapted for ifort compiler

parent 71d60683
Branches
Tags
No related merge requests found
# 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
......
# 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
......
......@@ -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.)
......
......@@ -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
......
......@@ -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)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment