Skip to content

Commit

Permalink
Fix RUC LSM initialization
Browse files Browse the repository at this point in the history
  • Loading branch information
climbfuji committed Oct 14, 2020
1 parent 7d6d8ce commit 05b9aba
Show file tree
Hide file tree
Showing 2 changed files with 68 additions and 76 deletions.
123 changes: 53 additions & 70 deletions physics/sfc_drv_ruc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ subroutine lsm_ruc_init (me, master, isot, ivegsrc, nlunit, &
lsm_ruc, lsm, slmsk, stype, vtype, & ! in
tsfc_lnd, tsfc_wat, & ! in
tg3, smc, slc, stc, & ! in
sh2o, smfrkeep, tslb, smois, wetness, & ! out
zs, sh2o, smfrkeep, tslb, smois, wetness, & ! out
tsice, errmsg, errflg)

implicit none
Expand All @@ -47,27 +47,29 @@ subroutine lsm_ruc_init (me, master, isot, ivegsrc, nlunit, &
integer, intent(in) :: lsm_ruc, lsm


real (kind=kind_phys), dimension(im), intent(in ) :: slmsk
real (kind=kind_phys), dimension(im), intent(in ) :: stype
real (kind=kind_phys), dimension(im), intent(in ) :: vtype
real (kind=kind_phys), dimension(im), intent(in ) :: tsfc_lnd
real (kind=kind_phys), dimension(im), intent(in ) :: tsfc_wat
real (kind=kind_phys), dimension(im), intent(in) :: tg3
real (kind=kind_phys), dimension(im), intent(in) :: slmsk
real (kind=kind_phys), dimension(im), intent(in) :: stype
real (kind=kind_phys), dimension(im), intent(in) :: vtype
real (kind=kind_phys), dimension(im), intent(in) :: tsfc_lnd
real (kind=kind_phys), dimension(im), intent(in) :: tsfc_wat
real (kind=kind_phys), dimension(im), intent(in) :: tg3

real (kind=kind_phys), dimension(im,lsoil), intent(in) :: smc,slc,stc

! --- in/out:
real (kind=kind_phys), dimension(im), intent(inout) :: wetness

! --- out
real (kind=kind_phys), dimension(im,lsoil_ruc), intent(out) :: sh2o, smfrkeep
real (kind=kind_phys), dimension(im,lsoil_ruc), intent(out) :: tslb, smois
real (kind=kind_phys), dimension(:), intent(out) :: zs
real (kind=kind_phys), dimension(im,lsoil_ruc), intent(inout) :: sh2o, smfrkeep
real (kind=kind_phys), dimension(im,lsoil_ruc), intent(inout) :: tslb, smois
real (kind=kind_phys), dimension(im,kice), intent(out) :: tsice

character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg

! --- local
real (kind=kind_phys), dimension(lsoil_ruc) :: dzs
integer :: ipr, i, k
logical :: debug_print
integer, dimension(im) :: soiltyp, vegtype
Expand Down Expand Up @@ -125,14 +127,16 @@ subroutine lsm_ruc_init (me, master, isot, ivegsrc, nlunit, &
endif
enddo

call init_soil_depth_3 ( zs , dzs , lsoil_ruc )

!if( .not. flag_restart) then
call rucinit (flag_restart, im, lsoil_ruc, lsoil, nlev, & ! in
me, master, lsm_ruc, lsm, slmsk, & ! in
soiltyp, vegtype, & ! in
tsfc_lnd, tsfc_wat, tg3, & ! in
smc, slc, stc, & ! in
sh2o, smfrkeep, tslb, smois, & ! out
wetness, errmsg, errflg)
me, master, lsm_ruc, lsm, slmsk, & ! in
soiltyp, vegtype, & ! in
tsfc_lnd, tsfc_wat, tg3, & ! in
zs, dzs, smc, slc, stc, & ! in
sh2o, smfrkeep, tslb, smois, & ! out
wetness, errmsg, errflg)

do i = 1, im ! i - horizontal loop
do k = 1, min(kice,lsoil_ruc)
Expand All @@ -146,10 +150,10 @@ subroutine lsm_ruc_init (me, master, isot, ivegsrc, nlunit, &
!-- end of initialization

if ( debug_print) then
write (0,*) 'ruc soil tslb',tslb(:,1)
write (0,*) 'ruc soil tsice',tsice(:,1)
write (0,*) 'ruc soil smois',smois(:,1)
write (0,*) 'ruc wetness',wetness(:)
write (0,*) 'ruc soil tslb',tslb(ipr,:)
write (0,*) 'ruc soil tsice',tsice(ipr,:)
write (0,*) 'ruc soil smois',smois(ipr,:)
write (0,*) 'ruc wetness',wetness(ipr)
endif

end subroutine lsm_ruc_init
Expand Down Expand Up @@ -303,8 +307,7 @@ subroutine lsm_ruc_run & ! inputs

! --- in/out:
integer, dimension(im), intent(inout) :: soiltyp, vegtype
real (kind=kind_phys), dimension(lsoil_ruc) :: dzs
real (kind=kind_phys), dimension(lsoil_ruc), intent(inout ) :: zs
real (kind=kind_phys), dimension(lsoil_ruc), intent(in) :: zs
real (kind=kind_phys), dimension(im), intent(inout) :: weasd, &
& snwdph, tskin, tskin_wat, &
& srflag, canopy, trans, tsurf, zorl, tsnow, &
Expand Down Expand Up @@ -415,12 +418,6 @@ subroutine lsm_ruc_run & ! inputs
write (0,*)'flag_init =',flag_init
write (0,*)'flag_restart =',flag_restart
endif

if(flag_init .and. iter==1) then
! Initialize the RUC soil levels, needed for cold starts and warm starts
CALL init_soil_depth_3 ( zs , dzs , lsoil_ruc )
if (.not. restart) xlai = 0.
endif ! flag_init=.true.,iter=1

ims = 1
its = 1
Expand Down Expand Up @@ -705,7 +702,11 @@ subroutine lsm_ruc_run & ! inputs
albbck(i,j) = max(0.01, 0.5 * (alvwf(i) + alnwf(i)))
alb(i,j) = sfalb(i)

if(rdlai2d) xlai(i,j) = laixy(i)
if(rdlai2d) then
xlai(i,j) = laixy(i)
else
xlai(i,j) = 0.
endif

tbot(i,j) = tg3(i)

Expand Down Expand Up @@ -1082,30 +1083,14 @@ subroutine lsm_ruc_run & ! inputs
deallocate(landusef)
!
!! Update standard (Noah LSM) soil variables for physics
!! that require these variables (e.g. sfc_sice), independent
!! of whether it is a land point or not
!do i = 1, im
! if (land(i)) then
! do k = 1, lsoil
! smc(i,k) = smois(i,k)
! slc(i,k) = sh2o(i,k)
! stc(i,k) = tslb(i,k)
! enddo
! endif
!enddo
!
!write(0,*) "DH DEBUG: i, k, land(i), smc(i,k), slc(i,k), stc(i,k):"
!do i = 1, im
! do k = 1, lsoil
! write(0,'(2i5,1x,l,1x,3e20.10)'), i, k, land(i), smc(i,k), slc(i,k), stc(i,k)
! smc(i,k) = smois(i,k)
! slc(i,k) = sh2o(i,k)
! stc(i,k) = tslb(i,k)
! enddo
!enddo

!call sleep(20)
!stop
!! that require these variables and for debugging purposes
do i = 1, im
do k = 1, lsoil
smc(i,k) = smois(i,k)
slc(i,k) = sh2o(i,k)
stc(i,k) = tslb(i,k)
enddo
enddo

return
!...................................
Expand All @@ -1118,24 +1103,26 @@ subroutine rucinit (restart, im, lsoil_ruc, lsoil, nlev, & ! in
me, master, lsm_ruc, lsm, slmsk, & ! in
soiltyp, vegtype, & ! in
tskin_lnd, tskin_wat, tg3, & ! !in
smc, slc, stc, & ! in
zs, dzs, smc, slc, stc, & ! in
sh2o, smfrkeep, tslb, smois, & ! out
wetness, errmsg, errflg)

implicit none

logical, intent(in ) :: restart
integer, intent(in ) :: lsm
integer, intent(in ) :: lsm_ruc
integer, intent(in ) :: im, nlev
integer, intent(in ) :: lsoil_ruc
integer, intent(in ) :: lsoil
real (kind=kind_phys), dimension(im), intent(in ) :: slmsk
real (kind=kind_phys), dimension(im), intent(in ) :: tskin_lnd, tskin_wat
real (kind=kind_phys), dimension(im), intent(in ) :: tg3
real (kind=kind_phys), dimension(im,lsoil), intent(in ) :: smc ! Noah
real (kind=kind_phys), dimension(im,lsoil), intent(in ) :: stc ! Noah
real (kind=kind_phys), dimension(im,lsoil), intent(in ) :: slc ! Noah
logical, intent(in ) :: restart
integer, intent(in ) :: lsm
integer, intent(in ) :: lsm_ruc
integer, intent(in ) :: im, nlev
integer, intent(in ) :: lsoil_ruc
integer, intent(in ) :: lsoil
real (kind=kind_phys), dimension(im), intent(in ) :: slmsk
real (kind=kind_phys), dimension(im), intent(in ) :: tskin_lnd, tskin_wat
real (kind=kind_phys), dimension(im), intent(in ) :: tg3
real (kind=kind_phys), dimension(1:lsoil_ruc), intent(in ) :: zs
real (kind=kind_phys), dimension(1:lsoil_ruc), intent(in ) :: dzs
real (kind=kind_phys), dimension(im,lsoil), intent(in ) :: smc ! Noah
real (kind=kind_phys), dimension(im,lsoil), intent(in ) :: stc ! Noah
real (kind=kind_phys), dimension(im,lsoil), intent(in ) :: slc ! Noah

integer, dimension(im), intent(inout) :: soiltyp
integer, dimension(im), intent(inout) :: vegtype
Expand All @@ -1157,7 +1144,6 @@ subroutine rucinit (restart, im, lsoil_ruc, lsoil, nlev, & ! in

integer :: flag_soil_layers, flag_soil_levels, flag_sst
real (kind=kind_phys), dimension(1:lsoil_ruc) :: factorsm
real (kind=kind_phys), dimension(1:lsoil_ruc) :: zs
real (kind=kind_phys), dimension(im) :: smcref2
real (kind=kind_phys), dimension(im) :: smcwlt2

Expand Down Expand Up @@ -1185,7 +1171,6 @@ subroutine rucinit (restart, im, lsoil_ruc, lsoil, nlev, & ! in
its,ite, jts,jte, kts,kte, &
i, j, k, l, num_soil_layers, ipr

real(kind=kind_phys), dimension(1:lsoil_ruc) :: zs2, dzs
integer, dimension(1:lsoil) :: st_levels_input ! 4 - for Noah lsm
integer, dimension(1:lsoil) :: sm_levels_input ! 4 - for Noah lsm

Expand All @@ -1205,6 +1190,7 @@ subroutine rucinit (restart, im, lsoil_ruc, lsoil, nlev, & ! in
else if (debug_print) then
write (0,*) 'Start of RUC LSM initialization'
write (0,*)'lsoil, lsoil_ruc =',lsoil, lsoil_ruc
write (0,*)'restart = ',restart
endif

ipr = 10
Expand All @@ -1229,9 +1215,6 @@ subroutine rucinit (restart, im, lsoil_ruc, lsoil, nlev, & ! in
kme = nlev
kte = nlev

! Initialize the RUC soil levels, needed for cold starts and warm starts
CALL init_soil_depth_3 ( zs , dzs , lsoil_ruc )

!! Check if RUC soil data (tslb, ...) is provided or not
!if (minval(tslb)==maxval(tslb)) then
! For restart runs, can assume that RUC soul data is provided
Expand Down
21 changes: 15 additions & 6 deletions physics/sfc_drv_ruc.meta
Original file line number Diff line number Diff line change
Expand Up @@ -200,14 +200,23 @@
kind = kind_phys
intent = in
optional = F
[zs]
standard_name = depth_of_soil_levels_for_land_surface_model
long_name = depth of soil levels for land surface model
units = m
dimensions = (soil_vertical_dimension_for_land_surface_model)
type = real
kind = kind_phys
intent = out
optional = F
[sh2o]
standard_name = volume_fraction_of_unfrozen_soil_moisture_for_land_surface_model
long_name = volume fraction of unfrozen soil moisture for lsm
units = frac
dimensions = (horizontal_dimension,soil_vertical_dimension_for_land_surface_model)
type = real
kind = kind_phys
intent = out
intent = inout
optional = F
[smfrkeep]
standard_name = volume_fraction_of_frozen_soil_moisture_for_land_surface_model
Expand All @@ -216,7 +225,7 @@
dimensions = (horizontal_dimension,soil_vertical_dimension_for_land_surface_model)
type = real
kind = kind_phys
intent = out
intent = inout
optional = F
[tslb]
standard_name = soil_temperature_for_land_surface_model
Expand All @@ -225,7 +234,7 @@
dimensions = (horizontal_dimension,soil_vertical_dimension_for_land_surface_model)
type = real
kind = kind_phys
intent = out
intent = inout
optional = F
[smois]
standard_name = volume_fraction_of_soil_moisture_for_land_surface_model
Expand All @@ -234,7 +243,7 @@
dimensions = (horizontal_dimension,soil_vertical_dimension_for_land_surface_model)
type = real
kind = kind_phys
intent = out
intent = inout
optional = F
[wetness]
standard_name = normalized_soil_wetness_for_land_surface_model
Expand All @@ -243,7 +252,7 @@
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
intent = inout
optional = F
[tsice]
standard_name = internal_ice_temperature
Expand Down Expand Up @@ -369,7 +378,7 @@
dimensions = (soil_vertical_dimension_for_land_surface_model)
type = real
kind = kind_phys
intent = inout
intent = in
optional = F
[t1]
standard_name = air_temperature_at_lowest_model_layer
Expand Down

0 comments on commit 05b9aba

Please sign in to comment.