Skip to content

Commit

Permalink
rename vars, add arg to test and depth arg.
Browse files Browse the repository at this point in the history
  • Loading branch information
mvdebolskiy committed Jul 22, 2024
1 parent 699936e commit 9ba2b5f
Show file tree
Hide file tree
Showing 6 changed files with 79 additions and 50 deletions.
16 changes: 8 additions & 8 deletions src/biogeophys/TemperatureType.F90
Original file line number Diff line number Diff line change
Expand Up @@ -120,8 +120,8 @@ module TemperatureType
real(r8), pointer :: c_h2osfc_col (:) ! heat capacity of surface water

! Namelist parameters for initialization
real(r8), private :: excess_ice_coldstart_depth ! depth below which excess ice will be present
real(r8), private :: excess_ice_coldstart_temp ! coldstart temperature of layers with excess ice present
real(r8) :: excess_ice_coldstart_depth ! depth below which excess ice will be present
real(r8) :: excess_ice_coldstart_temp ! coldstart temperature of layers with excess ice present

contains

Expand All @@ -147,7 +147,7 @@ module TemperatureType
!------------------------------------------------------------------------
subroutine Init(this, bounds, &
em_roof_lun, em_wall_lun, em_improad_lun, em_perroad_lun, &
is_simple_buildtemp, is_prog_buildtemp, exice_init_stream_col, NLFileName)
is_simple_buildtemp, is_prog_buildtemp, exice_init_conc_col, NLFileName)
!
! !DESCRIPTION:
!
Expand All @@ -162,7 +162,7 @@ subroutine Init(this, bounds, &
real(r8) , intent(in) :: em_perroad_lun(bounds%begl:)
logical , intent(in) :: is_simple_buildtemp ! Simple building temp is being used
logical , intent(in) :: is_prog_buildtemp ! Prognostic building temp is being used
real(r8) , intent(in) :: exice_init_stream_col(bounds%begc:) ! initial excess ice concentration from the stream file
real(r8) , intent(in) :: exice_init_conc_col(bounds%begc:) ! initial coldstart excess ice concentration (from the stream file)
character(len=*) , intent(in) :: NLFilename ! Namelist filename


Expand All @@ -175,7 +175,7 @@ subroutine Init(this, bounds, &
em_improad_lun(bounds%begl:bounds%endl), &
em_perroad_lun(bounds%begl:bounds%endl), &
is_simple_buildtemp, is_prog_buildtemp, &
exice_init_stream_col(bounds%begc:bounds%endc) )
exice_init_conc_col(bounds%begc:bounds%endc) )

end subroutine Init

Expand Down Expand Up @@ -650,7 +650,7 @@ end subroutine InitHistory
!-----------------------------------------------------------------------
subroutine InitCold(this, bounds, &
em_roof_lun, em_wall_lun, em_improad_lun, em_perroad_lun, &
is_simple_buildtemp, is_prog_buildtemp, exice_init_stream_col)
is_simple_buildtemp, is_prog_buildtemp, exice_init_conc_col)
!
! !DESCRIPTION:
! Initialize cold start conditions for module variables
Expand All @@ -675,7 +675,7 @@ subroutine InitCold(this, bounds, &
real(r8) , intent(in) :: em_perroad_lun(bounds%begl:)
logical , intent(in) :: is_simple_buildtemp ! Simple building temp is being used
logical , intent(in) :: is_prog_buildtemp ! Prognostic building temp is being used
real(r8) , intent(in) :: exice_init_stream_col(bounds%begc:) ! initial ammount of excess ice from the stream file
real(r8) , intent(in) :: exice_init_conc_col(bounds%begc:) ! initial coldstart excess ice concentration (from the stream file)
!
! !LOCAL VARIABLES:
integer :: j,l,c,p ! indices
Expand Down Expand Up @@ -757,7 +757,7 @@ subroutine InitCold(this, bounds, &
end if
else
this%t_soisno_col(c,1:nlevgrnd) = 272._r8
if (use_excess_ice .and. exice_init_stream_col(c) > 0.0_r8) then
if (use_excess_ice .and. exice_init_conc_col(c) > 0.0_r8) then
nexice_start = nlevsoi - 1
if (this%excess_ice_coldstart_depth <= 0.0_r8) then
! we double check this here, and when building namelists
Expand Down
8 changes: 4 additions & 4 deletions src/biogeophys/WaterStateBulkType.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ module WaterStateBulkType

!------------------------------------------------------------------------
subroutine InitBulk(this, bounds, info, vars, &
h2osno_input_col, watsat_col, t_soisno_col, use_aquifer_layer, NLFilename, exice_init_stream_col)
h2osno_input_col, watsat_col, t_soisno_col, use_aquifer_layer, exice_coldstart_depth, exice_init_conc_col)

class(waterstatebulk_type), intent(inout) :: this
type(bounds_type) , intent(in) :: bounds
Expand All @@ -57,8 +57,8 @@ subroutine InitBulk(this, bounds, info, vars, &
real(r8) , intent(in) :: watsat_col(bounds%begc:, 1:) ! volumetric soil water at saturation (porosity)
real(r8) , intent(in) :: t_soisno_col(bounds%begc:, -nlevsno+1:) ! col soil temperature (Kelvin)
logical , intent(in) :: use_aquifer_layer ! whether an aquifer layer is used in this run
character(len=*) , intent(in) :: NLFilename ! Namelist filename
real(r8) , intent(in) :: exice_init_stream_col(bounds%begc:) ! initial ammount of excess ice from stream
real(r8) , intent(in) :: exice_coldstart_depth ! depth below which excess ice will be present
real(r8) , intent(in) :: exice_init_conc_col(bounds%begc:) ! initial coldstart excess ice concentration (from the stream file)

call this%Init(bounds = bounds, &
info = info, &
Expand All @@ -67,7 +67,7 @@ subroutine InitBulk(this, bounds, info, vars, &
watsat_col = watsat_col, &
t_soisno_col = t_soisno_col, &
use_aquifer_layer = use_aquifer_layer, &
NLFilename = NLFilename, exice_init_stream_col = exice_init_stream_col(bounds%begc:bounds%endc))
exice_coldstart_depth = exice_coldstart_depth, exice_init_conc_col = exice_init_conc_col(bounds%begc:bounds%endc))

call this%InitBulkAllocate(bounds)

Expand Down
28 changes: 14 additions & 14 deletions src/biogeophys/WaterStateType.F90
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ module WaterStateType

!------------------------------------------------------------------------
subroutine Init(this, bounds, info, tracer_vars, &
h2osno_input_col, watsat_col, t_soisno_col, use_aquifer_layer, NLFilename, exice_init_stream_col)
h2osno_input_col, watsat_col, t_soisno_col, use_aquifer_layer, exice_coldstart_depth, exice_init_conc_col)

class(waterstate_type), intent(inout) :: this
type(bounds_type) , intent(in) :: bounds
Expand All @@ -90,8 +90,8 @@ subroutine Init(this, bounds, info, tracer_vars, &
real(r8) , intent(in) :: watsat_col(bounds%begc:, 1:) ! volumetric soil water at saturation (porosity)
real(r8) , intent(in) :: t_soisno_col(bounds%begc:, -nlevsno+1:) ! col soil temperature (Kelvin)
logical , intent(in) :: use_aquifer_layer ! whether an aquifer layer is used in this run
character(len=*) , intent(in) :: NLFilename ! Namelist filename
real(r8) , intent(in) :: exice_init_stream_col(bounds%begc:bounds%endc) ! initial ammount of excess ice from stream
real(r8) , intent(in) :: exice_coldstart_depth ! depth below which excess ice will be present
real(r8) , intent(in) :: exice_init_conc_col(bounds%begc:bounds%endc) ! initial coldstart excess ice concentration (from the stream file)

this%info => info

Expand All @@ -103,7 +103,7 @@ subroutine Init(this, bounds, info, tracer_vars, &
watsat_col = watsat_col, &
t_soisno_col = t_soisno_col, &
use_aquifer_layer = use_aquifer_layer, &
NLFilename = NLFilename, exice_init_stream_col = exice_init_stream_col)
exice_coldstart_depth = exice_coldstart_depth , exice_init_conc_col = exice_init_conc_col)

end subroutine Init

Expand Down Expand Up @@ -322,7 +322,7 @@ end subroutine InitHistory

!-----------------------------------------------------------------------
subroutine InitCold(this, bounds, &
h2osno_input_col, watsat_col, t_soisno_col, use_aquifer_layer, NLFilename, exice_init_stream_col)
h2osno_input_col, watsat_col, t_soisno_col, use_aquifer_layer, exice_coldstart_depth, exice_init_conc_col)
!
! !DESCRIPTION:
! Initialize time constant variables and cold start conditions
Expand All @@ -342,12 +342,12 @@ subroutine InitCold(this, bounds, &
real(r8) , intent(in) :: watsat_col(bounds%begc:, 1:) ! volumetric soil water at saturation (porosity)
real(r8) , intent(in) :: t_soisno_col(bounds%begc:, -nlevsno+1:) ! col soil temperature (Kelvin)
logical , intent(in) :: use_aquifer_layer ! whether an aquifer layer is used in this run
character(len=*) , intent(in) :: NLFilename ! Namelist filename
real(r8) , intent(in) :: exice_init_stream_col(bounds%begc:bounds%endc) ! initial ammount of excess ice from stream
real(r8) , intent(in) :: exice_coldstart_depth ! depth below which excess ice will be present
real(r8) , intent(in) :: exice_init_conc_col(bounds%begc:bounds%endc) ! initial coldstart excess ice concentration (from the stream file)
!
! !LOCAL VARIABLES:
integer :: c,j,l,nlevs,g
integer :: nbedrock, n05m ! layer containing 0.5 m
integer :: nbedrock, nexice ! layer containing 0.5 m
real(r8) :: ratio
!-----------------------------------------------------------------------

Expand Down Expand Up @@ -550,27 +550,27 @@ subroutine InitCold(this, bounds, &
this%dynbal_baseline_ice_col(bounds%begc:bounds%endc) = 0._r8

!Initialize excess ice
this%exice_bulk_init(bounds%begc:bounds%endc) = exice_init_stream_col(bounds%begc:bounds%endc)
this%exice_bulk_init(bounds%begc:bounds%endc) = exice_init_conc_col(bounds%begc:bounds%endc)
this%excess_ice_col(bounds%begc:bounds%endc,:) = 0.0_r8
if (use_excess_ice) then
do c = bounds%begc,bounds%endc
g = col%gridcell(c)
l = col%landunit(c)
if (.not. lun%lakpoi(l)) then !not lake
if (lun%itype(l) == istsoil .or. lun%itype(l) == istcrop) then
if (zisoi(nlevsoi) >= 0.5_r8) then
call find_soil_layer_containing_depth(0.5_r8,n05m)
if (zisoi(nlevsoi) >= exice_coldstart_depth) then
call find_soil_layer_containing_depth(exice_coldstart_depth,nexice)
else
n05m=nlevsoi-1
nexice=nlevsoi-1
endif
if (use_bedrock .and. col%nbedrock(c) <=nlevsoi) then
nbedrock = col%nbedrock(c)
else
nbedrock = nlevsoi
endif
do j = 2, nlevmaxurbgrnd ! ignore first layer
if (n05m<nbedrock) then ! bedrock below 1 m
if (j >= n05m .and. j<nbedrock .and. t_soisno_col(c,j) <= tfrz ) then
if (nexice<nbedrock) then ! bedrock below 1 m
if (j >= nexice .and. j<nbedrock .and. t_soisno_col(c,j) <= tfrz ) then
this%excess_ice_col(c,j) = col%dz(c,j)*denice*(this%exice_bulk_init(c))
else
this%excess_ice_col(c,j) = 0.0_r8
Expand Down
34 changes: 18 additions & 16 deletions src/biogeophys/WaterType.F90
Original file line number Diff line number Diff line change
Expand Up @@ -213,7 +213,8 @@ end function water_params_constructor

!-----------------------------------------------------------------------
subroutine Init(this, bounds, NLFilename, &
h2osno_col, snow_depth_col, watsat_col, t_soisno_col, use_aquifer_layer, exice_init_stream_col)
h2osno_col, snow_depth_col, watsat_col, t_soisno_col, use_aquifer_layer, &
exice_coldstart_depth, exice_init_conc_col)
!
! !DESCRIPTION:
! Initialize all water variables
Expand All @@ -227,7 +228,8 @@ subroutine Init(this, bounds, NLFilename, &
real(r8) , intent(in) :: watsat_col(bounds%begc:, 1:) ! volumetric soil water at saturation (porosity)
real(r8) , intent(in) :: t_soisno_col(bounds%begc:, -nlevsno+1:) ! col soil temperature (Kelvin)
logical , intent(in) :: use_aquifer_layer ! whether an aquifer layer is used in this run
real(r8) , intent(in) :: exice_init_stream_col(bounds%begc:) ! initial ammount of excess ice from stream
real(r8) , intent(in) :: exice_coldstart_depth ! depth below which excess ice will be present
real(r8) , intent(in) :: exice_init_conc_col(bounds%begc:) ! initial coldstart excess ice concentration (from the stream file)
!
! !LOCAL VARIABLES:

Expand All @@ -241,14 +243,14 @@ subroutine Init(this, bounds, NLFilename, &
watsat_col = watsat_col, &
t_soisno_col = t_soisno_col, &
use_aquifer_layer = use_aquifer_layer, &
NLFilename = NLFilename, exice_init_stream_col = exice_init_stream_col)
exice_coldstart_depth = exice_coldstart_depth, exice_init_conc_col = exice_init_conc_col)

end subroutine Init

!-----------------------------------------------------------------------
subroutine InitForTesting(this, bounds, params, &
h2osno_col, snow_depth_col, watsat_col, &
t_soisno_col, use_aquifer_layer, NLFilename, exice_init_stream_col)
t_soisno_col, use_aquifer_layer, exice_coldstart_depth, exice_init_conc_col)
!
! !DESCRIPTION:
! Version of Init routine just for unit tests
Expand All @@ -263,9 +265,9 @@ subroutine InitForTesting(this, bounds, params, &
real(r8) , intent(in) :: snow_depth_col(bounds%begc:)
real(r8) , intent(in) :: watsat_col(bounds%begc:, 1:) ! volumetric soil water at saturation (porosity)
real(r8) , intent(in) :: t_soisno_col(bounds%begc:, -nlevsno+1:) ! col soil temperature (Kelvin)
character(len=*) , intent(in) :: NLFilename ! Namelist filename
logical , intent(in), optional :: use_aquifer_layer ! whether an aquifer layer is used in this run (false by default)
real(r8) , intent(in) :: exice_init_stream_col(bounds%begc:) ! initial ammount of excess ice from stream
real(r8) , intent(in) :: exice_coldstart_depth ! depth below which excess ice will be present
real(r8) , intent(in) :: exice_init_conc_col(bounds%begc:) ! initial coldstart excess ice concentration (from the stream file)
!
! !LOCAL VARIABLES:
logical :: l_use_aquifer_layer
Expand All @@ -285,14 +287,14 @@ subroutine InitForTesting(this, bounds, params, &
watsat_col = watsat_col, &
t_soisno_col = t_soisno_col, &
use_aquifer_layer = l_use_aquifer_layer, &
NLFilename = NLFilename, &
exice_init_stream_col = exice_init_stream_col )
exice_coldstart_depth = exice_coldstart_depth, &
exice_init_conc_col = exice_init_conc_col )

end subroutine InitForTesting

!-----------------------------------------------------------------------
subroutine DoInit(this, bounds, &
h2osno_col, snow_depth_col, watsat_col, t_soisno_col, use_aquifer_layer, NLFilename, exice_init_stream_col)
h2osno_col, snow_depth_col, watsat_col, t_soisno_col, use_aquifer_layer, exice_coldstart_depth, exice_init_conc_col)
!
! !DESCRIPTION:
! Actually do the initialization (shared between main Init routine and InitForTesting)
Expand All @@ -307,8 +309,8 @@ subroutine DoInit(this, bounds, &
real(r8) , intent(in) :: watsat_col(bounds%begc:, 1:) ! volumetric soil water at saturation (porosity)
real(r8) , intent(in) :: t_soisno_col(bounds%begc:, -nlevsno+1:) ! col soil temperature (Kelvin)
logical , intent(in) :: use_aquifer_layer ! whether an aquifer layer is used in this run
character(len=*) , intent(in) :: NLFilename ! Namelist filename
real(r8) , intent(in) :: exice_init_stream_col(bounds%begc:) ! initial ammount of excess ice from stream
real(r8) , intent(in) :: exice_coldstart_depth ! depth below which excess ice will be present
real(r8) , intent(in) :: exice_init_conc_col(bounds%begc:) ! initial coldstart excess ice concentration (from the stream file)
!
! !LOCAL VARIABLES:
integer :: begc, endc
Expand All @@ -325,7 +327,7 @@ subroutine DoInit(this, bounds, &
SHR_ASSERT_ALL_FL((ubound(snow_depth_col) == [endc]), sourcefile, __LINE__)
SHR_ASSERT_ALL_FL((ubound(watsat_col, 1) == endc), sourcefile, __LINE__)
SHR_ASSERT_ALL_FL((ubound(t_soisno_col, 1) == endc), sourcefile, __LINE__)
SHR_ASSERT_ALL_FL((ubound(exice_init_stream_col, 1) == endc), sourcefile, __LINE__)
SHR_ASSERT_ALL_FL((ubound(exice_init_conc_col, 1) == endc), sourcefile, __LINE__)

call this%SetupTracerInfo()

Expand All @@ -345,8 +347,8 @@ subroutine DoInit(this, bounds, &
watsat_col = watsat_col(begc:endc, 1:), &
t_soisno_col = t_soisno_col(begc:endc, -nlevsno+1:), &
use_aquifer_layer = use_aquifer_layer, &
NLFilename = NLFilename, &
exice_init_stream_col = exice_init_stream_col)
exice_coldstart_depth = exice_coldstart_depth, &
exice_init_conc_col = exice_init_conc_col)

call this%waterdiagnosticbulk_inst%InitBulk(bounds, &
bulk_info, &
Expand Down Expand Up @@ -387,8 +389,8 @@ subroutine DoInit(this, bounds, &
watsat_col = watsat_col(begc:endc, 1:), &
t_soisno_col = t_soisno_col(begc:endc, -nlevsno+1:), &
use_aquifer_layer = use_aquifer_layer, &
NLFilename = NLFilename, &
exice_init_stream_col = exice_init_stream_col)
exice_coldstart_depth = exice_coldstart_depth, &
exice_init_conc_col = exice_init_conc_col)

call this%bulk_and_tracers(i)%waterdiagnostic_inst%Init(bounds, &
this%bulk_and_tracers(i)%info, &
Expand Down
15 changes: 8 additions & 7 deletions src/main/clm_instMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -222,7 +222,7 @@ subroutine clm_instInit(bounds)
type(file_desc_t) :: params_ncid ! pio netCDF file id for parameter file
real(r8), allocatable :: h2osno_col(:)
real(r8), allocatable :: snow_depth_col(:)
real(r8), allocatable :: exice_init_stream_col(:) ! initial concentration of excess ice in the soil (-)
real(r8), allocatable :: exice_init_conc_col(:) ! initial coldstart excess ice concentration (from the stream file or 0.0) (-)
type(excessicestream_type) :: exice_stream

integer :: dummy_to_make_pgi_happy
Expand Down Expand Up @@ -302,12 +302,12 @@ subroutine clm_instInit(bounds)
! Initialization of public data types

! If excess ice is read from the stream, it has to be read before we coldstart the temperature
allocate(exice_init_stream_col(bounds%begc:bounds%endc))
exice_init_stream_col(bounds%begc:bounds%endc) = 0.0_r8
allocate(exice_init_conc_col(bounds%begc:bounds%endc))
exice_init_conc_col(bounds%begc:bounds%endc) = 0.0_r8
if (use_excess_ice) then
call exice_stream%Init(bounds, NLFilename)
if (UseExcessIceStreams()) then
call exice_stream%CalcExcessIce(bounds, exice_init_stream_col(bounds%begc:bounds%endc))
call exice_stream%CalcExcessIce(bounds, exice_init_conc_col(bounds%begc:bounds%endc))
endif
endif

Expand All @@ -317,7 +317,7 @@ subroutine clm_instInit(bounds)
em_improad_lun=urbanparams_inst%em_improad(begl:endl), &
em_perroad_lun=urbanparams_inst%em_perroad(begl:endl), &
is_simple_buildtemp=IsSimpleBuildTemp(), is_prog_buildtemp=IsProgBuildTemp(), &
exice_init_stream_col=exice_init_stream_col(bounds%begc:bounds%endc) , NLFileName=NLFilename)
exice_init_conc_col=exice_init_conc_col(bounds%begc:bounds%endc) , NLFileName=NLFilename)

call active_layer_inst%Init(bounds)

Expand All @@ -332,7 +332,8 @@ subroutine clm_instInit(bounds)
watsat_col = soilstate_inst%watsat_col(begc:endc, 1:), &
t_soisno_col = temperature_inst%t_soisno_col(begc:endc, -nlevsno+1:), &
use_aquifer_layer = use_aquifer_layer(), &
exice_init_stream_col = exice_init_stream_col(begc:endc))
exice_coldstart_depth = temperature_inst%excess_ice_coldstart_depth, &
exice_init_conc_col = exice_init_conc_col(begc:endc))

call glacier_smb_inst%Init(bounds)

Expand Down Expand Up @@ -470,7 +471,7 @@ subroutine clm_instInit(bounds)

deallocate (h2osno_col)
deallocate (snow_depth_col)
deallocate (exice_init_stream_col)
deallocate (exice_init_conc_col)

! ------------------------------------------------------------------------
! Initialize accumulated fields
Expand Down
Loading

0 comments on commit 9ba2b5f

Please sign in to comment.