SCALE-RM
mod_atmos_driver.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
16 !-------------------------------------------------------------------------------
18  !-----------------------------------------------------------------------------
19  !
20  !++ used modules
21  !
22  use scale_precision
23  use scale_stdio
24  use scale_prof
26  !-----------------------------------------------------------------------------
27  implicit none
28  private
29  !-----------------------------------------------------------------------------
30  !
31  !++ Public procedure
32  !
33  public :: atmos_driver_setup
34  public :: atmos_driver_resume1
35  public :: atmos_driver_resume2
36  public :: atmos_driver
37  public :: atmos_driver_finalize
38  public :: atmos_surface_get
39  public :: atmos_surface_set
40 
41  !-----------------------------------------------------------------------------
42  !
43  !++ Public parameters & variables
44  !
45  !-----------------------------------------------------------------------------
46  !
47  !++ Private procedure
48  !
49  !-----------------------------------------------------------------------------
50  !
51  !++ Private parameters & variables
52  !
53  !-----------------------------------------------------------------------------
54 contains
55  !-----------------------------------------------------------------------------
57  subroutine atmos_driver_setup
58  use scale_time, only: &
60  use scale_atmos_solarins, only: &
62  use scale_atmos_refstate, only: &
64  use scale_atmos_boundary, only: &
66  use mod_atmos_dyn_driver, only: &
68  use mod_atmos_phy_mp_driver, only: &
70  use mod_atmos_phy_rd_driver, only: &
72  use mod_atmos_phy_ch_driver, only: &
74  use mod_atmos_phy_ae_driver, only: &
76  use mod_atmos_phy_cp_driver, only: &
78  use mod_atmos_phy_sf_driver, only: &
80  use mod_atmos_phy_tb_driver, only: &
82  implicit none
83  !---------------------------------------------------------------------------
84 
85  if( io_l ) write(io_fid_log,*)
86  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[ATMOS] / Origin[SCALE-RM]'
87 
88  if( io_l ) write(io_fid_log,*)
89  if( io_l ) write(io_fid_log,*) '*** Setup each atmospheric components ...'
90 
91  !--- setup solar insolation
93 
94  call prof_rapstart('ATM_Refstate', 2)
96  call prof_rapend ('ATM_Refstate', 2)
97 
98  call prof_rapstart('ATM_Boundary', 2)
100  call prof_rapend ('ATM_Boundary', 2)
101 
102  ! setup each components
111 
112  if( io_l ) write(io_fid_log,*)
113  if( io_l ) write(io_fid_log,*) '*** Finish setup of each atmospheric components.'
114 
115  return
116  end subroutine atmos_driver_setup
117 
118  !-----------------------------------------------------------------------------
120  subroutine atmos_driver_resume1
121  use mod_atmos_vars, only: &
123  dens, &
124  momz, &
125  momx, &
126  momy, &
127  rhot, &
128  qtrc, &
129  dens_tp, &
130  momz_tp, &
131  momx_tp, &
132  momy_tp, &
133  rhot_tp, &
134  rhoq_tp
135  use scale_atmos_refstate, only: &
137  use scale_atmos_boundary, only: &
139  use mod_atmos_phy_mp_driver, only: &
141  use mod_atmos_phy_rd_driver, only: &
143  use mod_atmos_phy_ch_driver, only: &
145  use mod_atmos_phy_ae_driver, only: &
147  implicit none
148  !---------------------------------------------------------------------------
149 
150  if( io_l ) write(io_fid_log,*)
151  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[ATMOS] / Origin[SCALE-RM]'
152 
153  if( io_l ) write(io_fid_log,*)
154  if( io_l ) write(io_fid_log,*) '*** Resume each atmospheric components 1 ...'
155 
156  call prof_rapstart('ATM_Refstate', 2)
158  call prof_rapend ('ATM_Refstate', 2)
159 
160  call prof_rapstart('ATM_Boundary', 2)
162  call prof_rapend ('ATM_Boundary', 2)
163 
164  !########## Get Surface Boundary Condition ##########
165  call prof_rapstart('ATM_SfcExch', 2)
166  call atmos_surface_get
167  call prof_rapend ('ATM_SfcExch', 2)
168 
169  !########## initialize tendencies ##########
170 !OCL XFILL
171  dens_tp(:,:,:) = 0.0_rp
172 !OCL XFILL
173  momz_tp(:,:,:) = 0.0_rp
174 !OCL XFILL
175  momx_tp(:,:,:) = 0.0_rp
176 !OCL XFILL
177  momy_tp(:,:,:) = 0.0_rp
178 !OCL XFILL
179  rhot_tp(:,:,:) = 0.0_rp
180 !OCL XFILL
181  rhoq_tp(:,:,:,:) = 0.0_rp
182 
183  ! setup each components
188 
189  !########## Calculate diagnostic variables ##########
191 
192  !########## Set Surface Boundary Condition ##########
193  call prof_rapstart('ATM_SfcExch', 2)
194  call atmos_surface_set( countup = .false. )
195  call prof_rapend ('ATM_SfcExch', 2)
196 
197  if( io_l ) write(io_fid_log,*)
198  if( io_l ) write(io_fid_log,*) '*** Finish resume of each atmospheric components 1.'
199 
200  return
201  end subroutine atmos_driver_resume1
202 
203  !-----------------------------------------------------------------------------
205  subroutine atmos_driver_resume2
206  use mod_atmos_vars, only: &
209  use mod_atmos_phy_cp_driver, only: &
211  use mod_atmos_phy_sf_driver, only: &
213  use mod_atmos_phy_tb_driver, only: &
215  implicit none
216  !---------------------------------------------------------------------------
217 
218  if( io_l ) write(io_fid_log,*)
219  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[ATMOS] / Origin[SCALE-RM]'
220 
221  if( io_l ) write(io_fid_log,*)
222  if( io_l ) write(io_fid_log,*) '*** Resume each atmospheric components 2 ...'
223 
224  !########## Get Surface Boundary Condition ##########
225  call prof_rapstart('ATM_SfcExch', 2)
226  call atmos_surface_get
227  call prof_rapend ('ATM_SfcExch', 2)
228 
229  ! setup each components
233 
234  !########## Set Surface Boundary Condition ##########
235  call prof_rapstart('ATM_SfcExch', 2)
236  call atmos_surface_set( countup = .true. )
237  call prof_rapend ('ATM_SfcExch', 2)
238 
239  !########## History & Monitor ##########
240  call prof_rapstart('ATM_History', 1)
241  call atmos_vars_history
242  call atmos_vars_monitor
243  call prof_rapend ('ATM_History', 1)
244 
245  if( io_l ) write(io_fid_log,*)
246  if( io_l ) write(io_fid_log,*) '*** Finish resume of each atmospheric components 2.'
247 
248  return
249  end subroutine atmos_driver_resume2
250 
251  !-----------------------------------------------------------------------------
253  subroutine atmos_driver
254  use mod_admin_time, only: &
255  do_dyn => time_doatmos_dyn, &
256  do_phy_mp => time_doatmos_phy_mp, &
257  do_phy_ae => time_doatmos_phy_ae, &
258  do_phy_ch => time_doatmos_phy_ch, &
259  do_phy_rd => time_doatmos_phy_rd, &
260  do_phy_sf => time_doatmos_phy_sf, &
261  do_phy_tb => time_doatmos_phy_tb, &
262  do_phy_cp => time_doatmos_phy_cp
263  use scale_atmos_refstate, only: &
266  use scale_atmos_boundary, only: &
269  use mod_atmos_admin, only: &
270  atmos_sw_dyn, &
271  atmos_sw_phy_mp, &
272  atmos_sw_phy_ae, &
273  atmos_sw_phy_ch, &
274  atmos_sw_phy_rd, &
275  atmos_sw_phy_sf, &
276  atmos_sw_phy_tb, &
278  use mod_atmos_vars, only: &
282  dens, &
283  momz, &
284  momx, &
285  momy, &
286  rhot, &
287  qtrc, &
288  dens_tp, &
289  momz_tp, &
290  momx_tp, &
291  momy_tp, &
292  rhot_tp, &
293  rhoq_tp
294  use mod_atmos_dyn_driver, only: &
296  use mod_atmos_phy_mp_driver, only: &
298  use mod_atmos_phy_ae_driver, only: &
300  use mod_atmos_phy_ch_driver, only: &
302  use mod_atmos_phy_rd_driver, only: &
304  use mod_atmos_phy_sf_driver, only: &
306  use mod_atmos_phy_tb_driver, only: &
308  use mod_atmos_phy_cp_driver, only: &
310  implicit none
311  !---------------------------------------------------------------------------
312 
313  !########## Get Surface Boundary Condition ##########
314  call prof_rapstart('ATM_SfcExch', 2)
315  call atmos_surface_get
316  call prof_rapend ('ATM_SfcExch', 2)
317 
318  !########## Dynamics ##########
319  if ( atmos_sw_dyn ) then
320  call prof_rapstart('ATM_Dynamics', 1)
321  call atmos_dyn_driver( do_dyn )
322  call prof_rapend ('ATM_Dynamics', 1)
323  endif
324 
325  !########## Reference State ###########
326  if ( atmos_refstate_update_flag ) then
327  call prof_rapstart('ATM_Refstate', 2)
328  call atmos_refstate_update( dens, rhot, qtrc ) ! [IN]
329  call prof_rapend ('ATM_Refstate', 2)
330  endif
331 
332  !########## Lateral/Top Boundary Condition ###########
333  if ( atmos_boundary_update_flag ) then
334  call prof_rapstart('ATM_Boundary', 2)
335  call atmos_boundary_update( dens, momz, momx, momy, rhot, qtrc ) ! [INOUT]
336  call prof_rapend ('ATM_Boundary', 2)
337  endif
338 
339  !########## reset tendencies ##########
340 !OCL XFILL
341  dens_tp(:,:,:) = 0.0_rp
342 !OCL XFILL
343  momz_tp(:,:,:) = 0.0_rp
344 !OCL XFILL
345  momx_tp(:,:,:) = 0.0_rp
346 !OCL XFILL
347  momy_tp(:,:,:) = 0.0_rp
348 !OCL XFILL
349  rhot_tp(:,:,:) = 0.0_rp
350 !OCL XFILL
351  rhoq_tp(:,:,:,:) = 0.0_rp
352 
353  !########## Calculate diagnostic variables ##########
354  call prof_rapstart('ATM_History', 1)
356  call prof_rapend ('ATM_History', 1)
357 
358  !########## Microphysics ##########
359  if ( atmos_sw_phy_mp ) then
360  call prof_rapstart('ATM_Microphysics', 1)
361  call atmos_phy_mp_driver( update_flag = do_phy_mp )
362  call prof_rapend ('ATM_Microphysics', 1)
363  endif
364 
365  !########## Aerosol ##########
366  if ( atmos_sw_phy_ae ) then
367  call prof_rapstart('ATM_Aerosol', 1)
368  call atmos_phy_ae_driver( update_flag = do_phy_ae )
369  call prof_rapend ('ATM_Aerosol', 1)
370  endif
371 
372  !########## Chemistry ##########
373  if ( atmos_sw_phy_ch ) then
374  call prof_rapstart('ATM_Chemistry', 1)
375  call atmos_phy_ch_driver( update_flag = do_phy_ch )
376  call prof_rapend ('ATM_Chemistry', 1)
377  endif
378 
379  !########## Radiation ##########
380  if ( atmos_sw_phy_rd ) then
381  call prof_rapstart('ATM_Radiation', 1)
382  call atmos_phy_rd_driver( update_flag = do_phy_rd )
383  call prof_rapend ('ATM_Radiation', 1)
384  endif
385 
386  !########## Surface Flux ##########
387  if ( atmos_sw_phy_sf ) then
388  call prof_rapstart('ATM_SurfaceFlux', 1)
389  call atmos_phy_sf_driver( update_flag = do_phy_sf )
390  call prof_rapend ('ATM_SurfaceFlux', 1)
391  endif
392 
393  !########## Turbulence ##########
394  if ( atmos_sw_phy_tb ) then
395  call prof_rapstart('ATM_Turbulence', 1)
396  call atmos_phy_tb_driver( update_flag = do_phy_tb )
397  call prof_rapend ('ATM_Turbulence', 1)
398  endif
399 
400  !########## Cumulus ##########
401  if ( atmos_sw_phy_cp ) then
402  call prof_rapstart('ATM_Cumulus', 1)
403  call atmos_phy_cp_driver( update_flag = do_phy_cp )
404  call prof_rapend ('ATM_Cumulus', 1)
405  endif
406 
407  !########## Set Surface Boundary Condition ##########
408  call prof_rapstart('ATM_SfcExch', 2)
409  call atmos_surface_set( countup = .true. )
410  call prof_rapend ('ATM_SfcExch', 2)
411 
412  !########## History & Monitor ##########
413  call prof_rapstart('ATM_History', 1)
414  call atmos_vars_history
415  call atmos_vars_monitor
416  call prof_rapend ('ATM_History', 1)
417 
418  return
419  end subroutine atmos_driver
420 
421  !-----------------------------------------------------------------------------
423  subroutine atmos_driver_finalize
424  use scale_atmos_boundary, only: &
427  use scale_grid_nest, only: &
429  implicit none
430  !---------------------------------------------------------------------------
431 
432  !########## Lateral/Top Boundary Condition ###########
433  if ( atmos_boundary_update_flag ) then
434  ! If this run is parent of online nesting, boundary data must be sent
436 
437  ! Finialize Inter-Communicators
439  endif
440 
441  return
442  end subroutine atmos_driver_finalize
443 
444  !-----------------------------------------------------------------------------
446  subroutine atmos_surface_get
448  sfc_temp => atmos_phy_sf_sfc_temp, &
449  sfc_albedo => atmos_phy_sf_sfc_albedo, &
450  sfc_z0m => atmos_phy_sf_sfc_z0m, &
451  sfc_z0h => atmos_phy_sf_sfc_z0h, &
452  sfc_z0e => atmos_phy_sf_sfc_z0e, &
453  sflx_mw => atmos_phy_sf_sflx_mw, &
454  sflx_mu => atmos_phy_sf_sflx_mu, &
455  sflx_mv => atmos_phy_sf_sflx_mv, &
456  sflx_sh => atmos_phy_sf_sflx_sh, &
457  sflx_lh => atmos_phy_sf_sflx_lh, &
458  sflx_gh => atmos_phy_sf_sflx_gh, &
459  sflx_qtrc => atmos_phy_sf_sflx_qtrc, &
460  u10 => atmos_phy_sf_u10, &
461  v10 => atmos_phy_sf_v10, &
462  t2 => atmos_phy_sf_t2, &
463  q2 => atmos_phy_sf_q2
464  use mod_cpl_admin, only: &
465  cpl_sw
466  use mod_cpl_vars, only: &
468  implicit none
469  !---------------------------------------------------------------------------
470 
471  if ( cpl_sw ) then
472  call cpl_getsfc_atm( sfc_temp(:,:), & ! [OUT]
473  sfc_albedo(:,:,:), & ! [OUT]
474  sfc_z0m(:,:), & ! [OUT]
475  sfc_z0h(:,:), & ! [OUT]
476  sfc_z0e(:,:), & ! [OUT]
477  sflx_mw(:,:), & ! [OUT]
478  sflx_mu(:,:), & ! [OUT]
479  sflx_mv(:,:), & ! [OUT]
480  sflx_sh(:,:), & ! [OUT]
481  sflx_lh(:,:), & ! [OUT]
482  sflx_gh(:,:), & ! [OUT]
483  sflx_qtrc(:,:,:), & ! [OUT]
484  u10(:,:), & ! [OUT]
485  v10(:,:), & ! [OUT]
486  t2(:,:), & ! [OUT]
487  q2(:,:) ) ! [OUT]
488  endif
489 
490  return
491  end subroutine atmos_surface_get
492 
493  !-----------------------------------------------------------------------------
495  subroutine atmos_surface_set( countup )
496  use scale_grid_real, only: &
497  real_cz, &
498  real_z1
499  use scale_topography, only: &
500  topo_zsfc
501  use scale_atmos_bottom, only: &
502  bottom_estimate => atmos_bottom_estimate
503  use mod_atmos_vars, only: &
504  dens, &
505  qtrc, &
506  temp, &
507  pres, &
508  w, &
509  u, &
510  v
511  use mod_atmos_phy_mp_vars, only: &
512  sflx_rain => atmos_phy_mp_sflx_rain, &
513  sflx_snow => atmos_phy_mp_sflx_snow
514  use mod_atmos_phy_rd_vars, only: &
515  sflx_rad_dn => atmos_phy_rd_sflx_downall, &
516  cossza => atmos_phy_rd_cossza
517  use mod_cpl_admin, only: &
518  cpl_sw
519  use mod_cpl_vars, only: &
520  cpl_putatm
521  implicit none
522 
523  ! arguments
524  logical, intent(in) :: countup
525 
526  ! works
527  real(RP) :: SFC_DENS(ia,ja)
528  real(RP) :: SFC_PRES(ia,ja)
529  real(RP) :: ATM_PBL (ia,ja)
530  !---------------------------------------------------------------------------
531 
532  if ( cpl_sw ) then
533  ! planetary boundary layer
534  atm_pbl(:,:) = 100.0_rp ! tentative
535 
536  call bottom_estimate( dens(:,:,:), & ! [IN]
537  pres(:,:,:), & ! [IN]
538  real_cz(:,:,:), & ! [IN]
539  topo_zsfc(:,:), & ! [IN]
540  real_z1(:,:), & ! [IN]
541  sfc_dens(:,:), & ! [OUT]
542  sfc_pres(:,:) ) ! [OUT]
543 
544  call cpl_putatm( temp(ks,:,:), & ! [IN]
545  pres(ks,:,:), & ! [IN]
546  w(ks,:,:), & ! [IN]
547  u(ks,:,:), & ! [IN]
548  v(ks,:,:), & ! [IN]
549  dens(ks,:,:), & ! [IN]
550  qtrc(ks,:,:,:), & ! [IN]
551  atm_pbl(:,:), & ! [IN]
552  sfc_pres(:,:), & ! [IN]
553  sflx_rad_dn(:,:,:,:), & ! [IN]
554  cossza(:,:), & ! [IN]
555  sflx_rain(:,:), & ! [IN]
556  sflx_snow(:,:), & ! [IN]
557  countup ) ! [IN]
558  endif
559 
560  return
561  end subroutine atmos_surface_set
562 
563 end module mod_atmos_driver
module ATMOS admin
real(rp), dimension(:,:,:), allocatable, public dens_tp
logical, public atmos_sw_phy_cp
subroutine, public atmos_phy_cp_driver_resume
Redume.
real(rp), dimension(:,:,:), allocatable, target, public momz
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sfc_z0e
subroutine, public atmos_surface_set(countup)
Set surface boundary condition.
real(rp), dimension(:,:,:), allocatable, public atmos_phy_sf_sflx_qtrc
logical, public time_doatmos_phy_rd
execute physics in this step? (radiation )
subroutine, public atmos_phy_ae_driver_setup
Setup.
subroutine, public atmos_phy_ae_driver(update_flag)
Driver.
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_mw
module GRID (nesting system)
logical, public atmos_sw_phy_rd
real(rp), dimension(:,:,:), allocatable, target, public rhot
real(rp), dimension(:,:,:), allocatable, public momy_tp
module ATMOSPHERE / Physics Turbulence
subroutine, public atmos_boundary_resume(DENS, MOMZ, MOMX, MOMY, RHOT, QTRC)
Resume.
subroutine, public atmos_phy_ch_driver_resume
Resume.
subroutine, public cpl_putatm(TEMP, PRES, W, U, V, DENS, QTRC, PBL, SFC_PRES, SFLX_rad_dn, cosSZA, SFLX_rain, SFLX_snow, countup)
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_v10
module Atmosphere / Physics Cloud Microphysics
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
module ATMOSPHERE / Physics Cumulus
module ATMOSPHERE / Bottom boundary treatment
real(rp), dimension(:,:,:), allocatable, public pres
module ATMOSPHERE / Physics Radiation
module ATMOSPHERE / Reference state
subroutine, public atmos_phy_sf_driver_resume
Resume.
module ATMOSPHERIC Variables
subroutine, public atmos_phy_ch_driver(update_flag)
Driver.
module ATMOSPHERE / Physics Surface fluxes
real(rp), dimension(:,:,:), allocatable, target, public momx
subroutine, public atmos_phy_mp_driver(update_flag)
Driver.
module STDIO
Definition: scale_stdio.F90:12
subroutine, public atmos_boundary_update(DENS, MOMZ, MOMX, MOMY, RHOT, QTRC)
Update boundary value with a constant time boundary.
real(rp), dimension(:,:,:), allocatable, public rhot_tp
module ATMOSPHERE / Physics Chemistry
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sfc_temp
subroutine, public atmos_boundary_setup
Setup.
real(rp), dimension(:,:,:), allocatable, public real_cz
geopotential height [m] (cell center)
logical, public atmos_sw_phy_ae
module Atmosphere / Dynamics
real(rp), dimension(:,:,:), allocatable, target, public dens
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_mv
module ATMOSPHERE / Physics Aerosol Microphysics
logical, public time_doatmos_phy_mp
execute physics in this step? (microphysics)
real(rp), dimension(:,:), allocatable, public atmos_phy_mp_sflx_rain
subroutine, public atmos_phy_rd_driver_setup
Setup.
subroutine, public cpl_getsfc_atm(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)
subroutine, public atmos_dyn_driver(do_flag)
Dynamical Process (Wrapper)
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_cossza
module Atmosphere / Physics Radiation
module grid index
module ATMOSPHERIC Surface Variables
subroutine, public atmos_dyn_driver_setup
Setup.
subroutine, public atmos_boundary_finalize
Finalize boundary value.
logical, public atmos_sw_phy_tb
subroutine, public atmos_surface_get
Get surface boundary condition.
integer, public ia
of x whole cells (local, with HALO)
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_u10
real(rp), dimension(:,:,:), allocatable, public temp
logical, public atmos_refstate_update_flag
real(rp), dimension(:,:), allocatable, public real_z1
Height of the lowermost grid from surface (cell center) [m].
module GRID (real space)
subroutine, public atmos_phy_cp_driver_setup
Setup.
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sfc_z0h
subroutine, public atmos_solarins_setup(iyear)
setup solar incidence module
subroutine, public atmos_refstate_update(DENS, RHOT, QTRC)
Update reference state profile (Horizontal average)
subroutine, public atmos_refstate_setup
Setup.
module COUPLER Variables
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
real(rp), dimension(:,:,:), allocatable, public atmos_phy_sf_sfc_albedo
logical, public atmos_sw_dyn
module ATMOSPHERE driver
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_lh
subroutine, public atmos_phy_sf_driver_setup
Setup.
subroutine, public atmos_driver_resume1
Resume.
module TIME
Definition: scale_time.F90:15
logical, public atmos_sw_phy_sf
logical, public time_doatmos_phy_ch
execute physics in this step? (chemistry )
logical, public atmos_sw_phy_ch
subroutine, public atmos_driver_setup
Setup.
subroutine, public atmos_phy_mp_driver_setup
Setup.
logical, public time_doatmos_phy_cp
execute physics in this step? (cumulus )
logical, public cpl_sw
subroutine, public atmos_phy_cp_driver(update_flag)
Driver.
subroutine, public atmos_phy_ae_driver_resume
Resume.
logical, public atmos_sw_phy_mp
subroutine, public atmos_bottom_estimate(DENS, PRES, CZ, Zsfc, Z1, SFC_DENS, SFC_PRES)
Calc bottom boundary of atmosphere (just above surface)
integer, public ks
start point of inner domain: z, local
subroutine, public atmos_phy_tb_driver_setup
Setup.
logical, public atmos_boundary_update_flag
real(rp), dimension(:,:,:), allocatable, public momx_tp
real(rp), dimension(:,:,:), allocatable, target, public momy
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:132
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_rd_sflx_downall
subroutine, public atmos_vars_monitor
monitor output
real(rp), dimension(:,:), allocatable, public atmos_phy_mp_sflx_snow
real(rp), dimension(:,:,:), allocatable, public momz_tp
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_sh
subroutine, public atmos_phy_rd_driver(update_flag)
Driver.
real(rp), dimension(:,:,:), allocatable, public v
module profiler
Definition: scale_prof.F90:10
logical, public time_doatmos_phy_ae
execute physics in this step? (aerosol )
real(rp), dimension(:,:,:), allocatable, public w
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_q2
subroutine, public atmos_phy_ch_driver_setup
Setup.
subroutine, public atmos_driver_finalize
Finalize.
module PRECISION
logical, public time_doatmos_phy_tb
execute physics in this step? (turbulence )
real(rp), dimension(:,:), allocatable, public topo_zsfc
absolute ground height [m]
subroutine, public atmos_phy_rd_driver_resume
Resume.
real(rp), dimension(:,:,:), allocatable, public u
module ATMOSPHERE / Boundary treatment
module TOPOGRAPHY
module ADMIN TIME
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sfc_z0m
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_t2
integer, dimension(6), public time_nowdate
current time [YYYY MM DD HH MM SS]
Definition: scale_time.F90:65
subroutine, public atmos_driver
advance atmospheric state
subroutine, public atmos_refstate_resume(DENS, RHOT, QTRC)
Resume.
subroutine, public atmos_phy_tb_driver(update_flag)
Driver.
logical, public time_doatmos_dyn
execute dynamics in this step?
subroutine, public atmos_vars_history
History output set for atmospheric variables.
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
logical, public time_doatmos_phy_sf
execute physics in this step? (surface flux)
module Coupler admin
subroutine, public atmos_phy_mp_driver_resume
resume
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_gh
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_mu
module ATMOSPHERE / Physics Cloud Microphysics
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:178
subroutine, public atmos_driver_resume2
Setup.
subroutine, public atmos_phy_tb_driver_resume
Resume.
subroutine, public nest_comm_disconnect()
[finalize: disconnect] Inter-communication
subroutine, public atmos_vars_diagnostics
Calc diagnostic variables.
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
subroutine, public atmos_phy_sf_driver(update_flag)
Driver.
integer, public ja
of y whole cells (local, with HALO)