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: &
208  use mod_atmos_phy_cp_driver, only: &
210  use mod_atmos_phy_sf_driver, only: &
212  use mod_atmos_phy_tb_driver, only: &
214  implicit none
215  !---------------------------------------------------------------------------
216 
217  if( io_l ) write(io_fid_log,*)
218  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[ATMOS] / Origin[SCALE-RM]'
219 
220  if( io_l ) write(io_fid_log,*)
221  if( io_l ) write(io_fid_log,*) '*** Resume each atmospheric components 2 ...'
222 
223  !########## Get Surface Boundary Condition ##########
224  call prof_rapstart('ATM_SfcExch', 2)
225  call atmos_surface_get
226  call prof_rapend ('ATM_SfcExch', 2)
227 
228  ! setup each components
232 
233  !########## Set Surface Boundary Condition ##########
234  call prof_rapstart('ATM_SfcExch', 2)
235  call atmos_surface_set( countup = .true. )
236  call prof_rapend ('ATM_SfcExch', 2)
237 
238  !########## History & Monitor ##########
239  call prof_rapstart('ATM_History', 1)
240  call atmos_vars_history
241  call prof_rapend ('ATM_History', 1)
242 
243  if( io_l ) write(io_fid_log,*)
244  if( io_l ) write(io_fid_log,*) '*** Finish resume of each atmospheric components 2.'
245 
246  return
247  end subroutine atmos_driver_resume2
248 
249  !-----------------------------------------------------------------------------
251  subroutine atmos_driver
252  use mod_admin_time, only: &
253  do_dyn => time_doatmos_dyn, &
254  do_phy_mp => time_doatmos_phy_mp, &
255  do_phy_ae => time_doatmos_phy_ae, &
256  do_phy_ch => time_doatmos_phy_ch, &
257  do_phy_rd => time_doatmos_phy_rd, &
258  do_phy_sf => time_doatmos_phy_sf, &
259  do_phy_tb => time_doatmos_phy_tb, &
260  do_phy_cp => time_doatmos_phy_cp
261  use scale_atmos_refstate, only: &
264  use scale_atmos_boundary, only: &
267  use mod_atmos_admin, only: &
268  atmos_sw_dyn, &
269  atmos_sw_phy_mp, &
270  atmos_sw_phy_ae, &
271  atmos_sw_phy_ch, &
272  atmos_sw_phy_rd, &
273  atmos_sw_phy_sf, &
274  atmos_sw_phy_tb, &
276  use mod_atmos_vars, only: &
280  dens, &
281  momz, &
282  momx, &
283  momy, &
284  rhot, &
285  qtrc, &
286  dens_tp, &
287  momz_tp, &
288  momx_tp, &
289  momy_tp, &
290  rhot_tp, &
291  rhoq_tp
292  use mod_atmos_dyn_driver, only: &
294  use mod_atmos_phy_mp_driver, only: &
296  use mod_atmos_phy_ae_driver, only: &
298  use mod_atmos_phy_ch_driver, only: &
300  use mod_atmos_phy_rd_driver, only: &
302  use mod_atmos_phy_sf_driver, only: &
304  use mod_atmos_phy_tb_driver, only: &
306  use mod_atmos_phy_cp_driver, only: &
308  implicit none
309  !---------------------------------------------------------------------------
310 
311  !########## Get Surface Boundary Condition ##########
312  call prof_rapstart('ATM_SfcExch', 2)
313  call atmos_surface_get
314  call prof_rapend ('ATM_SfcExch', 2)
315 
316  !########## Dynamics ##########
317  if ( atmos_sw_dyn ) then
318  call prof_rapstart('ATM_Dynamics', 1)
319  call atmos_dyn_driver( do_dyn )
320  call prof_rapend ('ATM_Dynamics', 1)
321  endif
322 
323  !########## Reference State ###########
324  if ( atmos_refstate_update_flag ) then
325  call prof_rapstart('ATM_Refstate', 2)
326  call atmos_refstate_update( dens, rhot, qtrc ) ! [IN]
327  call prof_rapend ('ATM_Refstate', 2)
328  endif
329 
330  !########## Lateral/Top Boundary Condition ###########
331  if ( atmos_boundary_update_flag ) then
332  call prof_rapstart('ATM_Boundary', 2)
333  call atmos_boundary_update( dens, momz, momx, momy, rhot, qtrc ) ! [INOUT]
334  call prof_rapend ('ATM_Boundary', 2)
335  endif
336 
337  !########## reset tendencies ##########
338 !OCL XFILL
339  dens_tp(:,:,:) = 0.0_rp
340 !OCL XFILL
341  momz_tp(:,:,:) = 0.0_rp
342 !OCL XFILL
343  momx_tp(:,:,:) = 0.0_rp
344 !OCL XFILL
345  momy_tp(:,:,:) = 0.0_rp
346 !OCL XFILL
347  rhot_tp(:,:,:) = 0.0_rp
348 !OCL XFILL
349  rhoq_tp(:,:,:,:) = 0.0_rp
350 
351  !########## Calculate diagnostic variables ##########
352  call prof_rapstart('ATM_History', 1)
354  call prof_rapend ('ATM_History', 1)
355 
356  !########## Microphysics ##########
357  if ( atmos_sw_phy_mp ) then
358  call prof_rapstart('ATM_Microphysics', 1)
359  call atmos_phy_mp_driver( update_flag = do_phy_mp )
360  call prof_rapend ('ATM_Microphysics', 1)
361  endif
362 
363  !########## Aerosol ##########
364  if ( atmos_sw_phy_ae ) then
365  call prof_rapstart('ATM_Aerosol', 1)
366  call atmos_phy_ae_driver( update_flag = do_phy_ae )
367  call prof_rapend ('ATM_Aerosol', 1)
368  endif
369 
370  !########## Chemistry ##########
371  if ( atmos_sw_phy_ch ) then
372  call prof_rapstart('ATM_Chemistry', 1)
373  call atmos_phy_ch_driver( update_flag = do_phy_ch )
374  call prof_rapend ('ATM_Chemistry', 1)
375  endif
376 
377  !########## Radiation ##########
378  if ( atmos_sw_phy_rd ) then
379  call prof_rapstart('ATM_Radiation', 1)
380  call atmos_phy_rd_driver( update_flag = do_phy_rd )
381  call prof_rapend ('ATM_Radiation', 1)
382  endif
383 
384  !########## Surface Flux ##########
385  if ( atmos_sw_phy_sf ) then
386  call prof_rapstart('ATM_SurfaceFlux', 1)
387  call atmos_phy_sf_driver( update_flag = do_phy_sf )
388  call prof_rapend ('ATM_SurfaceFlux', 1)
389  endif
390 
391  !########## Turbulence ##########
392  if ( atmos_sw_phy_tb ) then
393  call prof_rapstart('ATM_Turbulence', 1)
394  call atmos_phy_tb_driver( update_flag = do_phy_tb )
395  call prof_rapend ('ATM_Turbulence', 1)
396  endif
397 
398  !########## Cumulus ##########
399  if ( atmos_sw_phy_cp ) then
400  call prof_rapstart('ATM_Cumulus', 1)
401  call atmos_phy_cp_driver( update_flag = do_phy_cp )
402  call prof_rapend ('ATM_Cumulus', 1)
403  endif
404 
405  !########## Set Surface Boundary Condition ##########
406  call prof_rapstart('ATM_SfcExch', 2)
407  call atmos_surface_set( countup = .true. )
408  call prof_rapend ('ATM_SfcExch', 2)
409 
410  !########## History & Monitor ##########
411  call prof_rapstart('ATM_History', 1)
412  call atmos_vars_history
413  call atmos_vars_monitor
414  call prof_rapend ('ATM_History', 1)
415 
416  return
417  end subroutine atmos_driver
418 
419  !-----------------------------------------------------------------------------
421  subroutine atmos_driver_finalize
422  use scale_atmos_boundary, only: &
425  use scale_grid_nest, only: &
427  implicit none
428  !---------------------------------------------------------------------------
429 
430  !########## Lateral/Top Boundary Condition ###########
431  if ( atmos_boundary_update_flag ) then
432  ! If this run is parent of online nesting, boundary data must be sent
434 
435  ! Finialize Inter-Communicators
437  endif
438 
439  return
440  end subroutine atmos_driver_finalize
441 
442  !-----------------------------------------------------------------------------
444  subroutine atmos_surface_get
446  sfc_temp => atmos_phy_sf_sfc_temp, &
447  sfc_albedo => atmos_phy_sf_sfc_albedo, &
448  sfc_z0m => atmos_phy_sf_sfc_z0m, &
449  sfc_z0h => atmos_phy_sf_sfc_z0h, &
450  sfc_z0e => atmos_phy_sf_sfc_z0e, &
451  sflx_mw => atmos_phy_sf_sflx_mw, &
452  sflx_mu => atmos_phy_sf_sflx_mu, &
453  sflx_mv => atmos_phy_sf_sflx_mv, &
454  sflx_sh => atmos_phy_sf_sflx_sh, &
455  sflx_lh => atmos_phy_sf_sflx_lh, &
456  sflx_gh => atmos_phy_sf_sflx_gh, &
457  sflx_qtrc => atmos_phy_sf_sflx_qtrc, &
458  u10 => atmos_phy_sf_u10, &
459  v10 => atmos_phy_sf_v10, &
460  t2 => atmos_phy_sf_t2, &
461  q2 => atmos_phy_sf_q2
462  use mod_cpl_admin, only: &
463  cpl_sw
464  use mod_cpl_vars, only: &
466  implicit none
467  !---------------------------------------------------------------------------
468 
469  if ( cpl_sw ) then
470  call cpl_getsfc_atm( sfc_temp(:,:), & ! [OUT]
471  sfc_albedo(:,:,:), & ! [OUT]
472  sfc_z0m(:,:), & ! [OUT]
473  sfc_z0h(:,:), & ! [OUT]
474  sfc_z0e(:,:), & ! [OUT]
475  sflx_mw(:,:), & ! [OUT]
476  sflx_mu(:,:), & ! [OUT]
477  sflx_mv(:,:), & ! [OUT]
478  sflx_sh(:,:), & ! [OUT]
479  sflx_lh(:,:), & ! [OUT]
480  sflx_gh(:,:), & ! [OUT]
481  sflx_qtrc(:,:,:), & ! [OUT]
482  u10(:,:), & ! [OUT]
483  v10(:,:), & ! [OUT]
484  t2(:,:), & ! [OUT]
485  q2(:,:) ) ! [OUT]
486  endif
487 
488  return
489  end subroutine atmos_surface_get
490 
491  !-----------------------------------------------------------------------------
493  subroutine atmos_surface_set( countup )
494  use scale_grid_real, only: &
495  real_cz, &
496  real_z1
497  use scale_topography, only: &
498  topo_zsfc
499  use scale_atmos_bottom, only: &
500  bottom_estimate => atmos_bottom_estimate
501  use mod_atmos_vars, only: &
502  dens, &
503  qtrc, &
504  temp, &
505  pres, &
506  w, &
507  u, &
508  v
509  use mod_atmos_phy_mp_vars, only: &
510  sflx_rain => atmos_phy_mp_sflx_rain, &
511  sflx_snow => atmos_phy_mp_sflx_snow
512  use mod_atmos_phy_rd_vars, only: &
513  sflx_rad_dn => atmos_phy_rd_sflx_downall, &
514  cossza => atmos_phy_rd_cossza
515  use mod_cpl_admin, only: &
516  cpl_sw
517  use mod_cpl_vars, only: &
518  cpl_putatm
519  implicit none
520 
521  ! arguments
522  logical, intent(in) :: countup
523 
524  ! works
525  real(RP) :: SFC_DENS(ia,ja)
526  real(RP) :: SFC_PRES(ia,ja)
527  real(RP) :: ATM_PBL (ia,ja)
528  !---------------------------------------------------------------------------
529 
530  if ( cpl_sw ) then
531  ! planetary boundary layer
532  atm_pbl(:,:) = 100.0_rp ! tentative
533 
534  call bottom_estimate( dens(:,:,:), & ! [IN]
535  pres(:,:,:), & ! [IN]
536  real_cz(:,:,:), & ! [IN]
537  topo_zsfc(:,:), & ! [IN]
538  real_z1(:,:), & ! [IN]
539  sfc_dens(:,:), & ! [OUT]
540  sfc_pres(:,:) ) ! [OUT]
541 
542  call cpl_putatm( temp(ks,:,:), & ! [IN]
543  pres(ks,:,:), & ! [IN]
544  w(ks,:,:), & ! [IN]
545  u(ks,:,:), & ! [IN]
546  v(ks,:,:), & ! [IN]
547  dens(ks,:,:), & ! [IN]
548  qtrc(ks,:,:,:), & ! [IN]
549  atm_pbl(:,:), & ! [IN]
550  sfc_pres(:,:), & ! [IN]
551  sflx_rad_dn(:,:,:,:), & ! [IN]
552  cossza(:,:), & ! [IN]
553  sflx_rain(:,:), & ! [IN]
554  sflx_snow(:,:), & ! [IN]
555  countup ) ! [IN]
556  endif
557 
558  return
559  end subroutine atmos_surface_set
560 
561 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 increment.
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)