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_calc_tendency (force)
 Calculate tendency. More...
 
subroutine, public land_driver_update
 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
NAMELIST
  • No namelist group
History Output
namedescriptionunitvariable
RUNOFF runoff water kg RUNOFF
SNOW_ALB_LW Snow surface albedo (long wave) 1 SNOW_albedo
SNOW_ALB_SW Snow surface albedo (short wave) 1 SNOW_albedo
SNOW_ATMOS_SFLX_GH Snowpack received heat flux J/m2/s SNOW_ATMOS_SFLX_GH
SNOW_ATMOS_SFLX_LH Snow surface latent heat flux J/m2/s SNOW_ATMOS_SFLX_LH
SNOW_ATMOS_SFLX_MU Snow surface u-momentum flux J/m2/s SNOW_ATMOS_SFLX_MU
SNOW_ATMOS_SFLX_MV Snow surface v-momentum flux J/m2/s SNOW_ATMOS_SFLX_MV
SNOW_ATMOS_SFLX_MW Snow surface w-momentum flux J/m2/s SNOW_ATMOS_SFLX_MW
SNOW_ATMOS_SFLX_SH Snow surface sensible heat flux J/m2/s SNOW_ATMOS_SFLX_SH
SNOW_LAND_SFLX_GH land surface ground heat flux under snow J/m2/s SNOW_LAND_SFLX_GH
SNOW_LAND_SFLX_ice land surface ice water flux under snow kg/m2/s SNOW_LAND_SFLX_water
SNOW_LAND_SFLX_water land surface liquid water flux under snow kg/m2/s SNOW_LAND_SFLX_water
SNOW_Q2 Specific humidity at 2m on snow surface kg/kg SNOW_Q2
SNOW_T2 Air temperature at 2m on snow surface K SNOW_T2
SNOW_U10 Wind velocity u at 10 m on snow surface m/s SNOW_U10
SNOW_V10 Wind velocity v at 10 m on snow surface m/s SNOW_V10
SNOW_frac Snow fraction on land subgrid 1 SNOW_frac

Function/Subroutine Documentation

◆ land_driver_setup()

subroutine, public mod_land_driver::land_driver_setup ( )

Setup.

Definition at line 57 of file mod_land_driver.F90.

References scale_cpl_phy_sfc_fixed_temp::cpl_phy_sfc_fixed_temp_setup(), scale_cpl_phy_sfc_skin::cpl_phy_sfc_skin_setup(), mod_land_admin::land_do, scale_land_dyn_bucket::land_dyn_bucket_setup(), mod_land_admin::land_dyn_type, scale_land_phy_snow_ky90::land_phy_snow_ky90_setup(), mod_land_admin::land_sfc_type, scale_prc::prc_abort(), and mod_land_admin::snow_type.

Referenced by mod_rm_driver::rm_driver().

57  use scale_prc, only: &
58  prc_abort
59  use mod_land_admin, only: &
60  land_do, &
61  land_dyn_type, &
62  land_sfc_type, &
63  snow_type
64  use scale_land_dyn_bucket, only: &
66  use scale_land_phy_snow_ky90, only: &
68  use scale_cpl_phy_sfc_skin, only: &
70  use scale_cpl_phy_sfc_fixed_temp, only: &
72  implicit none
73  !---------------------------------------------------------------------------
74 
75  log_newline
76  log_info("LAND_driver_setup",*) 'Setup'
77 
78  snow_flag = .false.
79 
80  if ( land_do ) then
81 
82  select case ( land_dyn_type )
83  case ( 'BUCKET' )
85  case ( 'INIT' )
86  ! do nothing
87  case default
88  log_error("LAND_driver_setup",*) 'LAND_DYN_TYPE is invalid: ', trim(land_dyn_type)
89  call prc_abort
90  end select
91 
92  select case ( land_sfc_type )
93  case ( 'SKIN' )
95  case ( 'FIXED-TEMP' )
97  case default
98  log_error("LAND_driver_setup",*) 'LAND_SFC_TYPE is invalid: ', trim(land_sfc_type)
99  call prc_abort
100  end select
101 
102  select case ( snow_type )
103  case ( 'NONE', 'OFF' )
104  case ( 'KY90' )
105  log_info("LAND_driver_setup",*) 'SNOW model is enabled'
106  log_info("LAND_driver_setup",*) 'SNOW model is on experimental stage.'
107  log_info("LAND_driver_setup",*) 'Use this with your own risk.'
109  snow_flag = .true.
110  case default
111  log_error("LAND_driver_setup",*) 'SNOW_TYPE is invalid: ', trim(snow_type)
112  call prc_abort
113  end select
114 
115  end if
116 
117  return
module Land admin
module coupler / surface fixed temp model
module land / physics / snow / ky90
subroutine, public cpl_phy_sfc_fixed_temp_setup
Setup.
module coupler / physics / surface skin
module land / dynamics / bucket
character(len=h_short), public snow_type
module PROCESS
Definition: scale_prc.F90:11
subroutine, public land_phy_snow_ky90_setup
Setup.
subroutine, public cpl_phy_sfc_skin_setup
Setup.
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
character(len=h_short), public land_dyn_type
character(len=h_short), public land_sfc_type
logical, public land_do
subroutine, public land_dyn_bucket_setup
Setup.
Here is the call graph for this function:
Here is the caller graph for this function:

◆ land_driver_calc_tendency()

subroutine, public mod_land_driver::land_driver_calc_tendency ( logical, intent(in)  force)

Calculate tendency.

snow area

all land area without snow model or no snow area with snow model

Definition at line 123 of file mod_land_driver.F90.

References mod_land_vars::atmos_dens, scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_z1, scale_atmos_hydrometeor::atmos_hydrometeor_dry, mod_land_vars::atmos_pbl, mod_atmos_phy_ch_driver::atmos_phy_ch_driver_land_flux(), mod_land_vars::atmos_pres, mod_land_vars::atmos_qv, mod_land_vars::atmos_sfc_dens, mod_land_vars::atmos_sfc_pres, mod_land_vars::atmos_sflx_rad_dn, mod_land_vars::atmos_sflx_rain, mod_land_vars::atmos_sflx_snow, mod_atmos_admin::atmos_sw_phy_ch, mod_land_vars::atmos_temp, mod_land_vars::atmos_u, mod_land_vars::atmos_v, mod_land_vars::atmos_w, scale_cpl_phy_sfc_fixed_temp::cpl_phy_sfc_fixed_temp(), scale_cpl_phy_sfc_skin::cpl_phy_sfc_skin(), mod_land_vars::i_alblw, mod_land_vars::i_albsw, mod_land_vars::i_heatcapacity, scale_atmos_hydrometeor::i_qv, scale_cpl_sfc_index::i_r_diffuse, scale_cpl_sfc_index::i_r_direct, scale_cpl_sfc_index::i_r_ir, scale_cpl_sfc_index::i_r_nir, scale_cpl_sfc_index::i_r_vis, mod_land_vars::i_stomataresist, 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_land_grid_cartesc::land_grid_cartesc_cz, scale_land_phy_snow_diagnos::land_phy_snow_diags(), scale_land_phy_snow_ky90::land_phy_snow_ky90(), mod_land_vars::land_property, mod_land_vars::land_q2, mod_land_vars::land_sfc_albedo, mod_land_vars::land_sfc_temp, mod_land_admin::land_sfc_type, mod_land_vars::land_sflx_gh, mod_land_vars::land_sflx_ice, 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_qtrc, mod_land_vars::land_sflx_sh, mod_land_vars::land_sflx_water, land_surface_get(), land_surface_set(), 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_landuse::landuse_exists_land, scale_landuse::landuse_fact_land, scale_land_grid_cartesc_index::lia, scale_land_grid_cartesc_index::lie, scale_land_grid_cartesc_index::lis, scale_land_grid_cartesc_index::lja, scale_land_grid_cartesc_index::lje, scale_land_grid_cartesc_index::ljs, scale_land_grid_cartesc_index::lke, scale_land_grid_cartesc_index::lks, scale_prof::prof_rapend(), scale_prof::prof_rapstart(), scale_tracer::qa, mod_land_vars::snow_depth, mod_land_vars::snow_dzero, mod_land_vars::snow_nosnowsec, mod_land_vars::snow_sfc_temp, mod_land_vars::snow_swe, mod_land_admin::snow_type, and scale_time::time_dtsec_land.

Referenced by mod_rm_driver::restart_read(), and mod_rm_driver::rm_driver().

123  use scale_time, only: &
124  dt => time_dtsec_land
125  use scale_file_history, only: &
126  file_history_in
127  use scale_atmos_grid_cartesc_real, only: &
128  real_z1 => atmos_grid_cartesc_real_z1
129  use scale_atmos_hydrometeor, only: &
130  hydrometeor_lhv => atmos_hydrometeor_lhv, &
132  i_qv
133  use scale_land_grid_cartesc, only: &
134  lcz => land_grid_cartesc_cz
135  use scale_land_phy_snow_ky90, only: &
137  use scale_land_phy_snow_diagnos, only: &
139  use scale_cpl_phy_sfc_skin, only: &
141  use scale_cpl_phy_sfc_fixed_temp, only: &
143  use mod_atmos_admin, only: &
145  use mod_atmos_phy_ch_driver, only: &
147  use mod_land_admin, only: &
148  land_sfc_type, &
149  snow_type
150  use mod_land_vars, only: &
151  i_waterlimit, &
152  i_watercritical, &
153  i_stomataresist, &
154  i_thermalcond, &
155  i_heatcapacity, &
156  i_waterdiff, &
157  i_alblw, &
158  i_albsw, &
159  i_z0m, &
160  i_z0h, &
161  i_z0e, &
162  land_property, &
163  land_temp, &
164  land_water, &
165  land_sfc_temp, &
166  land_sfc_albedo, &
167  land_temp_t, &
168  land_water_t, &
169  land_sflx_mw, &
170  land_sflx_mu, &
171  land_sflx_mv, &
172  land_sflx_sh, &
173  land_sflx_lh, &
174  land_sflx_gh, &
175  land_sflx_qtrc, &
176  land_sflx_water, &
177  land_sflx_ice, &
178  land_u10, &
179  land_v10, &
180  land_t2, &
181  land_q2, &
182  snow_sfc_temp, &
183  snow_swe, &
184  snow_depth, &
185  snow_dzero, &
186  snow_nosnowsec, &
187  atmos_temp, &
188  atmos_pres, &
189  atmos_w, &
190  atmos_u, &
191  atmos_v, &
192  atmos_dens, &
193  atmos_qv, &
194  atmos_pbl, &
195  atmos_sfc_dens, &
196  atmos_sfc_pres, &
198  atmos_sflx_rain, &
200  use scale_landuse, only: &
203  implicit none
204 
205  logical, intent(in) :: force
206 
207  ! parameters
208  real(RP), parameter :: beta_max = 1.0_rp
209 
210  ! works
211  real(RP) :: snow_qvef (lia,lja)
212  real(RP) :: land_qvef (lia,lja)
213  real(RP) :: land_tc_dz(lia,lja)
214  real(RP) :: sflx_qv (lia,lja)
215  real(RP) :: sflx_gh (lia,lja)
216  real(RP) :: lhv (lia,lja) ! latent heat of vaporization [J/kg]
217 
218  ! for snow
219  real(RP) :: snow_albedo (lia,lja,2)
220  real(RP) :: snow_atmos_sflx_sh (lia,lja)
221  real(RP) :: snow_atmos_sflx_lh (lia,lja)
222  real(RP) :: snow_atmos_sflx_gh (lia,lja)
223  !real(RP) :: SNOW_ATMOS_SFLX_evap(LIA,LJA)
224  real(RP) :: snow_land_sflx_gh (lia,lja)
225  real(RP) :: snow_land_sflx_water(lia,lja)
226  real(RP) :: snow_land_sflx_ice (lia,lja)
227  real(RP) :: snow_frac (lia,lja)
228 
229  real(RP) :: snow_atmos_sflx_mw (lia,lja)
230  real(RP) :: snow_atmos_sflx_mu (lia,lja)
231  real(RP) :: snow_atmos_sflx_mv (lia,lja)
232  real(RP) :: snow_u10 (lia,lja)
233  real(RP) :: snow_v10 (lia,lja)
234  real(RP) :: snow_t2 (lia,lja)
235  real(RP) :: snow_q2 (lia,lja)
236 
237  ! monitor
238  !real(RP) :: MONIT_WCONT0 (LIA,LJA)
239  !real(RP) :: MONIT_WCONT1 (LIA,LJA)
240  !real(RP) :: MONIT_ENG0 (LIA,LJA)
241  !real(RP) :: MONIT_ENG1 (LIA,LJA)
242  !
243  !real(RP) :: MONIT_SNOW_heat (LIA,LJA)
244  !real(RP) :: MONIT_SNOW_water (LIA,LJA)
245  !real(RP) :: MONIT_LAND_heat (LIA,LJA)
246  !real(RP) :: MONIT_LAND_water (LIA,LJA)
247 
248  integer :: k, i, j, iq, idir
249  !---------------------------------------------------------------------------
250 
251  call prof_rapstart('LND_CalcTend', 1)
252 
253  !########## Get Surface Boundary from coupler ##########
254  call land_surface_get
255 
256  !########## reset tendencies ##########
257 !OCL XFILL
258  !$omp parallel do
259  do j = ljs, lje
260  do i = lis, lie
261  do k = lks, lke
262  land_temp_t(k,i,j) = 0.0_rp
263  land_water_t(k,i,j) = 0.0_rp
264  enddo
265  enddo
266  enddo
267 !OCL XFILL
268  do iq = 1, qa
269  !$omp parallel do
270  do j = ljs, lje
271  do i = lis, lie
272  land_sflx_qtrc(i,j,iq) = 0.0_rp
273  enddo
274  enddo
275  enddo
276 
277  call hydrometeor_lhv( lia, lis, lie, lja, ljs, lje, &
278  atmos_temp(:,:), lhv(:,:) )
279 
280  if ( snow_flag ) then
281  !------------------------------------------------------------------------
283 
284 !OCL XFILL
285  !$omp parallel do
286  do j = ljs, lje
287  do i = lis, lie
288  ! This is for debug---adachi start
289  !if(( int(SNOW_frac(i,j)) == 1 ).and.( abs(SNOW_SFC_TEMP(i,j)-LAND_SFC_TEMP(i,j))/=0 ))then
290  ! LOG_ERROR("LAND_driver_calc_tendency",*) "Error please check SNOW_SFC_TEMP routine"
291  ! call PRC_abort
292  !endif
293  ! This is for debug---adachi end
294  snow_sfc_temp(i,j) = land_sfc_temp(i,j)
295  end do
296  end do
297 
298  select case ( snow_type )
299  case ( 'KY90' )
300  ! accumulation and melt of snow if there is snow
301 
302  !MONIT_WCONT0 = 0.0_RP
303  !call monitor_snow_water( SNOW_Depth (:,:), & ! [IN]
304  ! SNOW_Dzero (:,:), & ! [IN]
305  ! MONIT_WCONT0 (:,:) ) ! [OUT]
306 
307  call land_phy_snow_ky90( lia, lis, lie, lja, ljs, lje, &
308  atmos_sflx_rain(:,:), atmos_sflx_snow(:,:), & ! [IN]
309  atmos_pres(:,:), atmos_temp(:,:), atmos_qv(:,:), & ! [IN]
310  atmos_w(:,:), atmos_u(:,:), atmos_v(:,:), & ! [IN]
311  atmos_sfc_dens(:,:), & ! [IN]
312  atmos_sflx_rad_dn(:,:,:,:), & ! [IN]
313  landuse_fact_land(:,:), dt, & ! [IN]
314  snow_sfc_temp(:,:), snow_swe(:,:), & ! [INOUT]
315  snow_depth(:,:), snow_dzero(:,:), & ! [INOUT]
316  snow_nosnowsec(:,:), & ! [INOUT]
317  snow_albedo(:,:,:), & ! [OUT]
318  snow_atmos_sflx_sh(:,:), snow_atmos_sflx_lh(:,:), & ! [OUT]
319  snow_atmos_sflx_gh(:,:), snow_land_sflx_gh(:,:), & ! [OUT]
320  snow_land_sflx_water(:,:), & ! [OUT]
321  snow_frac(:,:) ) ! [OUT]
322 
323 !OCL XFILL
324  !$omp parallel do
325  do j = ljs, lje
326  do i = lis, lie
327  snow_land_sflx_ice(i,j) = 0.0_rp
328  enddo
329  enddo
330  end select
331 
332 !OCL XFILL
333  !!$omp parallel do
334  !do j = LJS, LJE
335  !do i = LIS, LIE
336  ! SNOW_ATMOS_SFLX_evap (i,j) = - SNOW_ATMOS_SFLX_LH(i,j) / LHV(i,j)
337  !end do
338  !end do
339  !call monitor_snow_water( SNOW_Depth (:,:), & ! [IN]
340  ! SNOW_Dzero (:,:), & ! [IN]
341  ! MONIT_WCONT1 (:,:) ) ! [OUT]
342 
343  !call monitor_land_regidual( ATMOS_SFLX_rain (:,:), & ! [IN] ! downward at surface
344  ! ATMOS_SFLX_snow (:,:), & ! [IN] ! downward at surface
345  ! SNOW_ATMOS_SFLX_evap(:,:), & ! [IN] ! upward at surface
346  ! SNOW_LAND_SFLX_water(:,:), & ! [IN] ! downward at bottom
347  ! SNOW_LAND_SFLX_ice (:,:), & ! [IN] ! downward at bottom
348  ! MONIT_WCONT0 (:,:), & ! [IN]
349  ! MONIT_WCONT1 (:,:), & ! [IN]
350  ! MONIT_SNOW_water (:,:) ) ! [OUT]
351 
352 !OCL XFILL
353  !$omp parallel do
354  do j = ljs, lje
355  do i = lis, lie
356  snow_qvef(i,j) = 1.0_rp ! tentative
357  end do
358  end do
359 
360  ! momentum fluxes and diagnostic variables above snowpack
361  call land_phy_snow_diags( lia, lis, lie, lja, ljs, lje, &
362  snow_frac(:,:), & ! [IN]
363  atmos_temp(:,:), atmos_pres(:,:), & ! [IN]
364  atmos_w(:,:), atmos_u(:,:), atmos_v(:,:), & ! [IN]
365  atmos_dens(:,:), atmos_qv(:,:), & ! [IN]
366  real_z1(:,:), atmos_pbl(:,:), & ! [IN]
367  atmos_sfc_dens(:,:), atmos_sfc_pres(:,:), snow_sfc_temp(:,:), & ! [IN]
368  snow_qvef(:,:), & ! [IN]
369  land_property(:,:,i_z0m), & ! [IN]
370  land_property(:,:,i_z0h), & ! [IN]
371  land_property(:,:,i_z0e), & ! [IN]
372  snow_atmos_sflx_mw(:,:), & ! [OUT]
373  snow_atmos_sflx_mu(:,:), & ! [OUT]
374  snow_atmos_sflx_mv(:,:), & ! [OUT]
375  snow_u10(:,:), snow_v10(:,:), & ! [OUT]
376  snow_t2(:,:), snow_q2(:,:) ) ! [OUT]
377 
378  call file_history_in( snow_albedo(:,:,i_sw), 'SNOW_ALB_SW', 'Snow surface albedo (short wave)', '1', dim_type='XY' )
379  call file_history_in( snow_albedo(:,:,i_lw), 'SNOW_ALB_LW', 'Snow surface albedo (long wave)', '1', dim_type='XY' )
380  call file_history_in( snow_atmos_sflx_sh(:,:), 'SNOW_ATMOS_SFLX_SH', 'Snow surface sensible heat flux', 'J/m2/s', dim_type='XY' )
381  call file_history_in( snow_atmos_sflx_lh(:,:), 'SNOW_ATMOS_SFLX_LH', 'Snow surface latent heat flux', 'J/m2/s', dim_type='XY' )
382  call file_history_in( snow_atmos_sflx_gh(:,:), 'SNOW_ATMOS_SFLX_GH', 'Snowpack received heat flux', 'J/m2/s', dim_type='XY' )
383  call file_history_in( snow_land_sflx_gh(:,:), 'SNOW_LAND_SFLX_GH', 'land surface ground heat flux under snow', 'J/m2/s', dim_type='XY' )
384  call file_history_in( snow_land_sflx_water(:,:), 'SNOW_LAND_SFLX_water', 'land surface liquid water flux under snow', 'kg/m2/s',dim_type='XY' )
385  call file_history_in( snow_land_sflx_water(:,:), 'SNOW_LAND_SFLX_ice', 'land surface ice water flux under snow', 'kg/m2/s',dim_type='XY' )
386  call file_history_in( snow_frac(:,:), 'SNOW_frac', 'Snow fraction on land subgrid', '1', dim_type='XY' )
387  call file_history_in( snow_atmos_sflx_mw(:,:), 'SNOW_ATMOS_SFLX_MW', 'Snow surface w-momentum flux', 'J/m2/s', dim_type='XY' )
388  call file_history_in( snow_atmos_sflx_mu(:,:), 'SNOW_ATMOS_SFLX_MU', 'Snow surface u-momentum flux', 'J/m2/s', dim_type='XY' )
389  call file_history_in( snow_atmos_sflx_mv(:,:), 'SNOW_ATMOS_SFLX_MV', 'Snow surface v-momentum flux', 'J/m2/s', dim_type='XY' )
390  call file_history_in( snow_u10(:,:), 'SNOW_U10', 'Wind velocity u at 10 m on snow surface', 'm/s', dim_type='XY' )
391  call file_history_in( snow_v10(:,:), 'SNOW_V10', 'Wind velocity v at 10 m on snow surface', 'm/s', dim_type='XY' )
392  call file_history_in( snow_t2(:,:), 'SNOW_T2', 'Air temperature at 2m on snow surface', 'K', dim_type='XY' )
393  call file_history_in( snow_q2(:,:), 'SNOW_Q2', 'Specific humidity at 2m on snow surface', 'kg/kg', dim_type='XY' )
394  endif
395 
396 
397 !OCL XFILL
398  !$omp parallel do
399  do j = ljs, lje
400  do i = lis, lie
401  land_qvef(i,j) = min( land_water(lks,i,j) / land_property(i,j,i_watercritical), beta_max )
402 
403  ! eq.(12) in Merlin et al.(2011) but simplified P=0.5 used
404  !sw = 0.5_RP + sign(0.5_RP,LAND_WATER(LKS,i,j)-LAND_PROPERTY(i,j,I_WaterCritical)) ! if W > Wc, sw = 1
405  !LAND_QVEF(i,j) = ( sw ) * 1.0_RP &
406  ! + ( 1.0_RP-sw ) * sqrt( 0.5_RP - 0.5_RP * cos( PI * LAND_WATER(LKS,i,j) / LAND_PROPERTY(i,j,I_WaterCritical) ) )
407 
408  land_tc_dz(i,j) = land_property(i,j,i_thermalcond) / lcz(lks)
409  end do
410  end do
411 
412 
413  !------------------------------------------------------------------------
415 
416 
417  select case ( land_sfc_type )
418  case ( 'SKIN' )
419 !OCL XFILL
420  !$omp parallel do
421  do j = ljs, lje
422  do i = lis, lie
423  land_sfc_albedo(i,j,i_r_direct ,i_r_ir ) = land_property(i,j,i_alblw)
424  land_sfc_albedo(i,j,i_r_diffuse,i_r_ir ) = land_property(i,j,i_alblw)
425  land_sfc_albedo(i,j,i_r_direct ,i_r_nir) = land_property(i,j,i_albsw)
426  land_sfc_albedo(i,j,i_r_diffuse,i_r_nir) = land_property(i,j,i_albsw)
427  land_sfc_albedo(i,j,i_r_direct ,i_r_vis) = land_property(i,j,i_albsw)
428  land_sfc_albedo(i,j,i_r_diffuse,i_r_vis) = land_property(i,j,i_albsw)
429  end do
430  end do
431 
432  call cpl_phy_sfc_skin( lia, lis, lie, lja, ljs, lje, &
433  atmos_temp(:,:), atmos_pres(:,:), & ! [IN]
434  atmos_w(:,:), atmos_u(:,:), atmos_v(:,:), & ! [IN]
435  atmos_dens(:,:), atmos_qv(:,:), lhv(:,:), & ! [IN]
436  real_z1(:,:), atmos_pbl(:,:), & ! [IN]
437  atmos_sfc_dens(:,:), atmos_sfc_pres(:,:), & ! [IN]
438  atmos_sflx_rad_dn(:,:,:,:), & ! [IN]
439  land_temp(lks,:,:), land_qvef(:,:), & ! [IN]
440  land_sfc_albedo(:,:,:,:), & ! [IN]
441  land_property(:,:,i_stomataresist), & ! [IN]
442  land_tc_dz(:,:), & ! [IN]
443  land_property(:,:,i_z0m), & ! [IN]
444  land_property(:,:,i_z0h), & ! [IN]
445  land_property(:,:,i_z0e), & ! [IN]
446  landuse_exists_land(:,:), dt, & ! [IN]
447  'LAND', & ! [IN]
448  land_sfc_temp(:,:), & ! [INOUT]
449  land_sflx_mw(:,:), land_sflx_mu(:,:), land_sflx_mv(:,:), & ! [OUT]
450  land_sflx_sh(:,:), sflx_qv(:,:), sflx_gh(:,:), & ! [OUT]
451  land_u10(:,:), land_v10(:,:), land_t2(:,:), land_q2(:,:) ) ! [OUT]
452 
453  case ( 'FIXED-TEMP' )
454 !OCL XFILL
455  !$omp parallel do
456  do j = ljs, lje
457  do i = lis, lie
458  land_sfc_temp(i,j) = land_temp(lks,i,j)
459  end do
460  end do
461 !OCL XFILL
462  !$omp parallel do
463  do j = ljs, lje
464  do i = lis, lie
465  land_sfc_albedo(i,j,i_r_direct ,i_r_ir ) = land_property(i,j,i_alblw)
466  land_sfc_albedo(i,j,i_r_diffuse,i_r_ir ) = land_property(i,j,i_alblw)
467  land_sfc_albedo(i,j,i_r_direct ,i_r_nir) = land_property(i,j,i_albsw)
468  land_sfc_albedo(i,j,i_r_diffuse,i_r_nir) = land_property(i,j,i_albsw)
469  land_sfc_albedo(i,j,i_r_direct ,i_r_vis) = land_property(i,j,i_albsw)
470  land_sfc_albedo(i,j,i_r_diffuse,i_r_vis) = land_property(i,j,i_albsw)
471  end do
472  end do
473 
474  call cpl_phy_sfc_fixed_temp( lia, lis, lie, lja, ljs, lje, &
475  atmos_temp(:,:), atmos_pres(:,:), & ! [IN]
476  atmos_w(:,:), atmos_u(:,:), atmos_v(:,:), & ! [IN]
477  atmos_dens(:,:), atmos_qv(:,:), lhv(:,:), & ! [IN]
478  real_z1(:,:), atmos_pbl(:,:), & ! [IN]
479  atmos_sfc_dens(:,:), atmos_sfc_pres(:,:), & ! [IN]
480  atmos_sflx_rad_dn(:,:,:,:), & ! [IN]
481  land_sfc_temp(:,:), land_qvef(:,:), & ! [IN]
482  land_sfc_albedo(:,:,:,:), & ! [IN]
483  land_property(:,:,i_stomataresist), & ! [IN]
484  land_property(:,:,i_z0m), & ! [IN]
485  land_property(:,:,i_z0h), & ! [IN]
486  land_property(:,:,i_z0e), & ! [IN]
487  landuse_exists_land(:,:), dt, & ! [IN]
488  land_sflx_mw(:,:), land_sflx_mu(:,:), land_sflx_mv(:,:), & ! [OUT]
489  land_sflx_sh(:,:), sflx_qv(:,:), sflx_gh(:,:), & ! [OUT]
490  land_u10(:,:), land_v10(:,:), & ! [OUT]
491  land_t2(:,:), land_q2(:,:) ) ! [OUT]
492 
493  end select
494 
495  ! LAND_SFLX_* are positive for downward
496 !OCL XFILL
497  !$omp parallel do
498  do j = ljs, lje
499  do i = lis, lie
500  land_sflx_gh(i,j) = - sflx_gh(i,j) ! inverse sign ( positive for upward to downward )
501  land_sflx_water(i,j) = atmos_sflx_rain(i,j) - sflx_qv(i,j)
502  land_sflx_ice(i,j) = atmos_sflx_snow(i,j)
503  end do
504  end do
505 
506  if ( .NOT. atmos_hydrometeor_dry ) then
507  !$omp parallel do
508  do j = ljs, lje
509  do i = lis, lie
510  land_sflx_lh(i,j) = sflx_qv(i,j) * lhv(i,j) ! always LHV
511  enddo
512  enddo
513  else
514  !$omp parallel do
515  do j = ljs, lje
516  do i = lis, lie
517  land_sflx_lh(i,j) = 0.0_rp
518  enddo
519  enddo
520  endif
521 
522  if ( snow_flag ) then
523 
524  ! marge land surface and snow surface !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
525 !OCL XFILL
526  !$omp parallel do
527  do j = ljs, lje
528  do i = lis, lie
529  land_sfc_temp(i,j) = ( snow_frac(i,j) ) * snow_sfc_temp(i,j) &
530  + ( 1.0_rp-snow_frac(i,j) ) * land_sfc_temp(i,j)
531 
532  do idir = i_r_direct, i_r_diffuse
533  land_sfc_albedo(i,j,idir,i_r_ir ) = ( snow_frac(i,j) ) * snow_albedo(i,j,i_lw) &
534  + ( 1.0_rp-snow_frac(i,j) ) * land_sfc_albedo(i,j,idir,i_r_ir)
535  land_sfc_albedo(i,j,idir,i_r_nir) = ( snow_frac(i,j) ) * snow_albedo(i,j,i_sw) &
536  + ( 1.0_rp-snow_frac(i,j) ) * land_sfc_albedo(i,j,idir,i_r_nir)
537  land_sfc_albedo(i,j,idir,i_r_vis) = ( snow_frac(i,j) ) * snow_albedo(i,j,i_sw) &
538  + ( 1.0_rp-snow_frac(i,j) ) * land_sfc_albedo(i,j,idir,i_r_vis)
539  enddo
540 
541  ! flux to the soil
542  land_sflx_gh(i,j) = ( snow_frac(i,j) ) * snow_land_sflx_gh(i,j) &
543  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_gh(i,j)
544  land_sflx_water(i,j) = ( snow_frac(i,j) ) * snow_land_sflx_water(i,j) &
545  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_water(i,j)
546  land_sflx_ice(i,j) = ( snow_frac(i,j) ) * snow_land_sflx_ice(i,j) &
547  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_ice(i,j)
548  ! flux to the atmosphere
549  land_sflx_sh(i,j) = ( snow_frac(i,j) ) * snow_atmos_sflx_sh(i,j) &
550  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_sh(i,j)
551  land_sflx_lh(i,j) = ( snow_frac(i,j) ) * snow_atmos_sflx_lh(i,j) &
552  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_lh(i,j)
553 
554  ! diagnostics
555  land_u10(i,j) = ( snow_frac(i,j) ) * snow_u10(i,j) &
556  + ( 1.0_rp-snow_frac(i,j) ) * land_u10(i,j)
557  land_v10(i,j) = ( snow_frac(i,j) ) * snow_v10(i,j) &
558  + ( 1.0_rp-snow_frac(i,j) ) * land_v10(i,j)
559  land_t2(i,j) = ( snow_frac(i,j) ) * snow_t2(i,j) &
560  + ( 1.0_rp-snow_frac(i,j) ) * land_t2(i,j)
561  land_q2(i,j) = ( snow_frac(i,j) ) * snow_q2(i,j) &
562  + ( 1.0_rp-snow_frac(i,j) ) * land_q2(i,j)
563  enddo
564  enddo
565 
566  end if
567 
568  if ( .NOT. atmos_hydrometeor_dry ) then
569  !$omp parallel do
570  do j = ljs, lje
571  do i = lis, lie
572  land_sflx_qtrc(i,j,i_qv) = land_sflx_lh(i,j) / lhv(i,j)
573  enddo
574  enddo
575  endif
576 
577  ! Surface flux for chemical tracers
578  if ( atmos_sw_phy_ch ) then
579  call atmos_phy_ch_driver_land_flux( land_sflx_qtrc(:,:,:) ) ! [INOUT]
580  endif
581 
582  !########## Set Surface Boundary to coupler ##########
583  call land_surface_set( countup=.true. )
584 
585  call prof_rapend ('LND_CalcTend', 1)
586 
587  return
module ATMOS admin
module Land admin
real(rp), dimension(:,:), allocatable, public snow_swe
snow water equivalent [kg/m2]
real(rp), dimension(:,:), allocatable, public land_sflx_water
land surface water flux [kg/m2/s]
real(rp), dimension(:), allocatable, public land_grid_cartesc_cz
center coordinate [m]: z, local=global
module coupler / surface fixed temp model
real(rp), dimension(:,:), allocatable, public atmos_pres
real(rp), dimension(:,:), allocatable, public land_sflx_ice
land surface ice flux [kg/m2/s]
integer, parameter, public i_heatcapacity
module land / physics / snow / ky90
integer, parameter, public i_waterlimit
real(rp), dimension(:,:), allocatable, public atmos_dens
real(rp), dimension(:,:,:), allocatable, public land_property
land surface property
real(rp), dimension(:,:), allocatable, public snow_sfc_temp
snow surface temperature [K]
module coupler / physics / surface skin
integer, parameter, public i_watercritical
module ATMOSPHERE / Physics Chemistry
real(rp), dimension(:,:), allocatable, public atmos_sfc_dens
real(rp), dimension(:,:), allocatable, public atmos_v
real(rp), dimension(:,:), allocatable, public atmos_sflx_snow
real(rp), dimension(:,:), allocatable, public land_q2
land surface water vapor at 2m [kg/kg]
real(dp), public time_dtsec_land
time interval of land step [sec]
Definition: scale_time.F90:51
real(rp), dimension(:,:), allocatable, public snow_depth
snow depth [m]
integer, parameter, public i_z0h
integer, parameter, public i_z0e
logical, dimension(:,:), allocatable, public landuse_exists_land
land calculation flag
real(rp), dimension(:,:,:), allocatable, public land_sflx_qtrc
land surface tracer flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_sflx_mu
land surface u-momentum flux [kg/m2/s]
integer, parameter, public i_lw
real(rp), dimension(:,:), allocatable, public snow_nosnowsec
sec while no snow [s]
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_z1
Height of the lowermost grid from surface (cell center) [m].
real(rp), dimension(:,:), allocatable, public atmos_temp
real(rp), dimension(:,:), allocatable, public land_sfc_temp
land surface skin temperature [K]
real(rp), dimension(:,:), allocatable, public atmos_sflx_rain
integer, parameter, public i_sw
subroutine, public land_phy_snow_diags(LIA, LIS, LIE, LJA, LJS, LJE, SNOW_frac, TMPA, PRSA, WA, UA, VA, RHOA, QVA, Z1, PBL, RHOS, PRSS, LST1, QVEF, Z0M, Z0H, Z0E, ZMFLX, XMFLX, YMFLX, U10, V10, T2, Q2)
real(rp), dimension(:,:), allocatable, public land_v10
land surface velocity v at 10m [m/s]
real(rp), dimension(:,:), allocatable, public atmos_pbl
module atmosphere / hydrometeor
real(rp), dimension(:,:,:,:), allocatable, public land_sfc_albedo
land surface albedo (direct/diffuse,IR/near-IR/VIS) (0-1)
character(len=h_short), public snow_type
module LANDUSE
real(rp), dimension(:,:), allocatable, public land_t2
land surface temperature at 2m [K]
module land / physics / snow / diagnostics
real(rp), dimension(:,:,:), allocatable, public land_water_t
tendency of LAND_WATER
real(rp), dimension(:,:,:), allocatable, public land_temp
temperature of each soil layer [K]
real(rp), dimension(:,:), allocatable, public land_sflx_lh
land surface latent heat flux [J/m2/s]
module TIME
Definition: scale_time.F90:16
real(rp), dimension(:,:), allocatable, public atmos_qv
integer, parameter, public i_stomataresist
logical, public atmos_sw_phy_ch
module LAND Variables
real(rp), dimension(:,:), allocatable, public land_u10
land surface velocity u at 10m [m/s]
real(rp), dimension(:,:,:), allocatable, public land_temp_t
tendency of LAND_TEMP
real(rp), dimension(:,:), allocatable, public land_sflx_gh
land surface heat flux [J/m2/s]
module land / grid / cartesianC
real(rp), dimension(:,:), allocatable, public snow_dzero
snow depth at melting point [m]
real(rp), dimension(:,:,:), allocatable, public land_water
moisture of each soil layer [m3/m3]
real(rp), dimension(:,:), allocatable, public atmos_u
subroutine, public atmos_phy_ch_driver_land_flux(SFLX_QTRC)
Driver.
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
module Atmosphere GRID CartesC Real(real space)
integer, parameter, public i_z0m
real(rp), dimension(:,:,:,:), allocatable, public atmos_sflx_rad_dn
real(rp), dimension(:,:), allocatable, public land_sflx_mw
land surface w-momentum flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_sflx_mv
land surface v-momentum flux [kg/m2/s]
integer, parameter, public i_alblw
real(rp), dimension(:,:), allocatable, public land_sflx_sh
land surface sensible heat flux [J/m2/s]
integer, parameter, public i_albsw
subroutine, public land_phy_snow_ky90(LIA, LIS, LIE, LJA, LJS, LJE, SFLX_rain, SFLX_snow, PRSA, TA, QA, WA, UA, VA, DENS, SFLX_RAD_dn, LANDUSE_fact_land, dt, TSNOW, SWE, SDepth, SDzero, nosnowsec, Salbedo, SFLX_SH, SFLX_LH, SFLX_GH, SNOW_LAND_GH, SNOW_LAND_Water, SNOW_frac)
Main routine for land submodel.
real(rp), dimension(:,:), allocatable, public atmos_w
real(rp), dimension(:,:), allocatable, public landuse_fact_land
land factor
integer, parameter, public i_thermalcond
subroutine, public cpl_phy_sfc_skin(IA, IS, IE, JA, JS, JE, TMPA, PRSA, WA, UA, VA, RHOA, QVA, LH, Z1, PBL, RHOS, PRSS, RFLXD, TG, QVEF, ALBEDO, Rb, TC_dZ, Z0M, Z0H, Z0E, calc_flag, dt, model_name, TMPS, ZMFLX, XMFLX, YMFLX, SHFLX, QVFLX, GFLX, U10, V10, T2, Q2)
subroutine, public cpl_phy_sfc_fixed_temp(IA, IS, IE, JA, JS, JE, TMPA, PRSA, WA, UA, VA, RHOA, QVA, LH, Z1, PBL, RHOS, PRSS, RFLXD, TMPS, QVEF, ALBEDO, Rb, Z0M, Z0H, Z0E, calc_flag, dt, ZMFLX, XMFLX, YMFLX, SHFLX, QVFLX, GFLX, U10, V10, T2, Q2)
character(len=h_short), public land_sfc_type
integer, parameter, public i_waterdiff
module file_history
Here is the call graph for this function:
Here is the caller graph for this function:

◆ land_driver_update()

subroutine, public mod_land_driver::land_driver_update ( )

Land step.

Definition at line 593 of file mod_land_driver.F90.

References mod_land_vars::i_heatcapacity, mod_land_vars::i_thermalcond, mod_land_vars::i_waterdiff, mod_land_vars::i_waterlimit, scale_land_dyn_bucket::land_dyn_bucket(), mod_land_admin::land_dyn_type, scale_land_grid_cartesc::land_grid_cartesc_cdz, mod_land_vars::land_property, mod_land_vars::land_sfc_temp, mod_land_vars::land_sflx_gh, mod_land_vars::land_sflx_ice, mod_land_vars::land_sflx_water, land_surface_get(), 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_landuse::landuse_fact_land, scale_land_grid_cartesc_index::lia, scale_land_grid_cartesc_index::lie, scale_land_grid_cartesc_index::lis, scale_land_grid_cartesc_index::lja, scale_land_grid_cartesc_index::lje, scale_land_grid_cartesc_index::ljs, scale_land_grid_cartesc_index::lke, scale_land_grid_cartesc_index::lkmax, scale_land_grid_cartesc_index::lks, scale_prof::prof_rapend(), scale_prof::prof_rapstart(), scale_time::time_dtsec_land, and scale_time::time_nowdaysec.

Referenced by mod_rm_driver::rm_driver().

593  use scale_time, only: &
594  dt => time_dtsec_land
595  use mod_land_vars, only: &
596  land_property, &
597  i_waterlimit, &
598  i_thermalcond, &
599  i_heatcapacity, &
600  i_waterdiff, &
601  land_temp, &
602  land_water, &
603  land_sflx_gh, &
604  land_sflx_water, &
605  land_sflx_ice, &
606  land_sfc_temp, &
607  land_temp_t, &
608  land_water_t, &
609  land_vars_total, &
611  use scale_land_grid_cartesc, only: &
612  lcdz => land_grid_cartesc_cdz
613  use scale_land_dyn_bucket, only: &
615  use scale_landuse, only: &
617  use scale_time, only: &
618  nowdaysec => time_nowdaysec
619  use scale_file_history, only: &
620  file_history_in
621  use mod_land_admin, only: &
623  implicit none
624 
625  real(RP) :: runoff(lia,lja)
626 
627  integer :: k, i, j
628  !---------------------------------------------------------------------------
629 
630  call prof_rapstart('LND_Update', 2)
631 
632  !########## Get Surface Boundary from coupler ##########
633  call land_surface_get
634 
635  !########## Dynamics / Update variables ##########
636  select case ( land_dyn_type )
637  case ( 'BUCKET' )
638  call land_dyn_bucket( lkmax, lks, lke, lia, lis, lie, lja, ljs, lje, &
639  land_temp_t(:,:,:), land_water_t(:,:,:), & ! [IN]
640  land_property(:,:,i_waterlimit), & ! [IN]
641  land_property(:,:,i_thermalcond), & ! [IN]
642  land_property(:,:,i_heatcapacity), & ! [IN]
643  land_property(:,:,i_waterdiff), & ! [IN]
644  land_sflx_gh(:,:), & ! [IN]
645  land_sflx_water(:,:), land_sflx_ice(:,:), & ! [IN]
646  landuse_fact_land(:,:), lcdz(:), & ! [IN]
647  dt, nowdaysec, & ! [IN]
648  land_temp(:,:,:), land_water(:,:,:), & ! [INOUT]
649  runoff(:,:) ) ! [OUT]
650  call file_history_in( runoff(:,:), 'RUNOFF', 'runoff water', 'kg', dim_type='XY' )
651  case ( 'INIT' )
652  ! Never update LAND_TEMP and LAND_WATER from initial condition
653  end select
654 
655  !########## Negative Fixer ##########
656  !$omp parallel do
657  do j = ljs, lje
658  do i = lis, lie
659  do k = lks, lke
660  land_water(k,i,j) = max( land_water(k,i,j), 0.0_rp )
661  enddo
662  enddo
663  enddo
664 
665  call land_vars_total
666 
667  !########## History & Monitor ##########
668  call land_vars_history
669 
670 
671  call prof_rapend ('LND_Update', 1)
672 
673  return
module Land admin
real(rp), dimension(:,:), allocatable, public land_sflx_water
land surface water flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_sflx_ice
land surface ice flux [kg/m2/s]
integer, parameter, public i_heatcapacity
integer, parameter, public i_waterlimit
real(rp), dimension(:,:,:), allocatable, public land_property
land surface property
real(dp), public time_nowdaysec
second of current time [sec]
Definition: scale_time.F90:73
real(dp), public time_dtsec_land
time interval of land step [sec]
Definition: scale_time.F90:51
real(rp), dimension(:,:), allocatable, public land_sfc_temp
land surface skin temperature [K]
module land / dynamics / bucket
module LANDUSE
real(rp), dimension(:,:,:), allocatable, public land_water_t
tendency of LAND_WATER
real(rp), dimension(:,:,:), allocatable, public land_temp
temperature of each soil layer [K]
module TIME
Definition: scale_time.F90:16
module LAND Variables
real(rp), dimension(:,:,:), allocatable, public land_temp_t
tendency of LAND_TEMP
real(rp), dimension(:,:), allocatable, public land_sflx_gh
land surface heat flux [J/m2/s]
module land / grid / cartesianC
subroutine, public land_dyn_bucket(LKMAX, LKS, LKE, LIA, LIS, LIE, LJA, LJS, LJE, TEMP_t, WATER_t, WaterLimit, ThermalCond, HeatCapacity, WaterDiff, SFLX_GH, SFLX_water, SFLX_ice, fact_land, CDZ, dt, NOWDAYSEC, TEMP, WATER, RUNOFF)
Physical processes for land submodel.
character(len=h_short), public land_dyn_type
real(rp), dimension(:,:,:), allocatable, public land_water
moisture of each soil layer [m3/m3]
subroutine, public land_vars_total
Budget monitor for land.
subroutine, public land_vars_history
History output set for land variables.
real(rp), dimension(:,:), allocatable, public landuse_fact_land
land factor
integer, parameter, public i_thermalcond
integer, parameter, public i_waterdiff
module file_history
real(rp), dimension(:), allocatable, public land_grid_cartesc_cdz
z-length of control volume [m]
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 679 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_dens, mod_land_vars::atmos_sfc_pres, mod_land_vars::atmos_sflx_rad_dn, mod_land_vars::atmos_sflx_rain, mod_land_vars::atmos_sflx_snow, 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(), mod_land_admin::land_do, scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by land_driver_calc_tendency(), and land_driver_update().

679  use mod_land_admin, only: &
680  land_do
681  use mod_land_vars, only: &
682  atmos_temp, &
683  atmos_pres, &
684  atmos_w, &
685  atmos_u, &
686  atmos_v, &
687  atmos_dens, &
688  atmos_qv, &
689  atmos_pbl, &
690  atmos_sfc_dens, &
691  atmos_sfc_pres, &
693  atmos_cossza, &
694  atmos_sflx_rain, &
696  use mod_cpl_vars, only: &
698  implicit none
699  !---------------------------------------------------------------------------
700 
701  call prof_rapstart('LND_SfcExch', 2)
702 
703  if ( land_do ) then
704  call cpl_getatm_lnd( atmos_temp(:,:), & ! [OUT]
705  atmos_pres(:,:), & ! [OUT]
706  atmos_w(:,:), & ! [OUT]
707  atmos_u(:,:), & ! [OUT]
708  atmos_v(:,:), & ! [OUT]
709  atmos_dens(:,:), & ! [OUT]
710  atmos_qv(:,:), & ! [OUT]
711  atmos_pbl(:,:), & ! [OUT]
712  atmos_sfc_dens(:,:), & ! [OUT]
713  atmos_sfc_pres(:,:), & ! [OUT]
714  atmos_sflx_rad_dn(:,:,:,:), & ! [OUT]
715  atmos_cossza(:,:), & ! [OUT]
716  atmos_sflx_rain(:,:), & ! [OUT]
717  atmos_sflx_snow(:,:) ) ! [OUT]
718  endif
719 
720  call prof_rapend ('LND_SfcExch', 2)
721 
722  return
module Land admin
real(rp), dimension(:,:), allocatable, public atmos_pres
real(rp), dimension(:,:), allocatable, public atmos_dens
real(rp), dimension(:,:), allocatable, public atmos_sfc_dens
real(rp), dimension(:,:), allocatable, public atmos_v
real(rp), dimension(:,:), allocatable, public atmos_sflx_snow
real(rp), dimension(:,:), allocatable, public atmos_temp
real(rp), dimension(:,:), allocatable, public atmos_sflx_rain
real(rp), dimension(:,:), allocatable, public atmos_pbl
module COUPLER Variables
real(rp), dimension(:,:), allocatable, public atmos_qv
module LAND Variables
real(rp), dimension(:,:), allocatable, public atmos_u
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
subroutine, public cpl_getatm_lnd(TEMP, PRES, W, U, V, DENS, QV, PBL, SFC_DENS, SFC_PRES, SFLX_rad_dn, cosSZA, SFLX_rain, SFLX_snow)
real(rp), dimension(:,:), allocatable, public atmos_cossza
real(rp), dimension(:,:,:,:), allocatable, public atmos_sflx_rad_dn
real(rp), dimension(:,:), allocatable, public atmos_w
logical, public land_do
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 728 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_admin::land_do, 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_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_qtrc, mod_land_vars::land_sflx_sh, mod_land_vars::land_t2, mod_land_vars::land_u10, mod_land_vars::land_v10, scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by land_driver_calc_tendency(), mod_rm_driver::restart_read(), and mod_rm_prep::rm_prep().

728  use mod_land_admin, only: &
729  land_do
730  use mod_land_vars, only: &
731  land_property, &
732  i_z0m, &
733  i_z0h, &
734  i_z0e, &
735  land_sfc_temp, &
736  land_sfc_albedo, &
737  land_sflx_mw, &
738  land_sflx_mu, &
739  land_sflx_mv, &
740  land_sflx_sh, &
741  land_sflx_lh, &
742  land_sflx_gh, &
743  land_sflx_qtrc, &
744  land_u10, &
745  land_v10, &
746  land_t2, &
747  land_q2
748  use mod_cpl_vars, only: &
749  cpl_putlnd
750  implicit none
751 
752  ! arguments
753  logical, intent(in) :: countup
754  !---------------------------------------------------------------------------
755 
756  call prof_rapstart('LND_SfcExch', 2)
757 
758  if ( land_do ) then
759  call cpl_putlnd( land_sfc_temp(:,:), & ! [IN]
760  land_sfc_albedo(:,:,:,:), & ! [IN]
761  land_property(:,:,i_z0m), & ! [IN]
762  land_property(:,:,i_z0h), & ! [IN]
763  land_property(:,:,i_z0e), & ! [IN]
764  land_sflx_mw(:,:), & ! [IN]
765  land_sflx_mu(:,:), & ! [IN]
766  land_sflx_mv(:,:), & ! [IN]
767  land_sflx_sh(:,:), & ! [IN]
768  land_sflx_lh(:,:), & ! [IN]
769  land_sflx_gh(:,:), & ! [IN]
770  land_sflx_qtrc(:,:,:), & ! [IN]
771  land_u10(:,:), & ! [IN]
772  land_v10(:,:), & ! [IN]
773  land_t2(:,:), & ! [IN]
774  land_q2(:,:), & ! [IN]
775  countup ) ! [IN]
776  endif
777 
778  call prof_rapend ('LND_SfcExch', 2)
779 
780  return
module Land admin
real(rp), dimension(:,:,:), allocatable, public land_property
land surface property
real(rp), dimension(:,:), allocatable, public land_q2
land surface water vapor at 2m [kg/kg]
integer, parameter, public i_z0h
integer, parameter, public i_z0e
real(rp), dimension(:,:,:), allocatable, public land_sflx_qtrc
land surface tracer flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_sflx_mu
land surface u-momentum flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_sfc_temp
land surface skin temperature [K]
real(rp), dimension(:,:), allocatable, public land_v10
land surface velocity v at 10m [m/s]
real(rp), dimension(:,:,:,:), allocatable, public land_sfc_albedo
land surface albedo (direct/diffuse,IR/near-IR/VIS) (0-1)
real(rp), dimension(:,:), allocatable, public land_t2
land surface temperature at 2m [K]
module COUPLER Variables
real(rp), dimension(:,:), allocatable, public land_sflx_lh
land surface latent heat flux [J/m2/s]
module LAND Variables
real(rp), dimension(:,:), allocatable, public land_u10
land surface velocity u at 10m [m/s]
real(rp), dimension(:,:), allocatable, public land_sflx_gh
land surface heat flux [J/m2/s]
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_G, SFLX_QTRC, U10, V10, T2, Q2, countup)
integer, parameter, public i_z0m
real(rp), dimension(:,:), allocatable, public land_sflx_mw
land surface w-momentum flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_sflx_mv
land surface v-momentum flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_sflx_sh
land surface sensible heat flux [J/m2/s]
logical, public land_do
Here is the call graph for this function:
Here is the caller graph for this function: