SCALE-RM
mod_land_driver.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
9 !-------------------------------------------------------------------------------
10 #include "scalelib.h"
12  !-----------------------------------------------------------------------------
13  !
14  !++ used modules
15  !
16  use scale_precision
17  use scale_io
18  use scale_prof
20  use scale_tracer
22 
23  use scale_const, only: &
24  i_lw => const_i_lw, &
25  i_sw => const_i_sw
26  !-----------------------------------------------------------------------------
27  implicit none
28  private
29  !-----------------------------------------------------------------------------
30  !
31  !++ Public procedure
32  !
33  public :: land_driver_setup
34  public :: land_driver_finalize
36  public :: land_driver_update
37  public :: land_surface_get
38  public :: land_surface_set
39 
40  !-----------------------------------------------------------------------------
41  !
42  !++ Public parameters & variables
43  !
44  !-----------------------------------------------------------------------------
45  !
46  !++ Private procedure
47  !
48  !-----------------------------------------------------------------------------
49  !
50  !++ Private parameters & variables
51  !
52  !-----------------------------------------------------------------------------
53 contains
54  !-----------------------------------------------------------------------------
56  subroutine land_driver_setup
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  if ( land_do ) then
79 
80  select case ( land_dyn_type )
81  case ( 'BUCKET' )
83  case ( 'INIT' )
84  ! do nothing
85  case default
86  log_error("LAND_driver_setup",*) 'LAND_DYN_TYPE is invalid: ', trim(land_dyn_type)
87  call prc_abort
88  end select
89 
90  select case ( land_sfc_type )
91  case ( 'SKIN' )
93  case ( 'FIXED-TEMP' )
95  case default
96  log_error("LAND_driver_setup",*) 'LAND_SFC_TYPE is invalid: ', trim(land_sfc_type)
97  call prc_abort
98  end select
99 
100  select case ( snow_type )
101  case ( 'NONE', 'OFF' )
102  case ( 'KY90' )
103  log_warn("LAND_driver_setup",*) 'SNOW model is enabled'
104  log_warn("LAND_driver_setup",*) 'SNOW model is on experimental stage.'
105  log_warn("LAND_driver_setup",*) 'Use this with your own risk.'
107  case default
108  log_error("LAND_driver_setup",*) 'SNOW_TYPE is invalid: ', trim(snow_type)
109  call prc_abort
110  end select
111 
112  end if
113 
114  return
115  end subroutine land_driver_setup
116 
117  !-----------------------------------------------------------------------------
119  subroutine land_driver_finalize
120  use mod_land_admin, only: &
121  land_do, &
122  land_dyn_type, &
123  snow_type
124  implicit none
125  !---------------------------------------------------------------------------
126 
127  log_newline
128  log_info("LAND_driver_finalize",*) 'Finalize'
129 
130  if ( land_do ) then
131 
132  select case ( land_dyn_type )
133  case ( 'BUCKET' )
134  case ( 'INIT' )
135  end select
136 
137  select case ( snow_type )
138  case ( 'NONE', 'OFF' )
139  case ( 'KY90' )
140  end select
141 
142  end if
143 
144  return
145  end subroutine land_driver_finalize
146 
147  !-----------------------------------------------------------------------------
149  subroutine land_driver_calc_tendency( force )
150  use scale_const, only: &
151  tem00 => const_tem00
152  use scale_time, only: &
153  dt => time_dtsec_land
154  use scale_file_history, only: &
155  file_history_in
156  use scale_atmos_grid_cartesc_real, only: &
157  real_z1 => atmos_grid_cartesc_real_z1
158  use scale_topography, only: &
159  tansl_x => topography_tansl_x, &
160  tansl_y => topography_tansl_y
161  use scale_atmos_hydrometeor, only: &
162  hydrometeor_lhv => atmos_hydrometeor_lhv, &
163  hydrometeor_lhs => atmos_hydrometeor_lhs, &
165  cv_water, &
166  cv_ice, &
167  lhf, &
168  i_qv
169  use scale_land_grid_cartesc, only: &
170  lcz => land_grid_cartesc_cz, &
171  cdz => land_grid_cartesc_cdz
172  use scale_land_phy_snow_ky90, only: &
174  use scale_land_phy_snow_diagnos, only: &
176  use scale_cpl_phy_sfc_skin, only: &
178  use scale_cpl_phy_sfc_fixed_temp, only: &
180  use scale_bulkflux, only: &
181  bulkflux_diagnose_scales
182  use mod_atmos_admin, only: &
184  use mod_atmos_phy_ch_driver, only: &
186  use mod_land_admin, only: &
187  land_sfc_type, &
188  snow_type
189  use mod_land_vars, only: &
190  i_waterlimit, &
191  i_watercritical, &
192  i_stomataresist, &
193  i_thermalcond, &
194  i_heatcapacity, &
195  i_waterdiff, &
196  i_alblw, &
197  i_albsw, &
198  i_z0m, &
199  i_z0h, &
200  i_z0e, &
201  snow_flag, &
202  land_property, &
203  land_temp, &
204  land_water, &
205  land_ice, &
206  land_sfc_temp, &
207  land_sfc_albedo, &
208  snow_sfc_temp, &
209  snow_swe, &
210  snow_depth, &
211  snow_dzero, &
212  snow_nosnowsec, &
213  land_temp_t, &
214  land_water_t, &
215  land_ice_t, &
216  land_sflx_gh, &
217  land_sflx_water, &
218  land_sflx_engi, &
219  land_sflx_mw, &
220  land_sflx_mu, &
221  land_sflx_mv, &
222  land_sflx_sh, &
223  land_sflx_lh, &
224  land_sflx_qtrc, &
225  land_u10, &
226  land_v10, &
227  land_t2, &
228  land_q2, &
229  land_ustar, &
230  land_tstar, &
231  land_qstar, &
232  land_wstar, &
233  land_rlmo, &
234  soil_ustar, &
235  soil_tstar, &
236  soil_qstar, &
237  soil_wstar, &
238  soil_rlmo, &
239  snow_ustar, &
240  snow_tstar, &
241  snow_qstar, &
242  snow_wstar, &
243  snow_rlmo, &
244  atmos_temp, &
245  atmos_pres, &
246  atmos_u, &
247  atmos_v, &
248  atmos_dens, &
249  atmos_qv, &
250  atmos_pbl, &
251  atmos_sfc_dens, &
252  atmos_sfc_pres, &
256  use scale_landuse, only: &
257  exists_land => landuse_exists_land
258  implicit none
259 
260  logical, intent(in) :: force
261 
262  ! parameters
263  real(rp), parameter :: beta_max = 1.0_rp
264 
265  ! works
266  real(rp) :: land_temp1(lia,lja)
267  real(rp) :: snow_qvef (lia,lja)
268  real(rp) :: land_wstr (lia,lja)
269  real(rp) :: land_qvef (lia,lja)
270  real(rp) :: land_tc_dz(lia,lja)
271  real(rp) :: sflx_qv (lia,lja)
272  real(rp) :: sflx_engi (lia,lja)
273  real(rp) :: lh (lia,lja) ! latent heat of vaporization [J/kg]
274  real(rp) :: atmos_w (lia,lja)
275  real(rp) :: total
276 
277  ! for snow
278  real(rp) :: snow_albedo (lia,lja,2)
279  real(rp) :: snow_atmos_sflx_sh (lia,lja)
280  real(rp) :: snow_atmos_sflx_lh (lia,lja)
281  real(rp) :: snow_atmos_sflx_gh (lia,lja)
282  real(rp) :: snow_atmos_sflx_qv (lia,lja)
283  real(rp) :: snow_land_sflx_gh (lia,lja)
284  real(rp) :: snow_land_sflx_water(lia,lja)
285  real(rp) :: snow_land_sflx_engi (lia,lja)
286  real(rp) :: snow_frac (lia,lja)
287 
288  real(rp) :: snow_atmos_sflx_mw (lia,lja)
289  real(rp) :: snow_atmos_sflx_mu (lia,lja)
290  real(rp) :: snow_atmos_sflx_mv (lia,lja)
291  real(rp) :: snow_u10 (lia,lja)
292  real(rp) :: snow_v10 (lia,lja)
293  real(rp) :: snow_t2 (lia,lja)
294  real(rp) :: snow_q2 (lia,lja)
295 
296  ! monitor
297  !real(RP) :: MONIT_WCONT0 (LIA,LJA)
298  !real(RP) :: MONIT_WCONT1 (LIA,LJA)
299  !real(RP) :: MONIT_ENG0 (LIA,LJA)
300  !real(RP) :: MONIT_ENG1 (LIA,LJA)
301  !
302  !real(RP) :: MONIT_SNOW_heat (LIA,LJA)
303  !real(RP) :: MONIT_SNOW_water (LIA,LJA)
304  !real(RP) :: MONIT_LAND_heat (LIA,LJA)
305  !real(RP) :: MONIT_LAND_water (LIA,LJA)
306 
307  integer :: k, i, j, iq, idir
308  !---------------------------------------------------------------------------
309 
310  call prof_rapstart('LND_CalcTend', 1)
311 
312  !$acc data create(LAND_TEMP1,LAND_WSTR,LAND_QVEF,LAND_TC_dZ,SFLX_QV,SFLX_ENGI,LH,ATMOS_W)
313 
314  !########## Get Surface Boundary from coupler ##########
315  call land_surface_get
316 
317  !########## reset tendencies ##########
318 !OCL XFILL
319  !$omp parallel do collapse(2)
320  !$acc kernels
321  do j = ljs, lje
322  do i = lis, lie
323  do k = lks, lke
324  land_temp_t(k,i,j) = 0.0_rp
325  land_water_t(k,i,j) = 0.0_rp
326  land_ice_t(k,i,j) = 0.0_rp
327  enddo
328  enddo
329  enddo
330  !$acc end kernels
331 
332 !OCL XFILL
333  !$omp parallel do collapse(2)
334  !$acc kernels
335  do iq = 1, qa
336  do j = ljs, lje
337  do i = lis, lie
338  land_sflx_qtrc(i,j,iq) = 0.0_rp
339  enddo
340  enddo
341  enddo
342  !$acc end kernels
343 
344  !$omp parallel do
345  !$acc kernels
346  do j = ljs, lje
347  do i = lis, lie
348  atmos_w(i,j) = atmos_u(i,j) * tansl_x(i,j) + atmos_v(i,j) * tansl_y(i,j)
349  end do
350  end do
351  !$acc end kernels
352 
353  if ( snow_flag ) then
354  !------------------------------------------------------------------------
356 
357  !$acc update host(LAND_SFC_TEMP)
358  !$acc update host(ATMOS_SFLX_water,ATMOS_SFLX_ENGI,ATMOS_PRES,ATMOS_TEMP,ATMOS_QV,ATMOS_W,ATMOS_U,ATMOS_V,ATMOS_DENS,ATMOS_PBL,ATMOS_SFC_DENS,ATMOS_SFC_PRES,ATMOS_SFLX_rad_dn,exists_land,SFLX_ENGI)
359 
360 !OCL XFILL
361  !$omp parallel do
362  do j = ljs, lje
363  do i = lis, lie
364  ! This is for debug---adachi start
365  !if(( int(SNOW_frac(i,j)) == 1 ).and.( abs(SNOW_SFC_TEMP(i,j)-LAND_SFC_TEMP(i,j))/=0 ))then
366  ! LOG_ERROR("LAND_driver_calc_tendency",*) "Error please check SNOW_SFC_TEMP routine"
367  ! call PRC_abort
368  !endif
369  ! This is for debug---adachi end
370  snow_sfc_temp(i,j) = land_sfc_temp(i,j)
371  end do
372  end do
373 
374  select case ( snow_type )
375  case ( 'KY90' )
376  ! accumulation and melt of snow if there is snow
377 
378  !MONIT_WCONT0 = 0.0_RP
379  !call monitor_snow_water( SNOW_Depth (:,:), & ! [IN]
380  ! SNOW_Dzero (:,:), & ! [IN]
381  ! MONIT_WCONT0 (:,:) ) ! [OUT]
382 
383  call land_phy_snow_ky90( lia, lis, lie, lja, ljs, lje, &
384  atmos_sflx_water(:,:), atmos_sflx_engi(:,:), & ! [IN]
385  atmos_pres(:,:), atmos_temp(:,:), atmos_qv(:,:), & ! [IN]
386  atmos_w(:,:), atmos_u(:,:), atmos_v(:,:), & ! [IN]
387  atmos_sfc_dens(:,:), & ! [IN]
388  atmos_sflx_rad_dn(:,:,:,:), & ! [IN]
389  exists_land(:,:), dt, & ! [IN]
390  snow_sfc_temp(:,:), snow_swe(:,:), & ! [INOUT]
391  snow_depth(:,:), snow_dzero(:,:), & ! [INOUT]
392  snow_nosnowsec(:,:), & ! [INOUT]
393  snow_albedo(:,:,:), & ! [OUT]
394  snow_atmos_sflx_sh(:,:), & ! [OUT]
395  snow_atmos_sflx_lh(:,:), snow_atmos_sflx_qv(:,:), & ! [OUT]
396  sflx_engi(:,:), & ! [OUT]
397  snow_atmos_sflx_gh(:,:), snow_land_sflx_gh(:,:), & ! [OUT]
398  snow_land_sflx_water(:,:), & ! [OUT]
399  snow_frac(:,:) ) ! [OUT]
400 
401 !OCL XFILL
402  !$omp parallel do schedule(dynamic)
403  do j = ljs, lje
404  do i = lis, lie
405  if ( exists_land(i,j) ) then
406  snow_land_sflx_engi(i,j) = atmos_sflx_engi(i,j) & ! internal energy of precipitation
407  - sflx_engi(i,j) ! internal energy of evapolation
408  end if
409  enddo
410  enddo
411  end select
412 
413 !OCL XFILL
414  !call monitor_snow_water( SNOW_Depth (:,:), & ! [IN]
415  ! SNOW_Dzero (:,:), & ! [IN]
416  ! MONIT_WCONT1 (:,:) ) ! [OUT]
417 
418  !call monitor_land_regidual( ATMOS_SFLX_water (:,:), & ! [IN] ! downward at surface
419  ! ATMOS_SFLX_ENGI (:,:), & ! [IN] ! downward at surface
420  ! SNOW_ATMOS_SFLX_evap(:,:), & ! [IN] ! upward at surface
421  ! SNOW_LAND_SFLX_water(:,:), & ! [IN] ! downward at bottom
422  ! MONIT_WCONT0 (:,:), & ! [IN]
423  ! MONIT_WCONT1 (:,:), & ! [IN]
424  ! MONIT_SNOW_water (:,:) ) ! [OUT]
425 
426 !OCL XFILL
427  !$omp parallel do
428  do j = ljs, lje
429  do i = lis, lie
430  snow_qvef(i,j) = 1.0_rp ! tentative
431  end do
432  end do
433 
434  ! momentum fluxes and diagnostic variables above snowpack
435  call land_phy_snow_diags( lia, lis, lie, lja, ljs, lje, &
436  snow_frac(:,:), & ! [IN]
437  atmos_temp(:,:), atmos_pres(:,:), & ! [IN]
438  atmos_w(:,:), atmos_u(:,:), atmos_v(:,:), & ! [IN]
439  atmos_dens(:,:), atmos_qv(:,:), & ! [IN]
440  real_z1(:,:), atmos_pbl(:,:), & ! [IN]
441  atmos_sfc_dens(:,:), atmos_sfc_pres(:,:), snow_sfc_temp(:,:), & ! [IN]
442  snow_qvef(:,:), & ! [IN]
443  land_property(:,:,i_z0m), & ! [IN]
444  land_property(:,:,i_z0h), & ! [IN]
445  land_property(:,:,i_z0e), & ! [IN]
446  snow_atmos_sflx_mw(:,:), & ! [OUT]
447  snow_atmos_sflx_mu(:,:), & ! [OUT]
448  snow_atmos_sflx_mv(:,:), & ! [OUT]
449  snow_ustar(:,:), snow_tstar(:,:), snow_qstar(:,:), & ! [OUT]
450  snow_wstar(:,:), & ! [OUT]
451  snow_rlmo(:,:), & ! [OUT]
452  snow_u10(:,:), snow_v10(:,:), & ! [OUT]
453  snow_t2(:,:), snow_q2(:,:) ) ! [OUT]
454 
455  call file_history_in( snow_frac(:,:), 'LAND_SNOW_frac', 'Snow fraction on land subgrid', '1' )
456  call file_history_in( snow_albedo(:,:,i_sw), 'LAND_SNOW_ALB_SW', 'Snow surface albedo (short wave)', '1' )
457  call file_history_in( snow_albedo(:,:,i_lw), 'LAND_SNOW_ALB_LW', 'Snow surface albedo (long wave)', '1' )
458  call file_history_in( snow_atmos_sflx_sh(:,:), 'LAND_SNOW_SFLX_SH', 'Snow surface sensible heat flux', 'J/m2/s' )
459  call file_history_in( snow_atmos_sflx_lh(:,:), 'LAND_SNOW_SFLX_LH', 'Snow surface latent heat flux', 'J/m2/s' )
460  call file_history_in( snow_atmos_sflx_gh(:,:), 'LAND_SNOW_SFLX_GH', 'Snowpack received heat flux', 'J/m2/s' )
461  call file_history_in( snow_atmos_sflx_mw(:,:), 'LAND_SNOW_SFLX_MW', 'Snow surface w-momentum flux', 'J/m2/s' )
462  call file_history_in( snow_atmos_sflx_mu(:,:), 'LAND_SNOW_SFLX_MU', 'Snow surface u-momentum flux', 'J/m2/s' )
463  call file_history_in( snow_atmos_sflx_mv(:,:), 'LAND_SNOW_SFLX_MV', 'Snow surface v-momentum flux', 'J/m2/s' )
464  call file_history_in( snow_u10(:,:), 'LAND_SNOW_U10', 'Wind velocity u at 10 m on snow surface', 'm/s' )
465  call file_history_in( snow_v10(:,:), 'LAND_SNOW_V10', 'Wind velocity v at 10 m on snow surface', 'm/s' )
466  call file_history_in( snow_t2(:,:), 'LAND_SNOW_T2', 'Air temperature at 2m on snow surface', 'K' )
467  call file_history_in( snow_q2(:,:), 'LAND_SNOW_Q2', 'Specific humidity at 2m on snow surface', 'kg/kg' )
468 
469  call file_history_in( snow_land_sflx_gh(:,:), 'LAND_SNOW_LAND_SFLX_GH', 'land surface ground heat flux under snow', 'J/m2/s' )
470  call file_history_in( snow_land_sflx_water(:,:), 'LAND_SNOW_LAND_SFLX_water', 'land surface water mass flux under snow', 'kg/m2/s' )
471  call file_history_in( snow_land_sflx_engi(:,:), 'LAND_SNOW_LAND_SFLX_ENGI', 'land surface internal energy flux under snow', 'kg/m2/s' )
472  endif
473 
474 
475 !OCL XFILL
476  !$omp parallel do schedule(dynamic) &
477  !$omp private(total)
478  !$acc kernels
479  do j = ljs, lje
480  do i = lis, lie
481  if ( exists_land(i,j) ) then
482  total = land_water(lks,i,j) + land_ice(lks,i,j)
483  land_wstr(i,j) = total * cdz(lks) &
484  + dt * ( atmos_sflx_water(i,j) &
485  + max( 0.0_rp, 2.0_rp * land_property(i,j,i_waterdiff) &
486  * ( land_water(lks+1,i,j) - land_water(lks,i,j) ) / ( lcz(lks) + lcz(lks+1) ) ) )
487  if ( atmos_hydrometeor_dry ) then
488  land_qvef(i,j) = 0.0_rp
489  else
490  land_qvef(i,j) = min( total / land_property(i,j,i_watercritical), beta_max )
491  end if
492 
493  ! eq.(12) in Merlin et al.(2011) but simplified P=0.5 used
494  !sw = 0.5_RP + sign(0.5_RP,LAND_WATER(LKS,i,j)-LAND_PROPERTY(i,j,I_WaterCritical)) ! if W > Wc, sw = 1
495  !LAND_QVEF(i,j) = ( sw ) * 1.0_RP &
496  ! + ( 1.0_RP-sw ) * sqrt( 0.5_RP - 0.5_RP * cos( PI * LAND_WATER(LKS,i,j) / LAND_PROPERTY(i,j,I_WaterCritical) ) )
497 
498  land_tc_dz(i,j) = land_property(i,j,i_thermalcond) / lcz(lks)
499  end if
500  end do
501  end do
502  !$acc end kernels
503 
504 
505  !------------------------------------------------------------------------
507 
508 
509  !$omp parallel do schedule(dynamic)
510  !$acc kernels
511  do j = ljs, lje
512  do i = lis, lie
513  if ( exists_land(i,j) ) then
514  if ( land_ice(lks,i,j) > 0.0_rp ) then
515  call hydrometeor_lhs( land_sfc_temp(i,j), lh(i,j) )
516  else
517  call hydrometeor_lhv( land_sfc_temp(i,j), lh(i,j) )
518  end if
519  end if
520  end do
521  end do
522  !$acc end kernels
523 
524 
525  select case ( land_sfc_type )
526  case ( 'SKIN' )
527 !OCL XFILL
528  !$omp parallel do schedule(dynamic)
529  !$acc kernels
530  do j = ljs, lje
531  do i = lis, lie
532  if ( exists_land(i,j) ) then
533  land_temp1(i,j) = land_temp(lks,i,j)
534 
541  end if
542  end do
543  end do
544  !$acc end kernels
545 
546  call cpl_phy_sfc_skin( lia, lis, lie, lja, ljs, lje, &
547  atmos_temp(:,:), atmos_pres(:,:), & ! [IN]
548  atmos_w(:,:), atmos_u(:,:), atmos_v(:,:), & ! [IN]
549  atmos_dens(:,:), atmos_qv(:,:), & ! [IN]
550  lh(:,:), real_z1(:,:), atmos_pbl(:,:), & ! [IN]
551  atmos_sfc_dens(:,:), atmos_sfc_pres(:,:), & ! [IN]
552  atmos_sflx_rad_dn(:,:,:,:), & ! [IN]
553  land_temp1(:,:), land_wstr(:,:), land_qvef(:,:), & ! [IN]
554  land_sfc_albedo(:,:,:,:), & ! [IN]
555  land_property(:,:,i_stomataresist), & ! [IN]
556  land_tc_dz(:,:), & ! [IN]
557  land_property(:,:,i_z0m), & ! [IN]
558  land_property(:,:,i_z0h), & ! [IN]
559  land_property(:,:,i_z0e), & ! [IN]
560  exists_land(:,:), dt, & ! [IN]
561  'LAND', & ! [IN]
562  land_sfc_temp(:,:), & ! [INOUT]
563  land_sflx_mw(:,:), land_sflx_mu(:,:), land_sflx_mv(:,:), & ! [OUT]
564  land_sflx_sh(:,:), land_sflx_lh(:,:), sflx_qv(:,:), & ! [OUT]
565  land_sflx_gh(:,:), & ! [OUT]
566  soil_ustar(:,:), soil_tstar(:,:), soil_qstar(:,:), & ! [OUT]
567  soil_wstar(:,:), & ! [OUT]
568  soil_rlmo(:,:), & ! [OUT]
569  land_u10(:,:), land_v10(:,:), land_t2(:,:), land_q2(:,:) ) ! [OUT]
570 
571  case ( 'FIXED-TEMP' )
572 !OCL XFILL
573  !$omp parallel do schedule(dynamic)
574  !$acc kernels
575  do j = ljs, lje
576  do i = lis, lie
577  if ( exists_land(i,j) ) then
578  land_sfc_temp(i,j) = land_temp(lks,i,j)
579  end if
580  end do
581  end do
582  !$acc end kernels
583 !OCL XFILL
584  !$omp parallel do schedule(dynamic)
585  !$acc kernels
586  do j = ljs, lje
587  do i = lis, lie
588  if ( exists_land(i,j) ) then
595  end if
596  end do
597  end do
598  !$acc end kernels
599 
600  call cpl_phy_sfc_fixed_temp( lia, lis, lie, lja, ljs, lje, &
601  atmos_temp(:,:), atmos_pres(:,:), & ! [IN]
602  atmos_w(:,:), atmos_u(:,:), atmos_v(:,:), & ! [IN]
603  atmos_dens(:,:), atmos_qv(:,:), lh(:,:), & ! [IN]
604  real_z1(:,:), atmos_pbl(:,:), & ! [IN]
605  atmos_sfc_dens(:,:), atmos_sfc_pres(:,:), & ! [IN]
606  atmos_sflx_rad_dn(:,:,:,:), & ! [IN]
607  land_sfc_temp(:,:), land_wstr(:,:), land_qvef(:,:), & ! [IN]
608  land_sfc_albedo(:,:,:,:), & ! [IN]
609  land_property(:,:,i_stomataresist), & ! [IN]
610  land_property(:,:,i_z0m), & ! [IN]
611  land_property(:,:,i_z0h), & ! [IN]
612  land_property(:,:,i_z0e), & ! [IN]
613  exists_land(:,:), dt, & ! [IN]
614  land_sflx_mw(:,:), land_sflx_mu(:,:), land_sflx_mv(:,:), & ! [OUT]
615  land_sflx_sh(:,:), land_sflx_lh(:,:), sflx_qv(:,:), & ! [OUT]
616  land_sflx_gh(:,:), & ! [OUT]
617  soil_ustar(:,:), soil_tstar(:,:), soil_qstar(:,:), & ! [OUT]
618  soil_wstar(:,:), & ! [OUT]
619  soil_rlmo(:,:), & ! [OUT]
620  land_u10(:,:), land_v10(:,:), & ! [OUT]
621  land_t2(:,:), land_q2(:,:) ) ! [OUT]
622  end select
623 
624  !$omp parallel do schedule(dynamic)
625  !$acc kernels
626  do j = ljs, lje
627  do i = lis, lie
628  if ( exists_land(i,j) ) then
629  if ( land_ice(lks,i,j) > 0.0_rp ) then
630  sflx_engi(i,j) = ( cv_ice * land_sfc_temp(i,j) - lhf ) * sflx_qv(i,j)
631  else
632  sflx_engi(i,j) = cv_water * land_sfc_temp(i,j) * sflx_qv(i,j)
633  end if
634  end if
635  end do
636  end do
637  !$acc end kernels
638 
639  ! LAND_SFLX_* are positive for downward
640 !OCL XFILL
641  !$omp parallel do schedule(dynamic)
642  !$acc kernels
643  do j = ljs, lje
644  do i = lis, lie
645  if ( exists_land(i,j) ) then
646  land_sflx_water(i,j) = atmos_sflx_water(i,j) - sflx_qv(i,j)
647  land_sflx_engi(i,j) = atmos_sflx_engi(i,j) & ! internal energy of precipitation
648  - sflx_engi(i,j) ! internal energy of evapolation or sublimation
649  end if
650  end do
651  end do
652  !$acc end kernels
653 
654  if ( snow_flag ) then
655 
656  call file_history_in( land_sflx_mw(:,:), 'SOIL_SFLX_MW', 'soil surface w-momentum flux (upward)', 'kg/m2/s' )
657  call file_history_in( land_sflx_mu(:,:), 'SOIL_SFLX_MU', 'soil surface u-momentum flux (upward)', 'kg/m2/s' )
658  call file_history_in( land_sflx_mv(:,:), 'SOIL_SFLX_MV', 'soil surface v-momentum flux (upward)', 'kg/m2/s' )
659  call file_history_in( land_sflx_sh(:,:), 'SOIL_SFLX_SH', 'soil surface sensible heat flux (upward)', 'J/m2/s' )
660  call file_history_in( land_sflx_lh(:,:), 'SOIL_SFLX_LH', 'soil surface latent heat flux (upward)', 'J/m2/s' )
661  call file_history_in( land_u10(:,:), 'LAND_SOIL_U10', 'Wind velocity u at 10 m on soil surface', 'm/s' )
662  call file_history_in( land_v10(:,:), 'LAND_SOIL_V10', 'Wind velocity v at 10 m on soil surface', 'm/s' )
663  call file_history_in( land_t2(:,:), 'LAND_SOIL_T2', 'Air temperature at 2m on soil surface', 'K' )
664  call file_history_in( land_q2(:,:), 'LAND_SOIL_Q2', 'Specific humidity at 2m on soil surface', 'kg/kg' )
665 
666  ! marge land surface and snow surface !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
667 !OCL XFILL
668  !$omp parallel do schedule(dynamic)
669  do j = ljs, lje
670  do i = lis, lie
671  if ( exists_land(i,j) ) then
672  land_sfc_temp(i,j) = ( snow_frac(i,j) ) * snow_sfc_temp(i,j) &
673  + ( 1.0_rp-snow_frac(i,j) ) * land_sfc_temp(i,j)
674 
675  do idir = i_r_direct, i_r_diffuse
676  land_sfc_albedo(i,j,idir,i_r_ir ) = ( snow_frac(i,j) ) * snow_albedo(i,j,i_lw) &
677  + ( 1.0_rp-snow_frac(i,j) ) * land_sfc_albedo(i,j,idir,i_r_ir)
678  land_sfc_albedo(i,j,idir,i_r_nir) = ( snow_frac(i,j) ) * snow_albedo(i,j,i_sw) &
679  + ( 1.0_rp-snow_frac(i,j) ) * land_sfc_albedo(i,j,idir,i_r_nir)
680  land_sfc_albedo(i,j,idir,i_r_vis) = ( snow_frac(i,j) ) * snow_albedo(i,j,i_sw) &
681  + ( 1.0_rp-snow_frac(i,j) ) * land_sfc_albedo(i,j,idir,i_r_vis)
682  enddo
683 
684 
685  ! flux to the soil
686  land_sflx_gh(i,j) = ( snow_frac(i,j) ) * snow_land_sflx_gh(i,j) &
687  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_gh(i,j)
688  land_sflx_water(i,j) = ( snow_frac(i,j) ) * snow_land_sflx_water(i,j) &
689  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_water(i,j)
690  land_sflx_engi(i,j) = ( snow_frac(i,j) ) * snow_land_sflx_engi(i,j) &
691  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_engi(i,j)
692  ! flux to the atmosphere
693  land_sflx_mw(i,j) = ( snow_frac(i,j) ) * snow_atmos_sflx_mw(i,j) &
694  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_mw(i,j)
695  land_sflx_mu(i,j) = ( snow_frac(i,j) ) * snow_atmos_sflx_mu(i,j) &
696  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_mu(i,j)
697  land_sflx_mv(i,j) = ( snow_frac(i,j) ) * snow_atmos_sflx_mv(i,j) &
698  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_mv(i,j)
699  land_sflx_sh(i,j) = ( snow_frac(i,j) ) * snow_atmos_sflx_sh(i,j) &
700  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_sh(i,j)
701  land_sflx_lh(i,j) = ( snow_frac(i,j) ) * snow_atmos_sflx_lh(i,j) &
702  + ( 1.0_rp-snow_frac(i,j) ) * land_sflx_lh(i,j)
703  sflx_qv(i,j) = ( snow_frac(i,j) ) * snow_atmos_sflx_qv(i,j) &
704  + ( 1.0_rp-snow_frac(i,j) ) * sflx_qv(i,j)
705  ! diagnostics
706  land_u10(i,j) = ( snow_frac(i,j) ) * snow_u10(i,j) &
707  + ( 1.0_rp-snow_frac(i,j) ) * land_u10(i,j)
708  land_v10(i,j) = ( snow_frac(i,j) ) * snow_v10(i,j) &
709  + ( 1.0_rp-snow_frac(i,j) ) * land_v10(i,j)
710  land_t2(i,j) = ( snow_frac(i,j) ) * snow_t2(i,j) &
711  + ( 1.0_rp-snow_frac(i,j) ) * land_t2(i,j)
712  land_q2(i,j) = ( snow_frac(i,j) ) * snow_q2(i,j) &
713  + ( 1.0_rp-snow_frac(i,j) ) * land_q2(i,j)
714  end if
715  enddo
716  enddo
717 
718  !$acc update device(LAND_SFC_TEMP,LAND_SFC_albedo,LAND_SFLX_GH,LAND_SFLX_water,LAND_SFLX_ENGI,LAND_SFLX_MW,LAND_SFLX_MU,LAND_SFLX_MV,LAND_SFLX_SH,LAND_SFLX_LH,SFLX_QV,LAND_U10,LAND_V10,LAND_T2,LAND_Q2)
719 
720  call bulkflux_diagnose_scales( lia, lis, lie, lja, ljs, lje, &
721  land_sflx_mw(:,:), land_sflx_mu(:,:), land_sflx_mv(:,:), & ! [IN]
722  land_sflx_sh(:,:), sflx_qv(:,:), & ! [IN]
723  atmos_sfc_dens(:,:), land_sfc_temp(:,:), atmos_pbl(:,:), & ! [IN]
724  land_ustar(:,:), land_tstar(:,:), land_qstar(:,:), & ! [OUT]
725  land_wstar(:,:), land_rlmo(:,:), & ! [OUT]
726  mask = exists_land(:,:) ) ! [IN]
727 
728  end if
729 
730  if ( .NOT. atmos_hydrometeor_dry ) then
731  !$omp parallel do schedule(dynamic)
732  !$acc kernels
733  do j = ljs, lje
734  do i = lis, lie
735  if ( exists_land(i,j) ) then
736  land_sflx_qtrc(i,j,i_qv) = sflx_qv(i,j)
737  end if
738  enddo
739  enddo
740  !$acc end kernels
741  end if
742 
743 
744  ! Surface flux for chemical tracers
745  if ( atmos_sw_phy_ch ) then
746  !$acc update host(LAND_SFLX_QTRC)
747  call atmos_phy_ch_driver_land_flux( land_sflx_qtrc(:,:,:) ) ! [INOUT]
748  !$acc update device(LAND_SFLX_QTRC)
749  endif
750 
751  !########## Set Surface Boundary to coupler ##########
752  call land_surface_set( countup=.true. )
753 
754  !$acc end data
755 
756  call prof_rapend ('LND_CalcTend', 1)
757 
758  return
759  end subroutine land_driver_calc_tendency
760 
761  !-----------------------------------------------------------------------------
763  subroutine land_driver_update
764  use scale_time, only: &
765  dt => time_dtsec_land
766  use mod_land_vars, only: &
767  land_property, &
768  i_waterlimit, &
769  i_thermalcond, &
770  i_heatcapacity, &
771  i_waterdiff, &
772  land_temp, &
773  land_water, &
774  land_ice, &
775  land_sflx_gh, &
776  land_sflx_water, &
777  land_sflx_engi, &
778  land_runoff, &
780  land_sfc_temp, &
781  land_temp_t, &
782  land_water_t, &
783  land_ice_t, &
785  use scale_land_grid_cartesc, only: &
786  lcdz => land_grid_cartesc_cdz
787  use scale_land_dyn_bucket, only: &
789  use scale_landuse, only: &
790  exists_land => landuse_exists_land
791  use scale_time, only: &
792  nowdaysec => time_nowdaysec
793  use scale_file_history, only: &
794  file_history_in
795  use mod_land_admin, only: &
797  implicit none
798 
799  integer :: k, i, j
800  !---------------------------------------------------------------------------
801 
802  call prof_rapstart('LND_Update', 1)
803 
804  !########## Get Surface Boundary from coupler ##########
805  call land_surface_get
806 
807  !########## Dynamics / Update variables ##########
808  select case ( land_dyn_type )
809  case ( 'BUCKET' )
810  call land_dyn_bucket( lkmax, lks, lke, lia, lis, lie, lja, ljs, lje, &
811  land_temp_t(:,:,:), & ! [IN]
812  land_water_t(:,:,:), land_ice_t(:,:,:), & ! [IN]
813  land_property(:,:,i_waterlimit), & ! [IN]
814  land_property(:,:,i_thermalcond), & ! [IN]
815  land_property(:,:,i_heatcapacity), & ! [IN]
816  land_property(:,:,i_waterdiff), & ! [IN]
817  land_sflx_gh(:,:), & ! [IN]
818  land_sflx_water(:,:), & ! [IN]
819  land_sflx_engi(:,:), & ! [IN]
820  exists_land(:,:), lcdz(:), & ! [IN]
821  dt, nowdaysec, & ! [IN]
822  land_temp(:,:,:), & ! [INOUT]
823  land_water(:,:,:), land_ice(:,:,:), & ! [INOUT]
824  land_runoff(:,:), land_runoff_engi(:,:) ) ! [OUT]
825  case ( 'INIT' )
826  ! Never update LAND_TEMP and LAND_WATER from initial condition
827  end select
828 
829  !########## Negative Fixer ##########
830  !$omp parallel do schedule(dynamic)
831  !$acc kernels
832  do j = ljs, lje
833  do i = lis, lie
834  if ( exists_land(i,j) ) then
835  do k = lks, lke
836  land_water(k,i,j) = max( land_water(k,i,j), 0.0_rp )
837  land_ice(k,i,j) = max( land_ice(k,i,j), 0.0_rp )
838  enddo
839  end if
840  enddo
841  enddo
842  !$acc end kernels
843 
844  call land_vars_check
845 
846  call prof_rapend ('LND_Update', 1)
847 
848  return
849  end subroutine land_driver_update
850 
851  !-----------------------------------------------------------------------------
853  subroutine land_surface_get
854  use mod_land_admin, only: &
855  land_do
856  use mod_land_vars, only: &
857  atmos_temp, &
858  atmos_pres, &
859  atmos_w, &
860  atmos_u, &
861  atmos_v, &
862  atmos_dens, &
863  atmos_qv, &
864  atmos_pbl, &
865  atmos_sfc_dens, &
866  atmos_sfc_pres, &
868  atmos_cossza, &
871  use mod_cpl_vars, only: &
873  implicit none
874  !---------------------------------------------------------------------------
875 
876  call prof_rapstart('LND_SfcExch', 3)
877 
878  if ( land_do ) then
879  call cpl_getatm_lnd( atmos_temp(:,:), & ! [OUT]
880  atmos_pres(:,:), & ! [OUT]
881  atmos_w(:,:), & ! [OUT]
882  atmos_u(:,:), & ! [OUT]
883  atmos_v(:,:), & ! [OUT]
884  atmos_dens(:,:), & ! [OUT]
885  atmos_qv(:,:), & ! [OUT]
886  atmos_pbl(:,:), & ! [OUT]
887  atmos_sfc_dens(:,:), & ! [OUT]
888  atmos_sfc_pres(:,:), & ! [OUT]
889  atmos_sflx_rad_dn(:,:,:,:), & ! [OUT]
890  atmos_cossza(:,:), & ! [OUT]
891  atmos_sflx_water(:,:), & ! [OUT]
892  atmos_sflx_engi(:,:) ) ! [OUT]
893  endif
894 
895  call prof_rapend ('LND_SfcExch', 3)
896 
897  return
898  end subroutine land_surface_get
899 
900  !-----------------------------------------------------------------------------
902  subroutine land_surface_set( countup )
903  use mod_land_admin, only: &
904  land_do
905  use mod_land_vars, only: &
906  land_property, &
907  i_z0m, &
908  i_z0h, &
909  i_z0e, &
910  land_sfc_temp, &
911  land_sfc_albedo, &
912  land_sflx_mw, &
913  land_sflx_mu, &
914  land_sflx_mv, &
915  land_sflx_sh, &
916  land_sflx_lh, &
917  land_sflx_gh, &
918  land_sflx_qtrc, &
919  land_u10, &
920  land_v10, &
921  land_t2, &
922  land_q2
923  use mod_cpl_vars, only: &
924  cpl_putlnd
925  use scale_landuse, only: &
926  exists_land => landuse_exists_land
927  implicit none
928 
929  ! arguments
930  logical, intent(in) :: countup
931  !---------------------------------------------------------------------------
932 
933  call prof_rapstart('LND_SfcExch', 3)
934 
935  if ( land_do ) then
936  call cpl_putlnd( land_sfc_temp(:,:), & ! [IN]
937  land_sfc_albedo(:,:,:,:), & ! [IN]
938  land_property(:,:,i_z0m), & ! [IN]
939  land_property(:,:,i_z0h), & ! [IN]
940  land_property(:,:,i_z0e), & ! [IN]
941  land_sflx_mw(:,:), & ! [IN]
942  land_sflx_mu(:,:), & ! [IN]
943  land_sflx_mv(:,:), & ! [IN]
944  land_sflx_sh(:,:), & ! [IN]
945  land_sflx_lh(:,:), & ! [IN]
946  land_sflx_gh(:,:), & ! [IN]
947  land_sflx_qtrc(:,:,:), & ! [IN]
948  land_u10(:,:), & ! [IN]
949  land_v10(:,:), & ! [IN]
950  land_t2(:,:), & ! [IN]
951  land_q2(:,:), & ! [IN]
952  exists_land(:,:), & ! [IN]
953  countup ) ! [IN]
954  endif
955 
956  call prof_rapend ('LND_SfcExch', 3)
957 
958  return
959  end subroutine land_surface_set
960 
961 end module mod_land_driver
mod_land_vars::land_temp
real(rp), dimension(:,:,:), allocatable, public land_temp
temperature of each soil layer [K]
Definition: mod_land_vars.F90:62
scale_time::time_nowdaysec
real(dp), public time_nowdaysec
second of current time [sec]
Definition: scale_time.F90:72
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
scale_cpl_sfc_index::i_r_direct
integer, parameter, public i_r_direct
Definition: scale_cpl_sfc_index.F90:37
mod_land_vars::atmos_sfc_pres
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
Definition: mod_land_vars.F90:126
mod_land_vars::atmos_temp
real(rp), dimension(:,:), allocatable, public atmos_temp
Definition: mod_land_vars.F90:117
mod_land_vars::snow_sfc_temp
real(rp), dimension(:,:), allocatable, public snow_sfc_temp
snow surface temperature [K]
Definition: mod_land_vars.F90:69
scale_land_grid_cartesc_index::ljs
integer, public ljs
Definition: scale_land_grid_cartesC_index.F90:46
mod_land_vars::atmos_qv
real(rp), dimension(:,:), allocatable, public atmos_qv
Definition: mod_land_vars.F90:123
mod_land_driver
module LAND driver
Definition: mod_land_driver.F90:11
scale_tracer::qa
integer, public qa
Definition: scale_tracer.F90:35
mod_land_vars::i_stomataresist
integer, parameter, public i_stomataresist
Definition: mod_land_vars.F90:143
scale_land_grid_cartesc_index::lia
integer, public lia
Definition: scale_land_grid_cartesC_index.F90:41
mod_land_vars::land_sflx_mu
real(rp), dimension(:,:), allocatable, public land_sflx_mu
land surface u-momentum flux [kg/m2/s]
Definition: mod_land_vars.F90:87
scale_land_grid_cartesc_index::lja
integer, public lja
Definition: scale_land_grid_cartesC_index.F90:45
mod_land_vars::land_tstar
real(rp), dimension(:,:), allocatable, target, public land_tstar
temperature scale [K]
Definition: mod_land_vars.F90:97
scale_land_grid_cartesc::land_grid_cartesc_cdz
real(rp), dimension(:), allocatable, public land_grid_cartesc_cdz
z-length of control volume [m]
Definition: scale_land_grid_cartesC.F90:37
mod_land_vars::land_sfc_albedo
real(rp), dimension(:,:,:,:), allocatable, public land_sfc_albedo
land surface albedo (direct/diffuse,IR/near-IR/VIS) (0-1)
Definition: mod_land_vars.F90:66
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_z1
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_z1
Height of the lowermost grid from surface (cell center) [m].
Definition: scale_atmos_grid_cartesC_real.F90:60
scale_cpl_sfc_index::i_r_diffuse
integer, parameter, public i_r_diffuse
Definition: scale_cpl_sfc_index.F90:38
scale_topography::topography_tansl_y
real(rp), dimension(:,:), allocatable, public topography_tansl_y
tan(slope_y)
Definition: scale_topography.F90:41
mod_cpl_vars
module COUPLER Variables
Definition: mod_cpl_vars.F90:12
mod_land_vars::land_sflx_engi
real(rp), dimension(:,:), allocatable, public land_sflx_engi
land surface internal energy flux [J/m2/s]
Definition: mod_land_vars.F90:83
scale_precision
module PRECISION
Definition: scale_precision.F90:14
mod_atmos_admin
module ATMOS admin
Definition: mod_atmos_admin.F90:11
mod_land_vars::i_alblw
integer, parameter, public i_alblw
Definition: mod_land_vars.F90:147
mod_land_admin::land_sfc_type
character(len=h_short), public land_sfc_type
Definition: mod_land_admin.F90:36
mod_land_vars::i_albsw
integer, parameter, public i_albsw
Definition: mod_land_vars.F90:148
mod_land_vars::atmos_w
real(rp), dimension(:,:), allocatable, public atmos_w
Definition: mod_land_vars.F90:119
mod_land_vars::soil_ustar
real(rp), dimension(:,:), pointer, public soil_ustar
Definition: mod_land_vars.F90:101
mod_land_vars::land_water_t
real(rp), dimension(:,:,:), allocatable, public land_water_t
tendency of LAND_WATER
Definition: mod_land_vars.F90:77
scale_land_grid_cartesc_index::lkmax
integer, public lkmax
Definition: scale_land_grid_cartesC_index.F90:32
mod_land_vars::land_water
real(rp), dimension(:,:,:), allocatable, public land_water
moisture of each soil layer [m3/m3]
Definition: mod_land_vars.F90:63
mod_land_vars::land_runoff
real(rp), dimension(:,:), allocatable, public land_runoff
runoff of the land water [kg/m2/s]
Definition: mod_land_vars.F90:112
scale_cpl_sfc_index::i_r_ir
integer, parameter, public i_r_ir
Definition: scale_cpl_sfc_index.F90:29
mod_land_vars::atmos_u
real(rp), dimension(:,:), allocatable, public atmos_u
Definition: mod_land_vars.F90:120
scale_land_grid_cartesc_index::lje
integer, public lje
Definition: scale_land_grid_cartesC_index.F90:47
scale_prof::prof_rapstart
subroutine, public prof_rapstart(rapname_base, level, disable_barrier)
Start raptime.
Definition: scale_prof.F90:174
scale_bulkflux
module Surface bulk flux
Definition: scale_bulkflux.F90:12
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
mod_land_vars::land_sflx_mv
real(rp), dimension(:,:), allocatable, public land_sflx_mv
land surface v-momentum flux [kg/m2/s]
Definition: mod_land_vars.F90:88
mod_land_vars::i_waterdiff
integer, parameter, public i_waterdiff
Definition: mod_land_vars.F90:146
mod_land_vars::atmos_cossza
real(rp), dimension(:,:), allocatable, public atmos_cossza
Definition: mod_land_vars.F90:128
mod_land_vars::i_z0m
integer, parameter, public i_z0m
Definition: mod_land_vars.F90:149
mod_land_vars::atmos_sflx_rad_dn
real(rp), dimension(:,:,:,:), allocatable, public atmos_sflx_rad_dn
Definition: mod_land_vars.F90:127
mod_land_vars::land_ice_t
real(rp), dimension(:,:,:), allocatable, public land_ice_t
tendency of LAND_ICE
Definition: mod_land_vars.F90:78
scale_topography
module TOPOGRAPHY
Definition: scale_topography.F90:11
mod_land_vars::snow_wstar
real(rp), dimension(:,:), allocatable, public snow_wstar
Definition: mod_land_vars.F90:109
scale_landuse::landuse_exists_land
logical, dimension(:,:), allocatable, public landuse_exists_land
land calculation flag
Definition: scale_landuse.F90:51
scale_atmos_hydrometeor::atmos_hydrometeor_dry
logical, public atmos_hydrometeor_dry
Definition: scale_atmos_hydrometeor.F90:114
scale_cpl_phy_sfc_fixed_temp::cpl_phy_sfc_fixed_temp_setup
subroutine, public cpl_phy_sfc_fixed_temp_setup
Setup.
Definition: scale_cpl_phy_sfc_fixed_temp.F90:51
scale_land_phy_snow_ky90::land_phy_snow_ky90
subroutine, public land_phy_snow_ky90(LIA, LIS, LIE, LJA, LJS, LJE, SFLX_water, SFLX_ENGI, PRSA, TA, QA, WA, UA, VA, DENS, SFLX_RAD_dn, exists_land, dt, TSNOW, SWE, SDepth, SDzero, nosnowsec, Salbedo, SFLX_SH, SFLX_LH, SFLX_QV, SFLX_QV_ENGI, SFLX_GH, SNOW_LAND_GH, SNOW_LAND_Water, SNOW_frac)
Main routine for land submodel.
Definition: scale_land_phy_snow_ky90.F90:151
mod_land_vars::atmos_sflx_water
real(rp), dimension(:,:), allocatable, public atmos_sflx_water
Definition: mod_land_vars.F90:129
scale_atmos_grid_cartesc_real
module Atmosphere GRID CartesC Real(real space)
Definition: scale_atmos_grid_cartesC_real.F90:11
mod_land_vars::soil_rlmo
real(rp), dimension(:,:), pointer, public soil_rlmo
Definition: mod_land_vars.F90:105
scale_file_history
module file_history
Definition: scale_file_history.F90:15
mod_land_admin::snow_type
character(len=h_short), public snow_type
Definition: mod_land_admin.F90:38
mod_land_vars::land_rlmo
real(rp), dimension(:,:), allocatable, target, public land_rlmo
inversed Obukhov length [1/m]
Definition: mod_land_vars.F90:100
mod_land_vars::snow_tstar
real(rp), dimension(:,:), allocatable, public snow_tstar
Definition: mod_land_vars.F90:107
mod_land_vars::soil_tstar
real(rp), dimension(:,:), pointer, public soil_tstar
Definition: mod_land_vars.F90:102
scale_land_grid_cartesc_index
module land / grid / cartesianC / index
Definition: scale_land_grid_cartesC_index.F90:11
scale_const::const_i_sw
integer, public const_i_sw
short-wave radiation index
Definition: scale_const.F90:108
scale_land_phy_snow_ky90::land_phy_snow_ky90_setup
subroutine, public land_phy_snow_ky90_setup
Setup.
Definition: scale_land_phy_snow_ky90.F90:82
mod_land_admin::land_dyn_type
character(len=h_short), public land_dyn_type
Definition: mod_land_admin.F90:32
mod_land_vars::land_sflx_gh
real(rp), dimension(:,:), allocatable, public land_sflx_gh
land surface heat flux [J/m2/s]
Definition: mod_land_vars.F90:81
scale_prc
module PROCESS
Definition: scale_prc.F90:11
mod_land_vars::land_sflx_mw
real(rp), dimension(:,:), allocatable, public land_sflx_mw
land surface w-momentum flux [kg/m2/s]
Definition: mod_land_vars.F90:86
mod_land_vars::atmos_pres
real(rp), dimension(:,:), allocatable, public atmos_pres
Definition: mod_land_vars.F90:118
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
scale_io
module STDIO
Definition: scale_io.F90:10
scale_cpl_sfc_index::i_r_nir
integer, parameter, public i_r_nir
Definition: scale_cpl_sfc_index.F90:30
mod_land_vars::soil_wstar
real(rp), dimension(:,:), pointer, public soil_wstar
Definition: mod_land_vars.F90:104
scale_tracer::k
real(rp), public k
Definition: scale_tracer.F90:45
scale_const
module CONSTANT
Definition: scale_const.F90:11
mod_land_driver::land_surface_set
subroutine, public land_surface_set(countup)
Put surface boundary to other model.
Definition: mod_land_driver.F90:903
mod_land_vars::land_sflx_sh
real(rp), dimension(:,:), allocatable, public land_sflx_sh
land surface sensible heat flux [J/m2/s]
Definition: mod_land_vars.F90:89
mod_land_vars::land_wstar
real(rp), dimension(:,:), allocatable, target, public land_wstar
convective velocity scale [m/s]
Definition: mod_land_vars.F90:99
mod_land_vars::land_ustar
real(rp), dimension(:,:), allocatable, target, public land_ustar
friction velocity [m/s]
Definition: mod_land_vars.F90:96
mod_land_admin
module Land admin
Definition: mod_land_admin.F90:11
mod_land_vars::land_property
real(rp), dimension(:,:,:), allocatable, public land_property
land surface property
Definition: mod_land_vars.F90:136
mod_land_vars::land_temp_t
real(rp), dimension(:,:,:), allocatable, public land_temp_t
tendency of LAND_TEMP
Definition: mod_land_vars.F90:76
scale_land_grid_cartesc_index::lie
integer, public lie
Definition: scale_land_grid_cartesC_index.F90:43
mod_land_vars::snow_ustar
real(rp), dimension(:,:), allocatable, public snow_ustar
Definition: mod_land_vars.F90:106
mod_land_vars::land_qstar
real(rp), dimension(:,:), allocatable, target, public land_qstar
moisture scale [kg/kg]
Definition: mod_land_vars.F90:98
scale_topography::topography_tansl_x
real(rp), dimension(:,:), allocatable, public topography_tansl_x
tan(slope_x)
Definition: scale_topography.F90:40
scale_land_phy_snow_diagnos
module land / physics / snow / diagnostics
Definition: scale_land_phy_snow_diagnos.F90:11
mod_land_vars
module LAND Variables
Definition: mod_land_vars.F90:11
mod_land_vars::land_sflx_water
real(rp), dimension(:,:), allocatable, public land_sflx_water
land surface water flux [kg/m2/s]
Definition: mod_land_vars.F90:82
mod_land_driver::land_driver_setup
subroutine, public land_driver_setup
Setup.
Definition: mod_land_driver.F90:57
scale_prof
module profiler
Definition: scale_prof.F90:11
mod_land_vars::snow_nosnowsec
real(rp), dimension(:,:), allocatable, public snow_nosnowsec
sec while no snow [s]
Definition: mod_land_vars.F90:73
scale_land_phy_snow_diagnos::land_phy_snow_diags
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, Ustar, Tstar, Qstar, Wstar, RLmo, U10, V10, T2, Q2)
Definition: scale_land_phy_snow_diagnos.F90:59
scale_cpl_phy_sfc_skin::cpl_phy_sfc_skin
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, WSTR, QVEF, ALBEDO, Rb, TC_dZ, Z0M, Z0H, Z0E, calc_flag, dt_DP, model_name, TMPS, ZMFLX, XMFLX, YMFLX, SHFLX, LHFLX, QVFLX, GFLX, Ustar, Tstar, Qstar, Wstar, RLmo, U10, V10, T2, Q2)
Definition: scale_cpl_phy_sfc_skin.F90:133
mod_atmos_admin::atmos_sw_phy_ch
logical, public atmos_sw_phy_ch
Definition: mod_atmos_admin.F90:54
mod_land_vars::i_thermalcond
integer, parameter, public i_thermalcond
Definition: mod_land_vars.F90:144
scale_land_dyn_bucket::land_dyn_bucket
subroutine, public land_dyn_bucket(LKMAX, LKS, LKE, LIA, LIS, LIE, LJA, LJS, LJE, TEMP_t, WATER_t, ICE_t, WaterLimit, ThermalCond, HeatCapacity, WaterDiff, SFLX_GH, SFLX_water, SFLX_RHOE, exists_land, CDZ, dt, NOWDAYSEC, TEMP, WATER, ICE, RUNOFF, RUNOFF_ENGI)
Physical processes for land submodel.
Definition: scale_land_dyn_bucket.F90:200
scale_time
module TIME
Definition: scale_time.F90:11
mod_land_vars::land_runoff_engi
real(rp), dimension(:,:), allocatable, public land_runoff_engi
internal energy of the runoff [J/m2/s]
Definition: mod_land_vars.F90:113
scale_land_grid_cartesc_index::lis
integer, public lis
Definition: scale_land_grid_cartesC_index.F90:42
mod_land_driver::land_driver_update
subroutine, public land_driver_update
Land step.
Definition: mod_land_driver.F90:764
mod_land_vars::i_heatcapacity
integer, parameter, public i_heatcapacity
Definition: mod_land_vars.F90:145
mod_land_vars::soil_qstar
real(rp), dimension(:,:), pointer, public soil_qstar
Definition: mod_land_vars.F90:103
scale_cpl_phy_sfc_skin
module coupler / physics / surface skin
Definition: scale_cpl_phy_sfc_skin.F90:12
mod_land_vars::snow_swe
real(rp), dimension(:,:), allocatable, public snow_swe
snow water equivalent [kg/m2]
Definition: mod_land_vars.F90:70
scale_const::const_i_lw
integer, public const_i_lw
long-wave radiation index
Definition: scale_const.F90:107
mod_land_vars::i_waterlimit
integer, parameter, public i_waterlimit
Definition: mod_land_vars.F90:141
scale_land_grid_cartesc::land_grid_cartesc_cz
real(rp), dimension(:), allocatable, public land_grid_cartesc_cz
center coordinate [m]: z, local=global
Definition: scale_land_grid_cartesC.F90:35
scale_tracer
module TRACER
Definition: scale_tracer.F90:12
mod_land_vars::i_z0h
integer, parameter, public i_z0h
Definition: mod_land_vars.F90:150
mod_land_vars::land_q2
real(rp), dimension(:,:), allocatable, public land_q2
land surface water vapor at 2m [kg/kg]
Definition: mod_land_vars.F90:95
scale_atmos_hydrometeor::i_qv
integer, public i_qv
Definition: scale_atmos_hydrometeor.F90:93
mod_land_vars::i_z0e
integer, parameter, public i_z0e
Definition: mod_land_vars.F90:151
mod_land_vars::land_vars_check
subroutine, public land_vars_check(force)
Budget monitor for land.
Definition: mod_land_vars.F90:1089
mod_land_vars::atmos_dens
real(rp), dimension(:,:), allocatable, public atmos_dens
Definition: mod_land_vars.F90:122
mod_land_vars::land_sfc_temp
real(rp), dimension(:,:), allocatable, public land_sfc_temp
land surface skin temperature [K]
Definition: mod_land_vars.F90:65
mod_land_vars::snow_qstar
real(rp), dimension(:,:), allocatable, public snow_qstar
Definition: mod_land_vars.F90:108
mod_atmos_phy_ch_driver
module ATMOSPHERE / Physics Chemistry
Definition: mod_atmos_phy_ch_driver.F90:12
scale_const::const_tem00
real(rp), parameter, public const_tem00
temperature reference (0C) [K]
Definition: scale_const.F90:99
mod_land_driver::land_driver_calc_tendency
subroutine, public land_driver_calc_tendency(force)
Calculate tendency.
Definition: mod_land_driver.F90:150
scale_cpl_sfc_index
module coupler / surface-atmospehre
Definition: scale_cpl_sfc_index.F90:11
mod_land_driver::land_driver_finalize
subroutine, public land_driver_finalize
finalize
Definition: mod_land_driver.F90:120
mod_land_vars::snow_depth
real(rp), dimension(:,:), allocatable, public snow_depth
snow depth [m]
Definition: mod_land_vars.F90:71
mod_land_admin::land_do
logical, public land_do
Definition: mod_land_admin.F90:41
scale_time::time_dtsec_land
real(dp), public time_dtsec_land
time interval of land step [sec]
Definition: scale_time.F90:47
mod_land_vars::land_u10
real(rp), dimension(:,:), allocatable, public land_u10
land surface velocity u at 10m [m/s]
Definition: mod_land_vars.F90:92
scale_cpl_sfc_index::i_r_vis
integer, parameter, public i_r_vis
Definition: scale_cpl_sfc_index.F90:31
mod_land_vars::snow_flag
logical, public snow_flag
Definition: mod_land_vars.F90:133
mod_land_vars::atmos_sfc_dens
real(rp), dimension(:,:), allocatable, public atmos_sfc_dens
Definition: mod_land_vars.F90:125
scale_cpl_phy_sfc_fixed_temp::cpl_phy_sfc_fixed_temp
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, WSTR, QVEF, ALBEDO, Rb, Z0M, Z0H, Z0E, calc_flag, dt, ZMFLX, XMFLX, YMFLX, SHFLX, LHFLX, QVFLX, GFLX, Ustar, Tstar, Qstar, Wstar, RLmo, U10, V10, T2, Q2)
Definition: scale_cpl_phy_sfc_fixed_temp.F90:94
scale_land_dyn_bucket
module land / dynamics / bucket
Definition: scale_land_dyn_bucket.F90:11
scale_atmos_hydrometeor::lhf
real(rp), public lhf
latent heat of fusion for use [J/kg]
Definition: scale_atmos_hydrometeor.F90:146
mod_land_vars::land_sflx_lh
real(rp), dimension(:,:), allocatable, public land_sflx_lh
land surface latent heat flux [J/m2/s]
Definition: mod_land_vars.F90:90
scale_land_dyn_bucket::land_dyn_bucket_setup
subroutine, public land_dyn_bucket_setup
Setup.
Definition: scale_land_dyn_bucket.F90:71
mod_land_vars::land_v10
real(rp), dimension(:,:), allocatable, public land_v10
land surface velocity v at 10m [m/s]
Definition: mod_land_vars.F90:93
scale_cpl_phy_sfc_skin::cpl_phy_sfc_skin_setup
subroutine, public cpl_phy_sfc_skin_setup
Setup.
Definition: scale_cpl_phy_sfc_skin.F90:59
scale_prof::prof_rapend
subroutine, public prof_rapend(rapname_base, level, disable_barrier)
Save raptime.
Definition: scale_prof.F90:246
scale_land_grid_cartesc
module land / grid / cartesianC
Definition: scale_land_grid_cartesC.F90:11
mod_land_driver::land_surface_get
subroutine, public land_surface_get
Get surface boundary from other model.
Definition: mod_land_driver.F90:854
scale_land_grid_cartesc_index::lke
integer, public lke
Definition: scale_land_grid_cartesC_index.F90:39
mod_atmos_phy_ch_driver::atmos_phy_ch_driver_land_flux
subroutine, public atmos_phy_ch_driver_land_flux(SFLX_QTRC)
Driver.
Definition: mod_atmos_phy_ch_driver.F90:293
scale_landuse
module LANDUSE
Definition: scale_landuse.F90:19
mod_land_vars::land_ice
real(rp), dimension(:,:,:), allocatable, public land_ice
ice of each soil layer [m3/m3]
Definition: mod_land_vars.F90:64
mod_land_vars::land_t2
real(rp), dimension(:,:), allocatable, public land_t2
land surface temperature at 2m [K]
Definition: mod_land_vars.F90:94
mod_land_vars::atmos_sflx_engi
real(rp), dimension(:,:), allocatable, public atmos_sflx_engi
Definition: mod_land_vars.F90:130
mod_cpl_vars::cpl_putlnd
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_QTRC, U10, V10, T2, Q2, mask, countup)
Definition: mod_cpl_vars.F90:907
mod_land_vars::snow_rlmo
real(rp), dimension(:,:), allocatable, public snow_rlmo
Definition: mod_land_vars.F90:110
mod_land_vars::atmos_pbl
real(rp), dimension(:,:), allocatable, public atmos_pbl
Definition: mod_land_vars.F90:124
mod_land_vars::i_watercritical
integer, parameter, public i_watercritical
Definition: mod_land_vars.F90:142
scale_land_grid_cartesc_index::lks
integer, public lks
Definition: scale_land_grid_cartesC_index.F90:38
mod_cpl_vars::cpl_getatm_lnd
subroutine, public cpl_getatm_lnd(TEMP, PRES, W, U, V, DENS, QV, PBL, SFC_DENS, SFC_PRES, SFLX_rad_dn, cosSZA, SFLX_water, SFLX_ENGI)
Definition: mod_cpl_vars.F90:1379
scale_land_phy_snow_ky90
module land / physics / snow / ky90
Definition: scale_land_phy_snow_ky90.F90:12
scale_atmos_hydrometeor::cv_water
real(rp), public cv_water
CV for water [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:151
mod_land_vars::snow_dzero
real(rp), dimension(:,:), allocatable, public snow_dzero
snow depth at melting point [m]
Definition: mod_land_vars.F90:72
mod_land_vars::atmos_v
real(rp), dimension(:,:), allocatable, public atmos_v
Definition: mod_land_vars.F90:121
mod_land_vars::land_sflx_qtrc
real(rp), dimension(:,:,:), allocatable, public land_sflx_qtrc
land surface tracer flux [kg/m2/s]
Definition: mod_land_vars.F90:91
scale_atmos_hydrometeor::cv_ice
real(rp), public cv_ice
CV for ice [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:153
scale_cpl_phy_sfc_fixed_temp
module coupler / surface fixed temp model
Definition: scale_cpl_phy_sfc_fixed_temp.F90:12