Skip to content

Commit

Permalink
Move site initialisation to cable_driver_init_site
Browse files Browse the repository at this point in the history
  • Loading branch information
SeanBryan51 committed Nov 28, 2024
1 parent ca3a076 commit c78428c
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 22 deletions.
20 changes: 18 additions & 2 deletions src/offline/cable_driver_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,8 @@ MODULE cable_driver_init_mod
globalMetfile, &
set_group_output_values, &
timeunits, &
exists
exists, &
calendar
USE casadimension, ONLY : icycle
USE casavariable, ONLY : casafile
USE cable_namelist_util, ONLY : &
Expand All @@ -39,6 +40,7 @@ MODULE cable_driver_init_mod
USE cable_input_module, ONLY : open_met_file
USE CABLE_PLUME_MIP, ONLY : PLUME_MIP_TYPE, PLUME_MIP_INIT
USE CABLE_CRU, ONLY : CRU_TYPE, CRU_INIT
USE CABLE_site, ONLY : site_TYPE, site_INIT
IMPLICIT NONE
PRIVATE

Expand Down Expand Up @@ -236,14 +238,28 @@ SUBROUTINE cable_driver_init_gswp(mpi_grp, GSWP_MID, NRRRR)

END SUBROUTINE cable_driver_init_gswp

SUBROUTINE cable_driver_init_site()
SUBROUTINE cable_driver_init_site(site)
!* Model initialisation routine (site met specific).
! Site experiment, e.g. AmazonFace (spinup or transient run type).
TYPE (site_TYPE), INTENT(OUT) :: site

CHARACTER(len=9) :: str1, str2, str3

IF (.NOT. l_casacnp) THEN
WRITE(*,*) "MetType=site only works with CASA-CNP turned on"
STOP 991
END IF

CALL site_INIT( site )
WRITE(str1,'(i4)') cable_user%YearStart
str1 = ADJUSTL(str1)
WRITE(str2,'(i2)') 1
str2 = ADJUSTL(str2)
WRITE(str3,'(i2)') 1
str3 = ADJUSTL(str3)
timeunits="seconds since "//TRIM(str1)//"-"//TRIM(str2)//"-"//TRIM(str3)//"00:00"
calendar = 'standard'

END SUBROUTINE cable_driver_init_site

SUBROUTINE cable_driver_init_default(dels, koffset, kend)
Expand Down
6 changes: 4 additions & 2 deletions src/offline/cable_offline_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ PROGRAM cable_offline_driver
USE cable_common_module, ONLY : cable_user
USE CABLE_PLUME_MIP, ONLY : PLUME_MIP_TYPE
USE CABLE_CRU, ONLY : CRU_TYPE
USE CABLE_site, ONLY : site_TYPE

IMPLICIT NONE

Expand All @@ -25,6 +26,7 @@ PROGRAM cable_offline_driver
INTEGER, ALLOCATABLE :: GSWP_MID(:,:) !! NetCDF file IDs for GSWP met forcing
TYPE(PLUME_MIP_TYPE) :: PLUME
TYPE(CRU_TYPE) :: CRU
TYPE (site_TYPE) :: site

call mpi_mod_init()
mpi_grp = mpi_grp_t()
Expand All @@ -41,7 +43,7 @@ PROGRAM cable_offline_driver
CASE('cru')
CALL cable_driver_init_cru(dels, koffset, CRU)
CASE('site')
CALL cable_driver_init_site()
CALL cable_driver_init_site(site)
CALL cable_driver_init_default(dels, koffset, kend)
CASE('')
CALL cable_driver_init_default(dels, koffset, kend)
Expand All @@ -51,7 +53,7 @@ PROGRAM cable_offline_driver
END SELECT

IF (mpi_grp%size == 1) THEN
CALL serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME, CRU)
CALL serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME, CRU, site)
ELSE
IF (mpi_grp%rank == 0) THEN
CALL mpidrv_master(mpi_grp%comm, trunk_sumbal, dels, koffset, kend, PLUME, CRU)
Expand Down
22 changes: 4 additions & 18 deletions src/offline/cable_serial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -132,7 +132,7 @@ MODULE cable_serial
PLUME_MIP_INIT

USE CABLE_CRU, ONLY: CRU_TYPE, CRU_GET_SUBDIURNAL_MET
USE CABLE_site, ONLY: site_TYPE, site_INIT, site_GET_CO2_Ndep
USE CABLE_site, ONLY: site_TYPE, site_GET_CO2_Ndep

! LUC_EXPT only
USE CABLE_LUC_EXPT, ONLY: LUC_EXPT_TYPE, LUC_EXPT_INIT
Expand All @@ -153,7 +153,7 @@ MODULE cable_serial

CONTAINS

SUBROUTINE serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME, CRU)
SUBROUTINE serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME, CRU, site)
!! Offline serial driver.
DOUBLE PRECISION, INTENT(IN) :: trunk_sumbal
!! Reference value for quasi-bitwise reproducibility checks.
Expand All @@ -164,6 +164,7 @@ SUBROUTINE serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME,
INTEGER, ALLOCATABLE, INTENT(INOUT) :: GSWP_MID(:,:) !! NetCDF file IDs for GSWP met forcing
TYPE(PLUME_MIP_TYPE), INTENT(IN) :: PLUME
TYPE(CRU_TYPE), INTENT(IN) :: CRU
TYPE (site_TYPE), INTENT(IN) :: site

! timing variables
INTEGER, PARAMETER :: kstart = 1 ! start of simulation
Expand All @@ -185,7 +186,7 @@ SUBROUTINE serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME,
count_sum_casa ! number of time steps over which casa pools &
!and fluxes are aggregated (for output)

CHARACTER :: dum*9, str1*9, str2*9, str3*9
CHARACTER :: dum*9

! CABLE variables
TYPE (met_type) :: met ! met input variables
Expand Down Expand Up @@ -217,7 +218,6 @@ SUBROUTINE serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME,
! vh_js !
TYPE (POP_TYPE) :: POP
TYPE(POPLUC_TYPE) :: POPLUC
TYPE (site_TYPE) :: site
TYPE (LUC_EXPT_TYPE) :: LUC_EXPT
TYPE (landuse_mp) :: lucmp
CHARACTER :: cyear*4
Expand Down Expand Up @@ -332,20 +332,6 @@ SUBROUTINE serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME,
kend = NINT(24.0*3600.0/dels) * LOY
ELSE IF ( TRIM(cable_user%MetType) .EQ. 'site' ) THEN
! site experiment eg AmazonFace (spinup or transient run type)

IF ( CALL1 ) THEN
CALL CPU_TIME(etime)
CALL site_INIT( site )
WRITE(str1,'(i4)') CurYear
str1 = ADJUSTL(str1)
WRITE(str2,'(i2)') 1
str2 = ADJUSTL(str2)
WRITE(str3,'(i2)') 1
str3 = ADJUSTL(str3)
timeunits="seconds since "//TRIM(str1)//"-"//TRIM(str2)//"-"//TRIM(str3)//"00:00"
calendar = 'standard'

ENDIF
kend = NINT(24.0*3600.0/dels) * LOY
! get koffset to add to time-step of sitemet
IF (TRIM(site%RunType)=='historical') THEN
Expand Down

0 comments on commit c78428c

Please sign in to comment.