SCALE-RM
Functions/Subroutines
mod_land_phy_driver Module Reference

module LAND / Physics More...

Functions/Subroutines

subroutine, public land_phy_driver_setup
 Setup. More...
 
subroutine, public land_phy_driver_resume
 Resume. More...
 
subroutine, public land_phy_driver (update_flag)
 Driver. More...
 

Detailed Description

module LAND / Physics

Description
land physics module
Author
Team SCALE
NAMELIST
  • No namelist group
History Output
namedescriptionunitvariable
LAND_ALB_LW_t tendency of LAND_ALB_LW 1 LAND_SFC_albedo_t
LAND_ALB_SW_t tendency of LAND_ALB_SW 1 LAND_SFC_albedo_t
LAND_SFC_TEMP_t tendency of LAND_SFC_TEMP K LAND_SFC_TEMP_t
LAND_TEMP_t tendency of LAND_TEMP K LAND_TEMP_t
LAND_WATER_t tendency of LAND_WATER m3/m3 LAND_WATER_t
LP_HeatCapacity 'LAND PROPERTY HeatCapacity' LAND_PROPERTY
LP_ThermalCond 'LAND PROPERTY ThermalCond' LAND_PROPERTY
LP_WaterCritical 'LAND PROPERTY WaterCritical' LAND_PROPERTY
LP_WaterDiff 'LAND PROPERTY WaterDiff' LAND_PROPERTY
LP_WaterLimit 'LAND PROPERTY WaterLimit' LAND_PROPERTY
LP_Z0E 'LAND PROPERTY Z0E' LAND_PROPERTY
LP_Z0H 'LAND PROPERTY Z0H' LAND_PROPERTY
LP_Z0M 'LAND PROPERTY Z0M' LAND_PROPERTY

Function/Subroutine Documentation

◆ land_phy_driver_setup()

subroutine, public mod_land_phy_driver::land_phy_driver_setup ( )

Setup.

Definition at line 53 of file mod_land_phy_driver.f90.

References scale_stdio::io_fid_log, scale_stdio::io_l, scale_land_phy::land_phy_setup(), scale_land_sfc::land_sfc_setup(), mod_land_admin::land_sw, and mod_land_admin::land_type.

Referenced by mod_land_driver::land_driver_setup().

53  use scale_land_phy, only: &
55  use scale_land_sfc, only: &
57  use mod_land_admin, only: &
58  land_type, &
59  land_sw
60  implicit none
61  !---------------------------------------------------------------------------
62 
63  if( io_l ) write(io_fid_log,*)
64  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[LAND PHY] / Origin[SCALE-RM]'
65 
66  if ( land_sw ) then
67 
68  ! setup library component
71 
72  else
73  if( io_l ) write(io_fid_log,*) '*** this component is never called.'
74  endif
75 
76  return
module Land admin
character(len=h_short), public land_type
subroutine, public land_phy_setup(LAND_TYPE)
Setup.
module LAND / Physics
module LAND / Surface fluxes
subroutine, public land_sfc_setup(LAND_TYPE)
logical, public land_sw
Here is the call graph for this function:
Here is the caller graph for this function:

◆ land_phy_driver_resume()

subroutine, public mod_land_phy_driver::land_phy_driver_resume ( )

Resume.

Definition at line 82 of file mod_land_phy_driver.f90.

References land_phy_driver(), mod_land_admin::land_sw, scale_prof::prof_rapend(), scale_prof::prof_rapstart(), and mod_admin_restart::restart_run.

Referenced by mod_land_driver::land_driver_resume().

82  use mod_admin_restart, only: &
84  use mod_land_admin, only: &
85  land_sw
86  implicit none
87 
88  if ( land_sw ) then
89 
90  if ( .NOT. restart_run ) then ! tentative
91  ! run once (only for the diagnostic value)
92  call prof_rapstart('LND_Physics', 1)
93  call land_phy_driver( update_flag = .true. )
94  call prof_rapend ('LND_Physics', 1)
95  end if
96  end if
97 
98  return
module Land admin
subroutine, public land_phy_driver(update_flag)
Driver.
module administrator for restart
logical, public land_sw
logical, public restart_run
Is this run restart?
Here is the call graph for this function:
Here is the caller graph for this function:

◆ land_phy_driver()

subroutine, public mod_land_phy_driver::land_phy_driver ( logical, intent(in)  update_flag)

Driver.

Definition at line 103 of file mod_land_phy_driver.f90.

References mod_land_vars::atmos_dens, mod_land_vars::atmos_pbl, mod_land_vars::atmos_pres, mod_land_vars::atmos_qv, mod_land_vars::atmos_sfc_pres, mod_land_vars::atmos_sflx_lw, mod_land_vars::atmos_sflx_prec, mod_land_vars::atmos_sflx_sw, mod_land_vars::atmos_temp, mod_land_vars::atmos_u, mod_land_vars::atmos_v, mod_land_vars::atmos_w, scale_land_grid::grid_lcdz, mod_land_vars::i_heatcapacity, mod_land_vars::i_thermalcond, mod_land_vars::i_watercritical, mod_land_vars::i_waterdiff, mod_land_vars::i_waterlimit, mod_land_vars::i_z0e, mod_land_vars::i_z0h, mod_land_vars::i_z0m, scale_grid_index::ie, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, scale_land_phy::land_phy, mod_land_vars::land_property, mod_land_vars::land_q2, scale_land_sfc::land_sfc, mod_land_vars::land_sfc_albedo, mod_land_vars::land_sfc_albedo_t, mod_land_vars::land_sfc_temp, mod_land_vars::land_sfc_temp_t, mod_land_vars::land_sflx_evap, mod_land_vars::land_sflx_gh, mod_land_vars::land_sflx_lh, mod_land_vars::land_sflx_mu, mod_land_vars::land_sflx_mv, mod_land_vars::land_sflx_mw, mod_land_vars::land_sflx_sh, mod_land_vars::land_t2, mod_land_vars::land_temp, mod_land_vars::land_temp_t, mod_land_vars::land_u10, mod_land_vars::land_v10, mod_land_vars::land_water, mod_land_vars::land_water_t, scale_land_grid_index::lke, scale_land_grid_index::lks, scale_grid_real::real_z1, scale_rm_statistics::statistics_checktotal, and scale_time::time_dtsec_land.

Referenced by mod_land_driver::land_driver(), and land_phy_driver_resume().

