Skip to content

Commit

Permalink
adjust plumbing to USE cable_surface_types offline (#446)
Browse files Browse the repository at this point in the history
# CABLE

The same module name can indeed be USEd as there are seperate versions
picked up by coupled/offline apps. However some additional plumbing
needs to be tweaked offline.

Please see issue for further details:
Fixes #436
## Type of change

## Checklist

- [x] The new content is accessible and located in the appropriate
section.
- [x] I have checked that links are valid and point to the intended
content.
- [x] I have checked my code/text and corrected any misspellings

Please add a reviewer when ready for review.


<!-- readthedocs-preview cable start -->
----
📚 Documentation preview 📚:
https://cable--446.org.readthedocs.build/en/446/

<!-- readthedocs-preview cable end -->

---------

Co-authored-by: Ben Schroeter <benjschroeter@gmail.com>
Co-authored-by: Claire Carouge <claire.carouge@anu.edu.au>
  • Loading branch information
3 people authored Nov 24, 2024
1 parent babfe01 commit af51c0a
Show file tree
Hide file tree
Showing 10 changed files with 117 additions and 88 deletions.
1 change: 1 addition & 0 deletions CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,7 @@ add_library(
src/offline/cbl_model_driver_offline.F90
src/offline/landuse_inout.F90
src/offline/spincasacnp.F90
src/offline/cable_surface_types.F90
src/params/cable_maths_constants_mod.F90
src/params/cable_other_constants_mod.F90
src/params/cable_photo_constants_mod.F90
Expand Down
5 changes: 3 additions & 2 deletions src/offline/cable_parameters.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2461,8 +2461,9 @@ SUBROUTINE consistency_ice_veg_soil(soil, veg)
! Ensure that when an active patch has a veg type of ice then its soil type is also ice and vice versa
! Any change effected to enforce this consistency includes correcting the appropriate paramter values

USE grid_constants_mod_cbl, ONLY : ICE_SoilType, ICE_VegType => ice_cable
USE cable_phys_constants_mod, ONLY : csice, density_ice
USE grid_constants_mod_cbl, ONLY: ICE_SoilType
USE cable_surface_types_mod, ONLY: ICE_VegType => ice_cable
USE cable_phys_constants_mod, ONLY: csice, density_ice

TYPE (soil_parameter_type), INTENT(INOUT) :: soil ! soil parameter data
TYPE (veg_parameter_type), INTENT(INOUT) :: veg ! vegetation parameter
Expand Down
37 changes: 37 additions & 0 deletions src/offline/cable_surface_types.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
!#define UM_CBL YES
!******************************************************************************
! 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

89 changes: 45 additions & 44 deletions src/offline/cbl_model_driver_offline.F90
Original file line number Diff line number Diff line change
Expand Up @@ -39,57 +39,58 @@ SUBROUTINE cbm( ktau,dels, air, bgc, canopy, met,
bal, rad, rough, soil, &
ssnow, sum_flux, veg, climate, xk, c1, rhoch )

USE cable_common_module
USE cable_carbon_module
USE cbl_soil_snow_main_module, ONLY : soil_snow
USE cable_def_types_mod
USE cable_roughness_module, ONLY : ruff_resist
USE cbl_init_radiation_module, ONLY : init_radiation
USE cable_air_module, ONLY : define_air
USE casadimension, ONLY : icycle ! used in casa_cnp
USE cable_common_module
USE cable_carbon_module
USE cbl_soil_snow_main_module, ONLY : soil_snow
USE cable_def_types_mod
USE cable_roughness_module, ONLY : ruff_resist
USE cbl_init_radiation_module, ONLY : init_radiation
USE cable_air_module, ONLY : define_air
USE casadimension, ONLY : icycle ! used in casa_cnp
! physical constants
USE cable_phys_constants_mod, ONLY : CGRAV => GRAV
USE cable_phys_constants_mod, ONLY : CCAPP => CAPP
USE cable_phys_constants_mod, ONLY : CEMLEAF => EMLEAF
USE cable_phys_constants_mod, ONLY : CEMSOIL => EMSOIL
USE cable_phys_constants_mod, ONLY : CSBOLTZ => SBOLTZ
USE cable_phys_constants_mod, ONLY : density_liq
!mrd561
USE cable_gw_hydro_module, ONLY : sli_hydrology,&
soil_snow_gw
USE cable_canopy_module, ONLY : define_canopy
USE cbl_albedo_mod, ONLY : albedo
USE sli_main_mod, ONLY : sli_main
USE snow_aging_mod, ONLY: snow_aging

!data !jhan:pass these
USE cable_other_constants_mod, ONLY : CLAI_THRESH => lai_thresh
USE cable_other_constants_mod, ONLY : Crad_thresh => rad_thresh
USE cable_other_constants_mod, ONLY : Ccoszen_tols => coszen_tols
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 cbl_masks_mod, ONLY : fveg_mask, fsunlit_mask, fsunlit_veg_mask
USE grid_constants_mod_cbl, ONLY : ICE_SoilType, lakes_cable

! CABLE model variables
TYPE (air_type), INTENT(INOUT) :: air
TYPE (bgc_pool_type), INTENT(INOUT) :: bgc
TYPE (canopy_type), INTENT(INOUT) :: canopy
TYPE (met_type), INTENT(INOUT) :: met
TYPE (balances_type), INTENT(INOUT) :: bal
TYPE (radiation_type), INTENT(INOUT) :: rad
TYPE (roughness_type), INTENT(INOUT) :: rough
TYPE (soil_snow_type), INTENT(INOUT) :: ssnow
TYPE (sum_flux_type), INTENT(INOUT) :: sum_flux
TYPE (climate_type), INTENT(IN) :: climate

TYPE (soil_parameter_type), INTENT(INOUT) :: soil
TYPE (veg_parameter_type), INTENT(INOUT) :: veg

REAL, INTENT(IN) :: dels ! time setp size (s)
INTEGER, INTENT(IN) :: ktau
INTEGER :: k,kk,j
!mrd561
USE cable_gw_hydro_module, ONLY : sli_hydrology,&
soil_snow_gw
USE cable_canopy_module, ONLY : define_canopy
USE cbl_albedo_mod, ONLY : albedo
USE sli_main_mod, ONLY : sli_main
USE snow_aging_mod, ONLY: snow_aging

!data
USE cable_other_constants_mod, ONLY: CLAI_THRESH => lai_thresh
USE cable_other_constants_mod, ONLY: Crad_thresh => rad_thresh
USE cable_other_constants_mod, ONLY: Ccoszen_tols => coszen_tols
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 cbl_masks_mod, ONLY: fveg_mask, fsunlit_mask, fsunlit_veg_mask
USE cable_surface_types_mod, ONLY: lakes_cable
USE grid_constants_mod_cbl, ONLY: ICE_SoilType

! CABLE model variables
TYPE (air_type), INTENT(INOUT) :: air
TYPE (bgc_pool_type), INTENT(INOUT) :: bgc
TYPE (canopy_type), INTENT(INOUT) :: canopy
TYPE (met_type), INTENT(INOUT) :: met
TYPE (balances_type), INTENT(INOUT) :: bal
TYPE (radiation_type), INTENT(INOUT) :: rad
TYPE (roughness_type), INTENT(INOUT) :: rough
TYPE (soil_snow_type), INTENT(INOUT) :: ssnow
TYPE (sum_flux_type), INTENT(INOUT) :: sum_flux
TYPE (climate_type), INTENT(IN) :: climate

TYPE (soil_parameter_type), INTENT(INOUT) :: soil
TYPE (veg_parameter_type), INTENT(INOUT) :: veg

REAL, INTENT(IN) :: dels ! time setp size (s)
INTEGER, INTENT(IN) :: ktau
INTEGER :: k,kk,j

LOGICAL :: veg_mask(mp), sunlit_mask(mp), sunlit_veg_mask(mp)

Expand Down
12 changes: 3 additions & 9 deletions src/params/grid_constants_cbl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -46,17 +46,11 @@ MODULE grid_constants_mod_cbl
INTEGER, PARAMETER :: nsCs = 2 ! # soil carbon stores
INTEGER, PARAMETER :: nvCs = 3 ! # vegetation carbon stores
INTEGER, PARAMETER :: ICE_SoilType = 9 ! SoilType Index (soilparm_cable.nml JAC)
#ifndef UM_CBL
! UM_CBL gets from cable_surface_types namelist
INTEGER, PARAMETER :: lakes_cable = 16 ! cable_surface_type (nml) Index
INTEGER, PARAMETER :: ice_cable = 17 ! cable_surface_type (nml) Index
#endif
INTEGER, PARAMETER :: mf = 2 ! # leaves (sunlit, shaded)
INTEGER, PARAMETER :: niter = 4 ! number of iterations for za/L
INTEGER, PARAMETER :: swb = 2 ! # SW bands (VIS+NIR) - CM3 alloc TYPEs
INTEGER, PARAMETER :: mf = 2 ! # leaves (sunlit, shaded)
INTEGER, PARAMETER :: niter = 4 ! number of iterations for za/L
INTEGER, PARAMETER :: swb = 2 ! # SW bands (VIS+NIR) - CM3 alloc TYPEs

! Strictly NOT a constant. # of active tiles, length of CABLE working vectors
INTEGER :: mp


END MODULE grid_constants_mod_cbl
36 changes: 19 additions & 17 deletions src/science/canopy/cbl_SurfaceWetness.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,30 +9,32 @@ MODULE cbl_SurfaceWetness_module

SUBROUTINE Surf_wetness_fact( cansat, canopy, ssnow,veg, met, soil, dels )

USE cable_common_module
USE cable_def_types_mod
USE grid_constants_mod_cbl, ONLY : lakes_cable
! physical constants
USE cable_phys_constants_mod, ONLY : CTFRZ => TFRZ
!H!USE cable_gw_hydro_module, ONLY : calc_srf_wet_fraction
USE cable_common_module
USE cable_def_types_mod

! data
USE cable_surface_types_mod, ONLY: lakes_cable
USE cable_phys_constants_mod, ONLY: CTFRZ => TFRZ

use cable_init_wetfac_mod, ONLY: initialize_wetfac
!H!USE cable_gw_hydro_module, ONLY : calc_srf_wet_fraction

TYPE (veg_parameter_type), INTENT(INOUT) :: veg
TYPE (soil_snow_type), INTENT(inout):: ssnow
TYPE (soil_parameter_type), INTENT(inout) :: soil
TYPE (canopy_type), INTENT(INOUT) :: canopy
TYPE (met_type), INTENT(INOUT) :: met

REAL, INTENT(IN) :: dels ! integration time setp (s)
use cable_init_wetfac_mod, ONLY: initialize_wetfac

REAL,INTENT(IN), DIMENSION(:) :: cansat ! max canopy intercept. (mm)
TYPE (veg_parameter_type), INTENT(INOUT) :: veg
TYPE (soil_snow_type), INTENT(inout):: ssnow
TYPE (soil_parameter_type), INTENT(inout) :: soil
TYPE (canopy_type), INTENT(INOUT) :: canopy
TYPE (met_type), INTENT(INOUT) :: met

!local variables
REAL, DIMENSION(mp) :: lower_limit, upper_limit,ftemp
REAL, INTENT(IN) :: dels ! integration time setp (s)

INTEGER :: j, i
REAL,INTENT(IN), DIMENSION(:) :: cansat ! max canopy intercept. (mm)

!local variables
REAL, DIMENSION(mp) :: lower_limit, upper_limit,ftemp

INTEGER :: j, i

! Rainfall variable is limited so canopy interception is limited,
! used to stabilise latent fluxes.
Expand Down
4 changes: 2 additions & 2 deletions src/science/canopy/cbl_init_wetfac_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ SUBROUTINE initialize_wetfac( &


! Imports
USE grid_constants_mod_cbl, ONLY: lakes_cable
USE cable_surface_types_mod, ONLY: lakes_cable
USE cable_def_types_mod, ONLY : r_2
USE cable_other_constants_mod, ONLY : wilt_limitfactor

Expand Down Expand Up @@ -115,4 +115,4 @@ SUBROUTINE initialize_wetfac( &

END SUBROUTINE initialize_wetfac

END MODULE cable_init_wetfac_mod
END MODULE cable_init_wetfac_mod
6 changes: 3 additions & 3 deletions src/science/gw_hydro/cable_gw_hydro.F90
Original file line number Diff line number Diff line change
Expand Up @@ -337,7 +337,7 @@ SUBROUTINE ovrlndflx (dels, ssnow, soil,veg, canopy,sli_call )

USE cable_common_module, ONLY : gw_params,cable_user

USE grid_constants_mod_cbl, ONLY : lakes_cable
USE cable_surface_types_mod, ONLY: lakes_cable

IMPLICIT NONE
REAL, INTENT(IN) :: dels ! integration time step (s)
Expand Down Expand Up @@ -1387,7 +1387,7 @@ SUBROUTINE calc_srf_wet_fraction(ssnow,soil,met,veg)
! following [Decker, 2015](http://doi.wiley.com/10.1002/2015MS000507)


USE grid_constants_mod_cbl, ONLY : lakes_cable
USE cable_surface_types_mod, ONLY: lakes_cable

IMPLICIT NONE
TYPE(soil_snow_type), INTENT(INOUT) :: ssnow ! soil+snow variables
Expand Down Expand Up @@ -1755,7 +1755,7 @@ SUBROUTINE subsurface_drainage(ssnow,soil,veg)
! [Decker, 2015](http://doi.wiley.com/10.1002/2015MS000507)

USE cable_common_module
USE grid_constants_mod_cbl, ONLY : lakes_cable
USE cable_surface_types_mod, ONLY: lakes_cable

IMPLICIT NONE

Expand Down
5 changes: 0 additions & 5 deletions src/science/roughness/cable_roughness.F90
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
!#define UM_CBL YES
!==============================================================================
! This source code is part of the
! Australian Community Atmosphere Biosphere Land Exchange (CABLE) model.
Expand All @@ -23,11 +22,7 @@

MODULE cable_roughness_module

#ifdef UM_CBL
USE cable_surface_types_mod, ONLY: ICE_SurfaceType => ICE_cable
#else
USE grid_constants_mod_cbl, ONLY: ICE_SurfaceType => ICE_cable
#endif
USE cable_phys_constants_mod, ONLY: CCSD => CSD
USE cable_phys_constants_mod, ONLY: CCRD => CRD
USE cable_phys_constants_mod, ONLY: CCCD => CCD
Expand Down
10 changes: 4 additions & 6 deletions src/science/soilsnow/cbl_surfbv.F90
Original file line number Diff line number Diff line change
Expand Up @@ -8,15 +8,13 @@ MODULE surfbv_mod
CONTAINS

SUBROUTINE surfbv (dels, met, ssnow, soil, veg, canopy )
! subrs
USE smoisturev_mod, ONLY: smoisturev

USE smoisturev_mod, ONLY: smoisturev
USE cable_common_module
! data
#ifdef UM_CBL
USE cable_surface_types_mod, ONLY: lakes_cable
#else
USE grid_constants_mod_cbl, ONLY: lakes_cable
#endif

USE cable_common_module

IMPLICIT NONE

Expand Down

0 comments on commit af51c0a

Please sign in to comment.