Skip to content

Commit

Permalink
Merge branch 'main' into 441-investigate-compiling-science-code-as-li…
Browse files Browse the repository at this point in the history
…brary
  • Loading branch information
bschroeter authored Nov 28, 2024
2 parents fdd0d75 + 960970d commit 8c83bf1
Show file tree
Hide file tree
Showing 24 changed files with 364 additions and 409 deletions.
2 changes: 2 additions & 0 deletions documentation/docs/user_guide/inputs/cable_nml.md
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,8 @@ applications. The following are annotated examples of cable.nml:
| filename%fxpft | character(len=500) | any string of max. 500 characters | uninitialised | Plant functional type fraction, wood harvest and secondary harvest file. |
| filename%fxluh2cable | character(len=500) | any string of max. 500 characters | uninitialised | 12 land-use states into 17 CABLE plant functional types mapping file name. |
| filename%gridnew | character(len=500) | any string of max. 500 characters | uninitialised | Updated gridinfo file name. |
| filename%trunk_sumbal | character(len=500) | any string of max. 500 characters | '.trunk_sumbal' | Input filename to read combined energy and water balance at each timestep (control run). Used when `consistency_check` is TRUE |
| filename%new_sumbal | character(len=500) | any string of max. 500 characters | 'new_sumbal' | Output filename to write combined energy and water balance at each timestep (current run). Used when `consistency_check` is TRUE |
| vegparmnew | logical | .TRUE. .FALSE. | .FALSE. but was .TRUE. in ESM1.5 | Use new format for vegetation parameter files when .TRUE. |
| soilparmnew | logical | .TRUE. .FALSE. | uninitialised | Use new format for soil parameter files when .TRUE. |
| spinup | logical | .TRUE. .FALSE. | .FALSE. | Spin up the model when .TRUE. |
Expand Down
3 changes: 2 additions & 1 deletion src/coupled/ESM1.5/CABLEfilesFromESM1.5/cable_cbm.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,8 @@ SUBROUTINE cbm( dels, air, bgc, canopy, met, &
USE cable_other_constants_mod, ONLY: cgauss_w => gauss_w
USE cable_math_constants_mod, ONLY: cpi => pi
USE cable_math_constants_mod, ONLY: cpi180 => pi180
USE grid_constants_mod_cbl, ONLY : ICE_SoilType, lakes_cable
USE cable_surface_types_mod, ONLY: lakes_cable
USE grid_constants_mod_cbl, ONLY: ICE_SoilType


USE cable_common_module
Expand Down
3 changes: 2 additions & 1 deletion src/coupled/ESM1.5/CABLEfilesFromESM1.5/cable_rad_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,8 @@ SUBROUTINE cable_rad_driver( &
USE cable_common_module, ONLY : cable_runtime, cable_user

USE cbl_init_radiation_module, ONLY: Common_InitRad_Scalings
USE grid_constants_mod_cbl, ONLY : ICE_SoilType, lakes_cable
USE grid_constants_mod_cbl, ONLY: ICE_SoilType
USE cable_surface_types_mod, ONLY: lakes_cable

IMPLICIT NONE

Expand Down
35 changes: 35 additions & 0 deletions src/coupled/ESM1.5/cable_surface_types.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
!******************************************************************************
! This source code is part of the Community Atmosphere Biosphere Land Exchange
! (CABLE) model. This work is licensed under the CSIRO Open Source Software
! License Agreement (variation of the BSD / MIT License).You may not use this
! this file except in compliance with this License. A copy of the License is
! available at https://trac.nci.org.au/trac/cable/wiki/license.
!******************************************************************************

MODULE cable_surface_types_mod

IMPLICIT NONE

PUBLIC

! cable_surface_type (nml) Index
INTEGER, PARAMETER :: evergreen_needleleaf = 1
INTEGER, PARAMETER :: evergreen_broadleaf = 2
INTEGER, PARAMETER :: deciduous_needleleaf = 3
INTEGER, PARAMETER :: deciduous_broadleaf = 4
INTEGER, PARAMETER :: shrub_cable = 5
INTEGER, PARAMETER :: c3_grassland = 6
INTEGER, PARAMETER :: c4_grassland = 7
INTEGER, PARAMETER :: tundra = 8
INTEGER, PARAMETER :: c3_cropland = 9
INTEGER, PARAMETER :: c4_cropland = 10
INTEGER, PARAMETER :: wetland = 11
INTEGER, PARAMETER :: empty1 = 12
INTEGER, PARAMETER :: empty2 = 13
INTEGER, PARAMETER :: barren_cable = 14
INTEGER, PARAMETER :: urban_cable = 15
INTEGER, PARAMETER :: lakes_cable = 16
INTEGER, PARAMETER :: ice_cable = 17

END MODULE cable_surface_types_mod

103 changes: 95 additions & 8 deletions src/offline/cable_driver_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,8 @@ MODULE cable_driver_init_mod
wiltParam, &
satuParam, &
cable_user, &
gw_params
gw_params, &
cable_runtime
USE cable_IO_vars_module, ONLY : &
soilparmnew, &
output, &
Expand All @@ -23,19 +24,24 @@ MODULE cable_driver_init_mod
fixedCO2, &
ncciy, &
gswpfile, &
globalMetfile
globalMetfile, &
set_group_output_values
USE casadimension, ONLY : icycle
USE casavariable, ONLY : casafile
USE cable_namelist_util, ONLY : &
get_namelist_file_name, &
CABLE_NAMELIST
CABLE_NAMELIST, &
arg_not_namelist
USE cable_mpi_mod, ONLY : mpi_grp_t
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 All @@ -45,6 +51,8 @@ MODULE cable_driver_init_mod
REAL, SAVE, PUBLIC :: delsoilT ! allowed variation in soil temperature for spin up
REAL, SAVE, PUBLIC :: delgwM = 1e-4

INTEGER, SAVE, PUBLIC :: LALLOC = 0 ! allocation coefficient for passing to spincasa

NAMELIST /CABLE/ &
filename, & ! TYPE, containing input filenames
vegparmnew, & ! use new soil param. method
Expand All @@ -66,6 +74,7 @@ MODULE cable_driver_init_mod
l_landuse, &
l_laiFeedbk, &
l_vcmaxFeedbk, &
CASAONLY, &
icycle, &
casafile, &
ncciy, &
Expand All @@ -81,10 +90,15 @@ MODULE cable_driver_init_mod

CONTAINS

SUBROUTINE cable_driver_init(mpi_grp)
SUBROUTINE cable_driver_init(mpi_grp, trunk_sumbal, NRRRR)
!! Model initialisation routine for the CABLE offline driver.
TYPE(mpi_grp_t), INTENT(IN) :: mpi_grp !! MPI group to use
DOUBLE PRECISION, INTENT(OUT) :: trunk_sumbal
!! Reference value for quasi-bitwise reproducibility checks.
INTEGER, INTENT(OUT) :: NRRRR !! Number of repeated spin-up cycles

!! Model initialisation routine for the CABLE offline driver.
INTEGER :: ioerror, unit
CHARACTER(len=4) :: cRank ! for worker-logfiles

!check to see if first argument passed to cable is
!the name of the namelist file
Expand All @@ -96,9 +110,82 @@ SUBROUTINE cable_driver_init(mpi_grp)
END IF

! Open, read and close the namelist file.
OPEN(10, FILE=CABLE_NAMELIST, STATUS="OLD", ACTION="READ")
READ(10, NML=CABLE)
CLOSE(10)
OPEN(NEWUNIT=unit, FILE=CABLE_NAMELIST, STATUS="OLD", ACTION="READ")
READ(unit, NML=CABLE)
CLOSE(unit)

cable_runtime%offline = .TRUE.

! Open, read and close the consistency check file.
! Check triggered by cable_user%consistency_check = .TRUE. in cable.nml
IF (mpi_grp%rank == 0 .AND. cable_user%consistency_check) THEN
OPEN(NEWUNIT=unit, FILE=filename%trunk_sumbal, STATUS='old', ACTION='READ', IOSTAT=ioerror)
IF(ioerror == 0) THEN
READ(unit, *) trunk_sumbal ! written by previous trunk version
END IF
CLOSE(unit)
END IF

! Open log file:
IF (mpi_grp%rank == 0) THEN
OPEN(logn, FILE=filename%log)
ELSE IF (cable_user%logworker) THEN
WRITE(cRank, FMT='(I4.4)') mpi_grp%rank
OPEN(NEWUNIT=logn, FILE="cable_log_"//cRank, STATUS="REPLACE")
ELSE
OPEN(NEWUNIT=logn, FILE="/dev/null")
END IF

IF (IARGC() > 0 .AND. arg_not_namelist) THEN
CALL GETARG(1, filename%met)
CALL GETARG(2, casafile%cnpipool)
END IF

! Initialise flags to output individual variables according to group
! options from the namelist file
IF (mpi_grp%rank == 0) THEN
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) .AND. (.NOT. l_casacnp)) THEN
STOP 'casaCNP required to get prognostic LAI or Vcmax'
END IF
IF (l_vcmaxFeedbk .AND. (icycle < 2 .OR. icycle > 3)) 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

! 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
END IF

NRRRR = MERGE(MAX(cable_user%CASA_NREP,1), 1, CASAONLY)

END SUBROUTINE cable_driver_init

Expand Down
Loading

0 comments on commit 8c83bf1

Please sign in to comment.