Skip to content

Commit

Permalink
Move icycle related initialisation to cable_driver_init
Browse files Browse the repository at this point in the history
  • Loading branch information
SeanBryan51 committed Nov 18, 2024
1 parent b38ae68 commit 96bf22c
Show file tree
Hide file tree
Showing 4 changed files with 43 additions and 92 deletions.
37 changes: 37 additions & 0 deletions src/offline/cable_driver_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -36,9 +36,12 @@ MODULE cable_driver_init_mod
IMPLICIT NONE
PRIVATE

INTEGER, PARAMETER :: CASAONLY_ICYCLE_MIN = 10

LOGICAL, SAVE, PUBLIC :: vegparmnew = .FALSE. ! using new format input file (BP dec 2007)
LOGICAL, SAVE, PUBLIC :: spinup = .FALSE. ! model spinup to soil state equilibrium?
LOGICAL, SAVE, PUBLIC :: spincasa = .FALSE. ! TRUE: CASA-CNP Will spin mloop times, FALSE: no spin up
LOGICAL, SAVE, PUBLIC :: CASAONLY = .FALSE. ! ONLY Run CASA-CNP
LOGICAL, SAVE, PUBLIC :: l_casacnp = .FALSE. ! using CASA-CNP with CABLE
LOGICAL, SAVE, PUBLIC :: l_landuse = .FALSE. ! using CASA-CNP with CABLE
LOGICAL, SAVE, PUBLIC :: l_laiFeedbk = .FALSE. ! using prognostic LAI
Expand Down Expand Up @@ -69,6 +72,7 @@ MODULE cable_driver_init_mod
l_landuse, &
l_laiFeedbk, &
l_vcmaxFeedbk, &
CASAONLY, &
icycle, &
casafile, &
ncciy, &
Expand Down Expand Up @@ -140,6 +144,39 @@ SUBROUTINE cable_driver_init(mpi_grp, trunk_sumbal)
CALL set_group_output_values()
END IF

! TODO(Sean): we should not be setting namelist parameters in the following if
! block - all options are all configurable via the namelist file and is
! unclear that these options are being overwritten. A better approach would be
! to error for bad combinations of namelist parameters.
IF (icycle > CASAONLY_ICYCLE_MIN) THEN
icycle = icycle - CASAONLY_ICYCLE_MIN
CASAONLY = .TRUE.
CABLE_USER%CASA_DUMP_READ = .TRUE.
CABLE_USER%CASA_DUMP_WRITE = .FALSE.
ELSE IF (icycle == 0) THEN
CABLE_USER%CASA_DUMP_READ = .FALSE.
spincasa = .FALSE.
CABLE_USER%CALL_POP = .FALSE.
END IF

! TODO(Sean): overwriting l_casacnp defeats the purpose of it being a namelist
! option - we should either deprecate the l_casacnp option or not overwrite
! its value.
l_casacnp = icycle > 0

IF (l_casacnp .AND. (icycle == 0 .OR. icycle > 3)) THEN
STOP 'icycle must be 1 to 3 when using casaCNP'
END IF
IF (l_laiFeedbk .OR. l_vcmaxFeedbk) THEN
STOP 'casaCNP required to get prognostic LAI or Vcmax'
END IF
IF (l_vcmaxFeedbk .AND. icycle < 1) THEN
STOP 'icycle must be 2 to 3 to get prognostic Vcmax'
END IF
IF (icycle > 0 .AND. (.NOT. soilparmnew)) THEN
STOP 'casaCNP must use new soil parameters'
END IF

END SUBROUTINE cable_driver_init

END MODULE cable_driver_init_mod
33 changes: 2 additions & 31 deletions src/offline/cable_mpimaster.F90
Original file line number Diff line number Diff line change
Expand Up @@ -79,10 +79,8 @@ MODULE cable_mpimaster
vegparmnew, &
spinup, &
spincasa, &
l_casacnp, &
CASAONLY, &
l_landuse, &
l_laiFeedbk, &
l_vcmaxFeedbk, &
delsoilM, &
delsoilT, &
delgwM
Expand Down Expand Up @@ -168,7 +166,7 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal)
USE cable_def_types_mod
USE cable_IO_vars_module, ONLY: logn,gswpfile,ncciy,leaps,globalMetfile, &
output,check,&
patch_type,landpt,soilparmnew,&
patch_type,landpt,&
timeunits, exists, output, &
calendar
USE cable_common_module, ONLY: ktau_gl, kend_gl, knode_gl, cable_user, &
Expand Down Expand Up @@ -282,7 +280,6 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal)

LOGICAL, SAVE :: &
spinConv = .FALSE., & ! has spinup converged?
CASAONLY = .FALSE., & ! ONLY Run CASA-CNP
CALL1 = .TRUE.

! temporary storage for soil moisture/temp. in spin up mode
Expand Down Expand Up @@ -350,23 +347,6 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal)
ENDIF
ENDIF

IF ( icycle .GE. 11 ) THEN
icycle = icycle - 10
CASAONLY = .TRUE.
CABLE_USER%CASA_DUMP_READ = .TRUE.
CABLE_USER%CASA_DUMP_WRITE = .FALSE.
ELSEIF ( icycle .EQ. 0 ) THEN
CABLE_USER%CASA_DUMP_READ = .FALSE.
CABLE_USER%CALL_POP = .FALSE.
ENDIF

! vh_js !
IF (icycle.GT.0) THEN
l_casacnp = .TRUE.
ELSE
l_casacnp = .FALSE.
ENDIF

! vh_js ! suggest LALLOC should ulitmately be a switch in the .nml file
IF (CABLE_USER%CALL_POP) THEN
LALLOC = 3 ! for use with POP: makes use of pipe model to partition between stem and leaf
Expand All @@ -379,15 +359,6 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal)
cable_user%MetType = 'gswp'
ENDIF

IF( l_casacnp .AND. ( icycle == 0 .OR. icycle > 3 ) ) &
STOP 'icycle must be 1 to 3 when using casaCNP'
IF( ( l_laiFeedbk .OR. l_vcmaxFeedbk ) .AND. ( .NOT. l_casacnp ) ) &
STOP 'casaCNP required to get prognostic LAI or Vcmax'
IF( l_vcmaxFeedbk .AND. icycle < 2 ) &
STOP 'icycle must be 2 to 3 to get prognostic Vcmax'
IF( icycle > 0 .AND. ( .NOT. soilparmnew ) ) &
STOP 'casaCNP must use new soil parameters'

! casa time count
ctime = 0

Expand Down
32 changes: 2 additions & 30 deletions src/offline/cable_mpiworker.F90
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ MODULE cable_mpiworker
vegparmnew, &
spinup, &
spincasa, &
l_casacnp, &
CASAONLY, &
l_laiFeedbk, &
l_vcmaxFeedbk, &
delsoilM, &
Expand Down Expand Up @@ -129,7 +129,7 @@ SUBROUTINE mpidrv_worker (comm)
USE cable_def_types_mod
USE cable_IO_vars_module, ONLY: logn,leaps, &
output,check,&
patch_type,soilparmnew,&
patch_type,&
NO_CHECK
USE cable_common_module, ONLY: ktau_gl, kend_gl, knode_gl, cable_user, &
cable_runtime, filename, &
Expand Down Expand Up @@ -213,7 +213,6 @@ SUBROUTINE mpidrv_worker (comm)

LOGICAL, SAVE :: &
spinConv = .FALSE., & ! has spinup converged?
CASAONLY = .FALSE., & ! ONLY Run CASA-CNP
CALL1 = .TRUE.

! MPI:
Expand All @@ -236,24 +235,6 @@ SUBROUTINE mpidrv_worker (comm)
IF (CABLE_USER%POPLUC .AND. TRIM(CABLE_USER%POPLUC_RunType) .EQ. 'static') &
CABLE_USER%POPLUC= .FALSE.

IF ( icycle .GE. 11 ) THEN
icycle = icycle - 10
CASAONLY = .TRUE.
CABLE_USER%CASA_DUMP_READ = .TRUE.
CABLE_USER%CASA_DUMP_WRITE = .FALSE.
ELSEIF ( icycle .EQ. 0 ) THEN
CABLE_USER%CASA_DUMP_READ = .FALSE.
spincasa = .FALSE.
CABLE_USER%CALL_POP = .FALSE.
ENDIF

! vh_js !
IF (icycle.GT.0) THEN
l_casacnp = .TRUE.
ELSE
l_casacnp = .FALSE.
ENDIF

! vh_js ! suggest LALLOC should ulitmately be a switch in the .nml file
IF (CABLE_USER%CALL_POP) THEN
LALLOC = 3 ! for use with POP: makes use of pipe model to partition between stem and leaf
Expand All @@ -266,15 +247,6 @@ SUBROUTINE mpidrv_worker (comm)
cable_user%MetType = 'gswp'
ENDIF

IF( l_casacnp .AND. ( icycle == 0 .OR. icycle > 3 ) ) &
STOP 'icycle must be 1 to 3 when using casaCNP'
IF( ( l_laiFeedbk .OR. l_vcmaxFeedbk ) .AND. ( .NOT. l_casacnp ) ) &
STOP 'casaCNP required to get prognostic LAI or Vcmax'
IF( l_vcmaxFeedbk .AND. icycle < 2 ) &
STOP 'icycle must be 2 to 3 to get prognostic Vcmax'
IF( icycle > 0 .AND. ( .NOT. soilparmnew ) ) &
STOP 'casaCNP must use new soil parameters'

! Check for gswp run
! MPI: done by the master only; if check fails then master MPI_Aborts
! everyone
Expand Down
33 changes: 2 additions & 31 deletions src/offline/cable_serial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,7 @@ MODULE cable_serial
vegparmnew, &
spinup, &
spincasa, &
CASAONLY, &
l_casacnp, &
l_landuse, &
l_laiFeedbk, &
Expand All @@ -75,7 +76,7 @@ MODULE cable_serial
USE cable_def_types_mod
USE cable_IO_vars_module, ONLY: logn,gswpfile,ncciy,leaps, &
fixedCO2,output,check,&
patch_type,landpt,soilparmnew,&
patch_type,landpt,&
defaultLAI, sdoy, smoy, syear, timeunits, exists, calendar, &
NO_CHECK
USE casa_ncdf_module, ONLY: is_casa_time
Expand Down Expand Up @@ -225,7 +226,6 @@ SUBROUTINE serialdrv(trunk_sumbal)

LOGICAL, SAVE :: &
spinConv = .FALSE., & ! has spinup converged?
CASAONLY = .FALSE., & ! ONLY Run CASA-CNP
CALL1 = .TRUE., &
SPINon= .TRUE.

Expand Down Expand Up @@ -286,26 +286,6 @@ SUBROUTINE serialdrv(trunk_sumbal)
ENDIF
ENDIF

IF ( icycle .GE. 11 ) THEN
icycle = icycle - 10
CASAONLY = .TRUE.
CABLE_USER%CASA_DUMP_READ = .TRUE.
CABLE_USER%CASA_DUMP_WRITE = .FALSE.
ELSEIF ( icycle .EQ. 0 ) THEN
CABLE_USER%CASA_DUMP_READ = .FALSE.
spincasa = .FALSE.

! vh_js !
CABLE_USER%CALL_POP = .FALSE.
ENDIF

! vh_js !
IF (icycle.GT.0) THEN
l_casacnp = .TRUE.
ELSE
l_casacnp = .FALSE.
ENDIF

! vh_js ! suggest LALLOC should ulitmately be a switch in the .nml file
IF (CABLE_USER%CALL_POP) THEN
LALLOC = 3 ! for use with POP: makes use of pipe model to partition between stem and leaf
Expand All @@ -328,15 +308,6 @@ SUBROUTINE serialdrv(trunk_sumbal)
cable_user%MetType = 'gswp'
ENDIF

IF( l_casacnp .AND. ( icycle == 0 .OR. icycle > 3 ) ) &
STOP 'icycle must be 1 to 3 when using casaCNP'
!IF( ( l_laiFeedbk .OR. l_vcmaxFeedbk ) ) &
! STOP 'casaCNP required to get prognostic LAI or Vcmax'
IF( l_vcmaxFeedbk .AND. icycle < 1 ) &
STOP 'icycle must be 2 to 3 to get prognostic Vcmax'
IF( icycle > 0 .AND. ( .NOT. soilparmnew ) ) &
STOP 'casaCNP must use new soil parameters'

NRRRR = MERGE(MAX(CABLE_USER%CASA_NREP,1), 1, CASAONLY)
! casa time count
ctime = 0
Expand Down

0 comments on commit 96bf22c

Please sign in to comment.