103  use scale_atmos_hydrometeor, only: &
104  hydrometeor_lhv => atmos_hydrometeor_lhv
105  use scale_time, only: &
106  dt => time_dtsec_land
107  use scale_rm_statistics, only: &
109  stat_total
110  use scale_history, only: &
111  hist_in
112  use scale_grid_real, only: &
113  real_z1
114  use scale_land_grid, only: &
115  grid_lcdz
116  use scale_land_phy, only: &
117  land_phy
118  use scale_land_sfc, only: &
119  land_sfc
120  use mod_land_vars, only: &
121  land_property, &
122  i_waterlimit, &
123  i_watercritical, &
124  i_thermalcond, &
125  i_heatcapacity, &
126  i_waterdiff, &
127  i_z0m, &
128  i_z0h, &
129  i_z0e, &
130  land_temp, &
131  land_water, &
132  land_sfc_temp, &
133  land_sfc_albedo, &
134  land_temp_t, &
135  land_water_t, &
136  land_sfc_temp_t, &
138  land_sflx_mw, &
139  land_sflx_mu, &
140  land_sflx_mv, &
141  land_sflx_sh, &
142  land_sflx_lh, &
143  land_sflx_gh, &
144  land_sflx_evap, &
145  land_u10, &
146  land_v10, &
147  land_t2, &
148  land_q2, &
149  atmos_temp, &
150  atmos_pres, &
151  atmos_w, &
152  atmos_u, &
153  atmos_v, &
154  atmos_dens, &
155  atmos_qv, &
156  atmos_pbl, &
157  atmos_sfc_pres, &
158  atmos_sflx_lw, &
159  atmos_sflx_sw, &
161  implicit none
162 
163  ! parameters
164  real(RP), parameter :: BETA_MAX = 1.0_rp
165 
166  ! arguments
167  logical, intent(in) :: update_flag
168 
169  ! works
170  real(RP) :: LAND_QVEF(IA,JA)
171  real(RP) :: LAND_DZ1 (IA,JA)
172 
173  real(RP) :: LHV (IA,JA) ! latent heat of vaporization [J/kg]
174  real(RP) :: total ! dummy
175 
176  character(len=2) :: sk
177 
178  integer :: k, i, j
179  !---------------------------------------------------------------------------
180 
181  if ( update_flag ) then
182 
183 !OCL XFILL
184  do j = js, je
185  do i = is, ie
186  land_qvef(i,j) = min( land_water(lks,i,j) / land_property(i,j,i_watercritical), beta_max )
187  land_dz1(i,j) = grid_lcdz(lks)
188  end do
189  end do
190 
191  call land_sfc( land_sfc_temp_t(:,:), & ! [OUT]
192  land_sflx_mw(:,:), & ! [OUT]
193  land_sflx_mu(:,:), & ! [OUT]
194  land_sflx_mv(:,:), & ! [OUT]
195  land_sflx_sh(:,:), & ! [OUT]
196  land_sflx_lh(:,:), & ! [OUT]
197  land_sflx_gh(:,:), & ! [OUT]
198  land_u10(:,:), & ! [OUT]
199  land_v10(:,:), & ! [OUT]
200  land_t2(:,:), & ! [OUT]
201  land_q2(:,:), & ! [OUT]
202  atmos_temp(:,:), & ! [IN]
203  atmos_pres(:,:), & ! [IN]
204  atmos_w(:,:), & ! [IN]
205  atmos_u(:,:), & ! [IN]
206  atmos_v(:,:), & ! [IN]
207  atmos_dens(:,:), & ! [IN]
208  atmos_qv(:,:), & ! [IN]
209  real_z1(:,:), & ! [IN]
210  atmos_pbl(:,:), & ! [IN]
211  atmos_sfc_pres(:,:), & ! [IN]
212  atmos_sflx_lw(:,:), & ! [IN]
213  atmos_sflx_sw(:,:), & ! [IN]
214  land_temp(lks,:,:), & ! [IN]
215  land_sfc_temp(:,:), & ! [IN]
216  land_qvef(:,:), & ! [IN]
217  land_sfc_albedo(:,:,i_lw), & ! [IN]
218  land_sfc_albedo(:,:,i_sw), & ! [IN]
219  land_dz1(:,:), & ! [IN]
220  land_property(:,:,i_thermalcond), & ! [IN]
221  land_property(:,:,i_z0m), & ! [IN]
222  land_property(:,:,i_z0h), & ! [IN]
223  land_property(:,:,i_z0e), & ! [IN]
224  dt ) ! [IN]
225 
226  call hydrometeor_lhv( lhv(:,:), atmos_temp(:,:) )
227 
228 !OCL XFILL
229  do j = js, je
230  do i = is, ie
231  land_sflx_evap(i,j) = land_sflx_lh(i,j) / lhv(i,j)
232  end do
233  end do
234 
235  call land_phy( land_temp_t(:,:,:), & ! [OUT]
236  land_water_t(:,:,:), & ! [OUT]
237  land_temp(:,:,:), & ! [IN]
238  land_water(:,:,:), & ! [IN]
239  land_property(:,:,i_waterlimit), & ! [IN]
240  land_property(:,:,i_thermalcond), & ! [IN]
241  land_property(:,:,i_heatcapacity), & ! [IN]
242  land_property(:,:,i_waterdiff), & ! [IN]
243  land_sflx_gh(:,:), & ! [IN]
244  atmos_sflx_prec(:,:), & ! [IN]
245  land_sflx_evap(:,:), & ! [IN]
246  grid_lcdz(:), & ! [IN]
247  dt ) ! [IN]
248 
249  ! no albedo update (tentative)
250 !OCL XFILL
251  land_sfc_albedo_t(:,:,:) = 0.0_rp
252 
253  call hist_in( land_temp_t(:,:,:), 'LAND_TEMP_t', 'tendency of LAND_TEMP', 'K', zdim='land' )
254  call hist_in( land_water_t(:,:,:), 'LAND_WATER_t', 'tendency of LAND_WATER', 'm3/m3', zdim='land' )
255 
256  call hist_in( land_sfc_temp_t(:,:), 'LAND_SFC_TEMP_t', 'tendency of LAND_SFC_TEMP', 'K' )
257  call hist_in( land_sfc_albedo_t(:,:,i_lw), 'LAND_ALB_LW_t', 'tendency of LAND_ALB_LW', '1' )
258  call hist_in( land_sfc_albedo_t(:,:,i_sw), 'LAND_ALB_SW_t', 'tendency of LAND_ALB_SW', '1' )
259 
260  call hist_in( land_property(:,:,i_waterlimit), 'LP_WaterLimit', 'LAND PROPERTY, WaterLimit', 'm3/m3' )
261  call hist_in( land_property(:,:,i_watercritical), 'LP_WaterCritical', 'LAND PROPERTY, WaterCritical', 'm3/m3' )
262  call hist_in( land_property(:,:,i_thermalcond), 'LP_ThermalCond', 'LAND PROPERTY, ThermalCond', 'W/K/m' )
263  call hist_in( land_property(:,:,i_heatcapacity), 'LP_HeatCapacity', 'LAND PROPERTY, HeatCapacity', 'J/K/m3' )
264  call hist_in( land_property(:,:,i_waterdiff), 'LP_WaterDiff', 'LAND PROPERTY, WaterDiff', 'm2/s' )
265  call hist_in( land_property(:,:,i_z0m), 'LP_Z0M', 'LAND PROPERTY, Z0M', 'm' )
266  call hist_in( land_property(:,:,i_z0h), 'LP_Z0H', 'LAND PROPERTY, Z0H', 'm' )
267  call hist_in( land_property(:,:,i_z0e), 'LP_Z0E', 'LAND PROPERTY, Z0E', 'm' )
268 
269  endif
270 
271  if ( statistics_checktotal ) then
272  do k = lks, lke
273  write(sk,'(I2.2)') k
274 
275  call stat_total( total, land_temp_t(k,:,:), 'LAND_TEMP_t'//sk )
276  call stat_total( total, land_water_t(k,:,:), 'LAND_WATER_t'//sk )
277  enddo
278 
279  call stat_total( total, land_sfc_temp_t(:,:), 'LAND_SFC_TEMP_t' )
280  call stat_total( total, land_sfc_albedo_t(:,:,i_lw), 'LAND_ALB_LW_t' )
281  call stat_total( total, land_sfc_albedo_t(:,:,i_sw), 'LAND_ALB_SW_t' )
282  endif
283 
284  return
logical, public statistics_checktotal
calc&report variable totals to logfile?
real(rp), dimension(:,:), allocatable, public land_v10
land surface velocity v at 10m [m/s]
real(rp), dimension(:,:), allocatable, public land_sflx_mw
land surface w-momentum flux [kg/m2/s]
integer, parameter, public i_heatcapacity
integer, parameter, public i_waterlimit
real(rp), dimension(:,:), allocatable, public atmos_qv
real(rp), dimension(:,:), allocatable, public land_sflx_sh
land surface sensible heat flux [J/m2/s]
real(rp), dimension(:,:), allocatable, public atmos_pbl
real(rp), dimension(:,:), allocatable, public atmos_sflx_prec
real(rp), dimension(:,:), allocatable, public atmos_u
integer, parameter, public i_watercritical
module GRID (cartesian) for land
real(rp), dimension(:,:,:), allocatable, public land_sfc_albedo_t
tendency of LAND_SFC_albedo
real(rp), dimension(:,:), allocatable, public land_sflx_lh
land surface latent heat flux [J/m2/s]
real(rp), dimension(:,:), allocatable, public atmos_w
real(dp), public time_dtsec_land
time interval of land step [sec]
Definition: scale_time.F90:48
integer, parameter, public i_z0h
real(rp), dimension(:,:), allocatable, public land_sflx_evap
land surface water vapor flux [kg/m2/s]
integer, parameter, public i_z0e
integer, parameter, public i_lw
module Statistics
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
procedure(lnd), pointer, public land_phy
real(rp), dimension(:,:), allocatable, public atmos_pres
real(rp), dimension(:,:), allocatable, public land_sfc_temp
land surface skin temperature [K]
integer, parameter, public i_sw
real(rp), dimension(:,:), allocatable, public atmos_temp
real(rp), dimension(:,:), allocatable, public land_sflx_mu
land surface u-momentum flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_q2
land surface water vapor at 2m [kg/kg]
real(rp), dimension(:,:), allocatable, public land_t2
land surface temperature at 2m [K]
real(rp), dimension(:,:), allocatable, public real_z1
Height of the lowermost grid from surface (cell center) [m].
module GRID (real space)
real(rp), dimension(:,:,:), allocatable, public land_temp
temperature of each soil layer [K]
module LAND / Physics
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:), allocatable, public land_u10
land surface velocity u at 10m [m/s]
module LAND / Surface fluxes
real(rp), dimension(:,:,:), allocatable, public land_water_t
tendency of LAND_WATER
real(rp), dimension(:,:,:), allocatable, public land_sfc_albedo
land surface albedo (0-1)
module LAND Variables
real(rp), dimension(:,:), allocatable, public land_sfc_temp_t
tendency of LAND_SFC_TEMP
real(rp), dimension(:,:), allocatable, public atmos_dens
real(rp), dimension(:,:), allocatable, public land_sflx_gh
land surface heat flux [J/m2/s]
real(rp), dimension(:,:), allocatable, public atmos_v
real(rp), dimension(:,:,:), allocatable, public land_water
moisture of each soil layer [m3/m3]
procedure(lndsfc), pointer, public land_sfc
real(rp), dimension(:,:), allocatable, public land_sflx_mv
land surface v-momentum flux [kg/m2/s]
real(rp), dimension(:,:,:), allocatable, public land_temp_t
tendency of LAND_TEMP
real(rp), dimension(:), allocatable, public grid_lcdz
z-length of control volume [m]
integer, parameter, public i_z0m
module HISTORY
real(rp), dimension(:,:), allocatable, public atmos_sflx_sw
integer, parameter, public i_thermalcond
integer, parameter, public i_waterdiff
real(rp), dimension(:,:,:), allocatable, public land_property
land surface property
real(rp), dimension(:,:), allocatable, public atmos_sflx_lw
Here is the caller graph for this function: