SCALE-RM
Functions/Subroutines
mod_land_driver Module Reference

module LAND driver More...

Functions/Subroutines

subroutine, public land_driver_setup
 Setup. More...
 
subroutine, public land_driver_resume
 Resume. More...
 
subroutine, public land_driver
 Land step. More...
 
subroutine, public land_surface_get
 Get surface boundary from other model. More...
 
subroutine, public land_surface_set (countup)
 Put surface boundary to other model. More...
 

Detailed Description

module LAND driver

Description
Land model driver
Author
Team SCALE
  • 2013-08-31 (T.Yamaura) [new]

Function/Subroutine Documentation

◆ land_driver_setup()

subroutine, public mod_land_driver::land_driver_setup ( )

Setup.

Definition at line 56 of file mod_land_driver.f90.

References scale_stdio::io_fid_log, scale_stdio::io_l, and mod_land_phy_driver::land_phy_driver_setup().

Referenced by mod_rm_driver::scalerm().

56  use mod_land_phy_driver, only: &
58  implicit none
59  !---------------------------------------------------------------------------
60 
61  if( io_l ) write(io_fid_log,*)
62  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[LAND] / Origin[SCALE-RM]'
63 
65 
66  return
subroutine, public land_phy_driver_setup
Setup.
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
module LAND / Physics
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
Here is the call graph for this function:
Here is the caller graph for this function:

◆ land_driver_resume()

subroutine, public mod_land_driver::land_driver_resume ( )

Resume.

Definition at line 72 of file mod_land_driver.f90.

References scale_stdio::io_fid_log, scale_stdio::io_l, mod_land_phy_driver::land_phy_driver_resume(), land_surface_get(), land_surface_set(), mod_land_admin::land_sw, mod_land_vars::land_vars_history(), scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by mod_rm_driver::resume_state().

72  use mod_land_phy_driver, only: &
74  use mod_land_vars, only: &
76  use mod_land_admin, only: &
77  land_sw
78  implicit none
79  !---------------------------------------------------------------------------
80 
81  if( io_l ) write(io_fid_log,*)
82  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[LAND] / Origin[SCALE-RM]'
83 
84  !########## Get Surface Boundary from coupler ##########
85  call land_surface_get
86 
88 
89  !########## Set Surface Boundary to coupler ##########
90  call land_surface_set( countup=.true. )
91 
92  !########## History & Monitor ##########
93  if ( land_sw ) then
94  call prof_rapstart('LND_History', 1)
96  call prof_rapend ('LND_History', 1)
97  endif
98 
99  return
module Land admin
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
module LAND Variables
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:132
subroutine, public land_phy_driver_resume
Resume.
module LAND / Physics
subroutine, public land_vars_history
History output set for land variables.
logical, public land_sw
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:178
Here is the call graph for this function:
Here is the caller graph for this function:

◆ land_driver()

subroutine, public mod_land_driver::land_driver ( )

Land step.

Definition at line 105 of file mod_land_driver.f90.

References scale_grid_index::ie, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, mod_land_phy_driver::land_phy_driver(), 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, land_surface_get(), land_surface_set(), mod_land_admin::land_sw, mod_land_vars::land_temp, mod_land_vars::land_temp_t, mod_land_vars::land_vars_history(), mod_land_vars::land_vars_total(), mod_land_vars::land_water, mod_land_vars::land_water_t, scale_land_grid_index::lke, scale_land_grid_index::lks, scale_prof::prof_rapend(), scale_prof::prof_rapstart(), and scale_time::time_dtsec_land.

Referenced by mod_rm_driver::scalerm().

105  use scale_time, only: &
106  dt => time_dtsec_land
107  use mod_land_admin, only: &
108  land_sw
109  use mod_land_vars, only: &
110  land_temp, &
111  land_water, &
112  land_sfc_temp, &
113  land_sfc_albedo, &
114  land_temp_t, &
115  land_water_t, &
116  land_sfc_temp_t, &
118  land_vars_total, &
120  use mod_land_phy_driver, only: &
122  implicit none
123 
124  integer :: k, i, j
125  !---------------------------------------------------------------------------
126 
127  !########## Get Surface Boundary from coupler ##########
128  call prof_rapstart('LND_SfcExch', 2)
129  call land_surface_get
130  call prof_rapend ('LND_SfcExch', 2)
131 
132  !########## Physics ##########
133  if ( land_sw ) then
134  call prof_rapstart('LND_Physics', 1)
135  call land_phy_driver( update_flag = .true. )
136  call prof_rapend ('LND_Physics', 1)
137  endif
138 
139  !########## Update ##########
140  do j = js, je
141  do i = is, ie
142  do k = lks, lke
143  land_temp(k,i,j) = land_temp(k,i,j) + land_temp_t(k,i,j) * dt
144  land_water(k,i,j) = land_water(k,i,j) + land_water_t(k,i,j) * dt
145  enddo
146  enddo
147  enddo
148  do j = js, je
149  do i = is, ie
150  land_sfc_temp(i,j) = land_sfc_temp(i,j) + land_sfc_temp_t(i,j) * dt
153  enddo
154  enddo
155 
156  !########## Negative Fixer ##########
157  do j = js, je
158  do i = is, ie
159  do k = lks, lke
160  land_water(k,i,j) = max( land_water(k,i,j), 0.0_rp )
161  enddo
162  enddo
163  enddo
164 
165  call land_vars_total
166 
167  !########## Set Surface Boundary to coupler ##########
168  call prof_rapstart('LND_SfcExch', 2)
169  call land_surface_set( countup=.true. )
170  call prof_rapend ('LND_SfcExch', 2)
171 
172  !########## reset tendencies ##########
173 !OCL XFILL
174  do j = js, je
175  do i = is, ie
176  do k = lks, lke
177  land_temp_t(k,i,j) = 0.0_rp
178  land_water_t(k,i,j) = 0.0_rp
179  enddo
180  enddo
181  enddo
182 
183 !OCL XFILL
184  do j = js, je
185  do i = is, ie
186  land_sfc_temp_t(i,j) = 0.0_rp
187  land_sfc_albedo_t(i,j,i_lw) = 0.0_rp
188  land_sfc_albedo_t(i,j,i_sw) = 0.0_rp
189  enddo
190  enddo
191 
192  !########## History & Monitor ##########
193  call prof_rapstart('LND_History', 1)
194  call land_vars_history
195  call prof_rapend ('LND_History', 1)
196 
197  return
module Land admin
integer, public is
start point of inner domain: x, local
integer, public je
end point of inner domain: y, local
subroutine, public land_phy_driver(update_flag)
Driver.
real(rp), dimension(:,:,:), allocatable, public land_sfc_albedo_t
tendency of LAND_SFC_albedo
real(dp), public time_dtsec_land
time interval of land step [sec]
Definition: scale_time.F90:48
integer, parameter, public i_lw
real(rp), dimension(:,:), allocatable, public land_sfc_temp
land surface skin temperature [K]
integer, parameter, public i_sw
real(rp), dimension(:,:,:), allocatable, public land_temp
temperature of each soil layer [K]
integer, public js
start point of inner domain: y, local
module TIME
Definition: scale_time.F90:15
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
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:132
real(rp), dimension(:,:,:), allocatable, public land_water
moisture of each soil layer [m3/m3]
subroutine, public land_vars_total
Budget monitor for land.
integer, public ie
end point of inner domain: x, local
real(rp), dimension(:,:,:), allocatable, public land_temp_t
tendency of LAND_TEMP
module LAND / Physics
subroutine, public land_vars_history
History output set for land variables.
logical, public land_sw
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:178
Here is the call graph for this function:
Here is the caller graph for this function:

◆ land_surface_get()

subroutine, public mod_land_driver::land_surface_get ( )

Get surface boundary from other model.

Definition at line 203 of file mod_land_driver.f90.

References mod_land_vars::atmos_cossza, 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, mod_cpl_vars::cpl_getatm_lnd(), and mod_land_admin::land_sw.

Referenced by land_driver(), and land_driver_resume().

203  use mod_land_admin, only: &
204  land_sw
205  use mod_land_vars, only: &
206  atmos_temp, &
207  atmos_pres, &
208  atmos_w, &
209  atmos_u, &
210  atmos_v, &
211  atmos_dens, &
212  atmos_qv, &
213  atmos_pbl, &
214  atmos_sfc_pres, &
215  atmos_sflx_lw, &
216  atmos_sflx_sw, &
217  atmos_cossza, &
219  use mod_cpl_vars, only: &
221  implicit none
222 
223  real(RP) :: atmos_sflx_rad_dn(ia,ja,2,2)
224  real(RP) :: atmos_sflx_rain (ia,ja)
225  real(RP) :: atmos_sflx_snow (ia,ja)
226  !---------------------------------------------------------------------------
227 
228  if ( land_sw ) then
229  call cpl_getatm_lnd( atmos_temp(:,:), & ! [OUT]
230  atmos_pres(:,:), & ! [OUT]
231  atmos_w(:,:), & ! [OUT]
232  atmos_u(:,:), & ! [OUT]
233  atmos_v(:,:), & ! [OUT]
234  atmos_dens(:,:), & ! [OUT]
235  atmos_qv(:,:), & ! [OUT]
236  atmos_pbl(:,:), & ! [OUT]
237  atmos_sfc_pres(:,:), & ! [OUT]
238  atmos_sflx_rad_dn(:,:,:,:), & ! [OUT]
239  atmos_cossza(:,:), & ! [OUT]
240  atmos_sflx_rain(:,:), & ! [OUT]
241  atmos_sflx_snow(:,:) ) ! [OUT]
242  endif
243 
244  atmos_sflx_sw(:,:) = atmos_sflx_rad_dn(:,:,i_sw,1) + atmos_sflx_rad_dn(:,:,i_sw,2) ! direct+diffuse
245  atmos_sflx_lw(:,:) = atmos_sflx_rad_dn(:,:,i_lw,1) + atmos_sflx_rad_dn(:,:,i_lw,2) ! direct+diffuse
246 
247  atmos_sflx_prec(:,:) = atmos_sflx_rain(:,:) + atmos_sflx_snow(:,:) ! liquid+ice
248 
249  return
module Land admin
real(rp), dimension(:,:), allocatable, public atmos_qv
real(rp), dimension(:,:), allocatable, public atmos_pbl
real(rp), dimension(:,:), allocatable, public atmos_sflx_prec
real(rp), dimension(:,:), allocatable, public atmos_u
real(rp), dimension(:,:), allocatable, public atmos_w
integer, parameter, public i_lw
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
real(rp), dimension(:,:), allocatable, public atmos_pres
integer, parameter, public i_sw
real(rp), dimension(:,:), allocatable, public atmos_temp
integer, public ia
of x whole cells (local, with HALO)
module COUPLER Variables
module LAND Variables
real(rp), dimension(:,:), allocatable, public atmos_dens
real(rp), dimension(:,:), allocatable, public atmos_v
logical, public land_sw
subroutine, public cpl_getatm_lnd(TEMP, PRES, W, U, V, DENS, QV, PBL, SFC_PRES, SFLX_rad_dn, cosSZA, SFLX_rain, SFLX_snow)
real(rp), dimension(:,:), allocatable, public atmos_sflx_sw
real(rp), dimension(:,:), allocatable, public atmos_cossza
real(rp), dimension(:,:), allocatable, public atmos_sflx_lw
integer, public ja
of y whole cells (local, with HALO)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ land_surface_set()

subroutine, public mod_land_driver::land_surface_set ( logical, intent(in)  countup)

Put surface boundary to other model.

Definition at line 255 of file mod_land_driver.f90.

References mod_cpl_vars::cpl_putlnd(), mod_land_vars::i_z0e, mod_land_vars::i_z0h, mod_land_vars::i_z0m, mod_land_vars::land_property, mod_land_vars::land_q2, mod_land_vars::land_sfc_albedo, mod_land_vars::land_sfc_temp, 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_admin::land_sw, mod_land_vars::land_t2, mod_land_vars::land_u10, and mod_land_vars::land_v10.

Referenced by land_driver(), land_driver_resume(), mod_mkinit::mkinit(), and mod_rm_driver::resume_state().

255  use mod_land_admin, only: &
256  land_sw
257  use mod_land_vars, only: &
258  land_property, &
259  i_z0m, &
260  i_z0h, &
261  i_z0e, &
262  land_sfc_temp, &
263  land_sfc_albedo, &
264  land_sflx_mw, &
265  land_sflx_mu, &
266  land_sflx_mv, &
267  land_sflx_sh, &
268  land_sflx_lh, &
269  land_sflx_gh, &
270  land_sflx_evap, &
271  land_u10, &
272  land_v10, &
273  land_t2, &
274  land_q2
275  use mod_cpl_vars, only: &
276  cpl_putlnd
277  implicit none
278 
279  ! arguments
280  logical, intent(in) :: countup
281  !---------------------------------------------------------------------------
282 
283  if ( land_sw ) then
284  call cpl_putlnd( land_sfc_temp(:,:), & ! [IN]
285  land_sfc_albedo(:,:,:), & ! [IN]
286  land_property(:,:,i_z0m), & ! [IN]
287  land_property(:,:,i_z0h), & ! [IN]
288  land_property(:,:,i_z0e), & ! [IN]
289  land_sflx_mw(:,:), & ! [IN]
290  land_sflx_mu(:,:), & ! [IN]
291  land_sflx_mv(:,:), & ! [IN]
292  land_sflx_sh(:,:), & ! [IN]
293  land_sflx_lh(:,:), & ! [IN]
294  land_sflx_gh(:,:), & ! [IN]
295  land_sflx_evap(:,:), & ! [IN]
296  land_u10(:,:), & ! [IN]
297  land_v10(:,:), & ! [IN]
298  land_t2(:,:), & ! [IN]
299  land_q2(:,:), & ! [IN]
300  countup ) ! [IN]
301  endif
302 
303  return
module Land admin
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]
real(rp), dimension(:,:), allocatable, public land_sflx_sh
land surface sensible heat flux [J/m2/s]
real(rp), dimension(:,:), allocatable, public land_sflx_lh
land surface latent heat flux [J/m2/s]
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
subroutine, public cpl_putlnd(SFC_TEMP, SFC_albedo, SFC_Z0M, SFC_Z0H, SFC_Z0E, SFLX_MW, SFLX_MU, SFLX_MV, SFLX_SH, SFLX_LH, SFLX_GH, SFLX_evap, U10, V10, T2, Q2, countup)
real(rp), dimension(:,:), allocatable, public land_sfc_temp
land surface skin temperature [K]
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]
module COUPLER Variables
real(rp), dimension(:,:), allocatable, public land_u10
land surface velocity u at 10m [m/s]
real(rp), dimension(:,:,:), allocatable, public land_sfc_albedo
land surface albedo [0-1]
module LAND Variables
real(rp), dimension(:,:), allocatable, public land_sflx_gh
land surface heat flux [J/m2/s]
real(rp), dimension(:,:), allocatable, public land_sflx_mv
land surface v-momentum flux [kg/m2/s]
integer, parameter, public i_z0m
logical, public land_sw
real(rp), dimension(:,:,:), allocatable, public land_property
land surface property
Here is the call graph for this function:
Here is the caller graph for this function: