SCALE-RM
mod_atmos_driver.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
10 !-------------------------------------------------------------------------------
11 #include "scalelib.h"
13  !-----------------------------------------------------------------------------
14  !
15  !++ used modules
16  !
17  use scale_precision
18  use scale_io
19  use scale_prof
21  !-----------------------------------------------------------------------------
22  implicit none
23  private
24  !-----------------------------------------------------------------------------
25  !
26  !++ Public procedure
27  !
29  public :: atmos_driver_setup
30  public :: atmos_driver_finalize
33  public :: atmos_driver_update
34  public :: atmos_surface_get
35  public :: atmos_surface_set
36 
37  !-----------------------------------------------------------------------------
38  !
39  !++ Public parameters & variables
40  !
41  !-----------------------------------------------------------------------------
42  !
43  !++ Private procedure
44  !
45  !-----------------------------------------------------------------------------
46  !
47  !++ Private parameters & variables
48  !
49  !-----------------------------------------------------------------------------
50 contains
51  !-----------------------------------------------------------------------------
53  subroutine atmos_driver_tracer_setup
58  use mod_atmos_phy_mp_vars, only: &
59  qa_mp, &
60  qs_mp, &
61  qe_mp
62  use mod_atmos_phy_ae_driver, only: &
64  use mod_atmos_phy_ch_driver, only: &
66  use mod_atmos_phy_tb_driver, only: &
68  use mod_atmos_phy_bl_driver, only: &
70  use scale_atmos_hydrometeor, only: &
73  use mod_atmos_admin, only: &
75  use mod_atmos_phy_lt_driver, only: &
77  implicit none
78 
79  !---------------------------------------------------------------------------
80 
81  log_newline
82  log_info("ATMOS_driver_tracer_setup",*) 'Setup'
83 
84 
91 
92  if ( atmos_hydrometeor_dry .and. atmos_use_qv ) then
93  log_info("ATMOS_driver_tracer_setup",*) 'Regist QV'
94  call atmos_hydrometeor_regist( 0, 0, & ! (in)
95  (/'QV'/), & ! (in)
96  (/'Ratio of Water Vapor mass to total mass (Specific humidity)'/), & ! (in)
97  (/'kg/kg'/), & ! (in)
98  qs_mp ) ! (out)
99  qa_mp = 1
100  qe_mp = qs_mp
102 
103  end if
104 
105  return
106  end subroutine atmos_driver_tracer_setup
107 
108  !-----------------------------------------------------------------------------
110  subroutine atmos_driver_setup( init )
111  use scale_time, only: &
113  use scale_atmos_solarins, only: &
115  use scale_atmos_refstate, only: &
117  use mod_atmos_bnd_driver, only: &
119  use mod_atmos_dyn_driver, only: &
121  use mod_atmos_phy_mp_driver, only: &
123  use mod_atmos_phy_mp_vars, only: &
124  qa_mp, &
125  qs_mp, &
126  qe_mp
127  use mod_atmos_phy_ch_driver, only: &
129  use mod_atmos_phy_ae_driver, only: &
131  use mod_atmos_phy_rd_driver, only: &
133  use mod_atmos_phy_sf_driver, only: &
135  use mod_atmos_phy_tb_driver, only: &
137  use mod_atmos_phy_bl_driver, only: &
139  use mod_atmos_phy_cp_driver, only: &
141  use mod_atmos_phy_lt_driver, only: &
143  use scale_atmos_grid_cartesc, only: &
144  cz => atmos_grid_cartesc_cz, &
146  use scale_atmos_grid_cartesc_real, only: &
149  real_cz => atmos_grid_cartesc_real_cz, &
150  real_fz => atmos_grid_cartesc_real_fz, &
151  real_phi => atmos_grid_cartesc_real_phi
152  implicit none
153  logical, intent(in), optional :: init
154  logical :: not_init
155  !---------------------------------------------------------------------------
156 
157  not_init = .true.
158  if ( present(init) ) not_init = .not. init
159 
160  log_newline
161  log_info("ATMOS_driver_setup",*) 'Setup'
162 
163  log_newline
164  log_info("ATMOS_driver_setup",*) 'Setup each atmospheric components ...'
165 
166  !--- setup solar insolation
167  call atmos_solarins_setup( base_lon, base_lat, time_nowdate(1) )
168 
169  call prof_rapstart('ATM_Refstate', 2)
170  call atmos_refstate_setup( ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
171  cz(:), fz(:), real_cz(:,:,:), real_fz(:,:,:), real_phi(:,:,:) )
172  call prof_rapend ('ATM_Refstate', 2)
173 
174  call prof_rapstart('ATM_Boundary', 2)
175  if ( not_init ) call atmos_boundary_driver_setup
176  call prof_rapend ('ATM_Boundary', 2)
177 
178  ! setup each components
179  if ( not_init ) call atmos_dyn_driver_setup
180  if ( not_init ) call atmos_phy_lt_driver_setup
182  if ( not_init ) call atmos_phy_ae_driver_setup
183  if ( not_init ) call atmos_phy_ch_driver_setup
184  if ( not_init ) call atmos_phy_rd_driver_setup
185  if ( not_init ) call atmos_phy_sf_driver_setup
186  if ( not_init ) call atmos_phy_tb_driver_setup
188  if ( not_init ) call atmos_phy_cp_driver_setup
189 
190  log_newline
191  log_info("ATMOS_driver_setup",*) 'Finish setup of each atmospheric components.'
192 
193  return
194  end subroutine atmos_driver_setup
195 
196  !-----------------------------------------------------------------------------
198  subroutine atmos_driver_calc_tendency( force )
199  use mod_atmos_vars, only: &
200  dens_tp, &
201  momz_tp, &
202  rhou_tp, &
203  rhov_tp, &
204  rhot_tp, &
205  rhoh_p, &
206  rhoq_tp, &
207  momx_tp, &
208  momy_tp
209  use mod_atmos_phy_mp_driver, only: &
211  use mod_atmos_phy_ch_driver, only: &
213  use mod_atmos_phy_ae_driver, only: &
215  use mod_atmos_phy_rd_driver, only: &
217  use mod_atmos_phy_sf_driver, only: &
219  use mod_atmos_phy_tb_driver, only: &
221  use mod_atmos_phy_cp_driver, only: &
223  use mod_atmos_phy_bl_driver, only: &
225  use mod_admin_time, only: &
226  do_phy_mp => time_doatmos_phy_mp, &
227  do_phy_ae => time_doatmos_phy_ae, &
228  do_phy_ch => time_doatmos_phy_ch, &
229  do_phy_rd => time_doatmos_phy_rd, &
230  do_phy_sf => time_doatmos_phy_sf, &
231  do_phy_tb => time_doatmos_phy_tb, &
232  do_phy_bl => time_doatmos_phy_bl, &
233  do_phy_cp => time_doatmos_phy_cp, &
234  do_phy_lt => time_doatmos_phy_lt
235  use mod_atmos_admin, only: &
236  atmos_sw_phy_mp, &
237  atmos_sw_phy_ae, &
238  atmos_sw_phy_ch, &
239  atmos_sw_phy_rd, &
240  atmos_sw_phy_sf, &
241  atmos_sw_phy_tb, &
242  atmos_sw_phy_bl, &
244  use mod_cpl_admin, only: &
245  cpl_sw
246  implicit none
247  logical, intent(in) :: force
248  !---------------------------------------------------------------------------
249 
250  !########## Get Surface Boundary from coupler ##########
251  call atmos_surface_get
252 
253  !########## calculate tendency ##########
254  ! reset tendencies
255  !$omp parallel workshare
256  !$acc kernels
257 !OCL XFILL
258  dens_tp(:,:,:) = 0.0_rp
259  !$acc end kernels
260  !$acc kernels
261 !OCL XFILL
262  momz_tp(:,:,:) = 0.0_rp
263  !$acc end kernels
264  !$acc kernels
265 !OCL XFILL
266  rhou_tp(:,:,:) = 0.0_rp
267  !$acc end kernels
268  !$acc kernels
269 !OCL XFILL
270  rhov_tp(:,:,:) = 0.0_rp
271  !$acc end kernels
272  !$acc kernels
273 !OCL XFILL
274  rhot_tp(:,:,:) = 0.0_rp
275  !$acc end kernels
276  !$acc kernels
277 !OCL XFILL
278  rhoh_p(:,:,:) = 0.0_rp
279  !$acc end kernels
280  !$acc kernels
281 !OCL XFILL
282  rhoq_tp(:,:,:,:) = 0.0_rp
283  !$acc end kernels
284  !$acc kernels
285 !OCL XFILL
286  momx_tp(:,:,:) = 0.0_rp
287  !$acc end kernels
288  !$acc kernels
289 !OCL XFILL
290  momy_tp(:,:,:) = 0.0_rp
291  !$acc end kernels
292  !$omp end parallel workshare
293 
294  ! Microphysics
295  if ( atmos_sw_phy_mp ) then
296  call prof_rapstart('ATM_Microphysics', 1)
297  call atmos_phy_mp_driver_calc_tendency( update_flag = do_phy_mp .or. force )
298  call prof_rapend ('ATM_Microphysics', 1)
299  endif
300  ! Aerosol
301  if ( atmos_sw_phy_ae ) then
302  call prof_rapstart('ATM_Aerosol', 1)
303  call atmos_phy_ae_driver_calc_tendency( update_flag = do_phy_ae .or. force )
304  call prof_rapend ('ATM_Aerosol', 1)
305  endif
306  ! Chemistry
307  if ( atmos_sw_phy_ch ) then
308  call prof_rapstart('ATM_Chemistry', 1)
309  call atmos_phy_ch_driver_calc_tendency( update_flag = do_phy_ch .or. force )
310  call prof_rapend ('ATM_Chemistry', 1)
311  endif
312  ! Radiation
313  if ( atmos_sw_phy_rd ) then
314  call prof_rapstart('ATM_Radiation', 1)
315  call atmos_phy_rd_driver_calc_tendency( update_flag = do_phy_rd .or. force )
316  call prof_rapend ('ATM_Radiation', 1)
317  endif
318  ! Turbulence
319  if ( atmos_sw_phy_tb ) then
320  call prof_rapstart('ATM_Turbulence', 1)
321  call atmos_phy_tb_driver_calc_tendency( update_flag = do_phy_tb .or. force )
322  call prof_rapend ('ATM_Turbulence', 1)
323  endif
324  ! Cumulus
325  if ( atmos_sw_phy_cp ) then
326  call prof_rapstart('ATM_Cumulus', 1)
327  call atmos_phy_cp_driver_calc_tendency( update_flag = do_phy_cp .or. force )
328  call prof_rapend ('ATM_Cumulus', 1)
329  endif
330  if ( .not. cpl_sw ) then
331  ! Surface Flux
332  if ( atmos_sw_phy_sf ) then
333  call prof_rapstart('ATM_SurfaceFlux', 1)
334  call atmos_phy_sf_driver_calc_tendency( update_flag = do_phy_sf .or. force )
335  call prof_rapend ('ATM_SurfaceFlux', 1)
336  endif
337  ! Planetary Boundary layer
338  if ( atmos_sw_phy_bl ) then
339  call prof_rapstart('ATM_PBL', 1)
340  call atmos_phy_bl_driver_calc_tendency( update_flag = do_phy_bl .or. force )
341  call prof_rapend ('ATM_PBL', 1)
342  endif
343  end if
344 
345  !########## Set Surface Boundary Condition ##########
346  call atmos_surface_set( countup = .true. )
347 
348  return
349  end subroutine atmos_driver_calc_tendency
350 
351  !-----------------------------------------------------------------------------
353  subroutine atmos_driver_calc_tendency_from_sflux( force )
356  use mod_atmos_phy_bl_driver, only: &
358  use mod_cpl_admin, only: &
359  cpl_sw
360  use mod_atmos_admin, only: &
361  atmos_sw_phy_sf, &
363  use mod_admin_time, only: &
364  do_phy_sf => time_doatmos_phy_sf, &
365  do_phy_bl => time_doatmos_phy_bl
366  implicit none
367  logical, intent(in) :: force
368  !---------------------------------------------------------------------------
369 
370  if ( cpl_sw ) then
371 
372  !########## Get Surface Boundary Condition ##########
373  call atmos_surface_get
374 
375  ! Surface Flux
376  if ( atmos_sw_phy_sf ) then
377  call prof_rapstart('ATM_SurfaceFlux', 1)
378  call atmos_phy_sf_driver_calc_tendency( update_flag = do_phy_sf .or. force )
379  call prof_rapend ('ATM_SurfaceFlux', 1)
380  endif
381 
382  ! Planetary Boundary layer
383  if ( atmos_sw_phy_bl ) then
384  call prof_rapstart('ATM_PBL', 1)
385  call atmos_phy_bl_driver_calc_tendency( update_flag = do_phy_bl .or. force )
386  call prof_rapend ('ATM_PBL', 1)
387  endif
388 
389  end if
390 
391  return
393 
394  !-----------------------------------------------------------------------------
396  subroutine atmos_driver_update
397  use mod_atmos_admin, only: &
398  atmos_sw_dyn, &
399  atmos_sw_phy_mp, &
400  atmos_sw_phy_ae, &
402  use mod_admin_time, only: &
403  do_dyn => time_doatmos_dyn, &
404  do_phy_mp => time_doatmos_phy_mp, &
405  do_phy_ae => time_doatmos_phy_ae
406  use scale_atmos_refstate, only: &
408  use mod_atmos_vars, only: &
411  dens, &
412  temp, &
413  pres, &
414  pott, &
415  qv
416  use mod_atmos_bnd_driver, only: &
420  use mod_atmos_dyn_driver, only: &
422  use mod_atmos_phy_mp_driver, only: &
424  use mod_atmos_phy_ae_driver, only: &
426  use mod_atmos_phy_lt_driver, only: &
428  use scale_atmos_grid_cartesc, only: &
429  cz => atmos_grid_cartesc_cz, &
430  fz => atmos_grid_cartesc_fz, &
431  fdz => atmos_grid_cartesc_fdz, &
433  use scale_atmos_grid_cartesc_real, only: &
434  real_cz => atmos_grid_cartesc_real_cz, &
435  real_fz => atmos_grid_cartesc_real_fz, &
436  real_phi => atmos_grid_cartesc_real_phi, &
438  use scale_time, only: &
439  time_nowdaysec, &
440  time_dtsec
441  implicit none
442 
443  !---------------------------------------------------------------------------
444 
445  !########## Dynamics ##########
446  if ( atmos_sw_dyn ) then
447  if ( atmos_boundary_update_flag ) then
448  call prof_rapstart('ATM_Boundary', 2)
450  call prof_rapend ('ATM_Boundary', 2)
452  endif
453  call prof_rapstart('ATM_Dynamics', 1)
454  call atmos_dyn_driver( do_dyn )
455  call prof_rapend ('ATM_Dynamics', 1)
456  endif
457 
458 
459  !########## Calculate diagnostic variables ##########
461 
462 
463  !########## Adjustment ##########
464  ! Microphysics
465  if ( atmos_sw_phy_mp ) then
466  call prof_rapstart('ATM_Microphysics', 1)
468  call prof_rapend ('ATM_Microphysics', 1)
471  endif
472  ! Aerosol
473  if ( atmos_sw_phy_ae ) then
474  call prof_rapstart('ATM_Aerosol', 1)
476  call prof_rapend ('ATM_Aerosol', 1)
479  endif
480  ! Lightning
481  if ( atmos_sw_phy_lt ) then
482  call prof_rapstart('ATM_Lightning', 1)
484  call prof_rapend ('ATM_Lightning', 1)
486  ! calc_diagnostics is not necessary
487  end if
488 
489 
490  !########## Lateral/Top Boundary Condition ###########
491  if ( atmos_boundary_update_flag ) then
492  call prof_rapstart('ATM_Boundary', 2)
494  call prof_rapend ('ATM_Boundary', 2)
497  endif
498 
499 
500  !########## Send Lateral/Top Boundary Condition (Online nesting) ###########
501  if ( atmos_boundary_update_flag ) then
502  call prof_rapstart('ATM_Boundary', 2)
504  call prof_rapend ('ATM_Boundary', 2)
505  endif
506 
507 
508  !########## Reference State ###########
509  call prof_rapstart('ATM_Refstate', 2)
510  call atmos_refstate_update( ka, ks, ke, ia, is, ie, isb, ieb, ja, js, je, jsb, jeb, &
511  dens(:,:,:), pott(:,:,:), temp(:,:,:), pres(:,:,:), qv(:,:,:), & ! [IN]
512  cz(:), fz(:), fdz(:), rcdz(:), & ! [IN]
513  real_cz(:,:,:), real_fz(:,:,:), real_phi(:,:,:), area(:,:), & ! [IN]
514  time_nowdaysec ) ! [IN]
515  call prof_rapend ('ATM_Refstate', 2)
516 
517  return
518  end subroutine atmos_driver_update
519 
520  !-----------------------------------------------------------------------------
522  subroutine atmos_driver_finalize( init )
523  use scale_atmos_refstate, only: &
525  use mod_atmos_bnd_driver, only: &
527  use mod_atmos_dyn_driver, only: &
529  use mod_atmos_phy_lt_driver, only: &
531  use mod_atmos_phy_mp_driver, only: &
533  use mod_atmos_phy_ae_driver, only: &
535  use mod_atmos_phy_ch_driver, only: &
537  use mod_atmos_phy_rd_driver, only: &
539  use mod_atmos_phy_tb_driver, only: &
541  use mod_atmos_phy_bl_driver, only: &
543  use mod_atmos_phy_cp_driver, only: &
545  implicit none
546  logical, intent(in), optional :: init
547  logical :: not_init
548  !---------------------------------------------------------------------------
549 
550  log_newline
551  log_info("ATMOS_driver_finalize",*) 'Finalize'
552 
553  not_init = .true.
554  if ( present(init) ) not_init = .not. init
555 
556  if ( not_init ) call atmos_dyn_driver_finalize
557  if ( not_init ) call atmos_phy_lt_driver_finalize
559  if ( not_init ) call atmos_phy_ae_driver_finalize
560  if ( not_init ) call atmos_phy_ch_driver_finalize
561  if ( not_init ) call atmos_phy_rd_driver_finalize
562  !if ( not_init ) call ATMOS_PHY_SF_driver_finalize
563  if ( not_init ) call atmos_phy_tb_driver_finalize
565  if ( not_init )call atmos_phy_cp_driver_finalize
566 
567  if ( not_init ) call atmos_boundary_driver_finalize
568 
570 
571  return
572  end subroutine atmos_driver_finalize
573 
574  !-----------------------------------------------------------------------------
576  subroutine atmos_surface_get
578  sfc_temp => atmos_phy_sf_sfc_temp, &
579  sfc_albedo => atmos_phy_sf_sfc_albedo, &
580  sfc_z0m => atmos_phy_sf_sfc_z0m, &
581  sfc_z0h => atmos_phy_sf_sfc_z0h, &
582  sfc_z0e => atmos_phy_sf_sfc_z0e, &
583  sflx_mw => atmos_phy_sf_sflx_mw, &
584  sflx_mu => atmos_phy_sf_sflx_mu, &
585  sflx_mv => atmos_phy_sf_sflx_mv, &
586  sflx_sh => atmos_phy_sf_sflx_sh, &
587  sflx_lh => atmos_phy_sf_sflx_lh, &
588  sflx_shex => atmos_phy_sf_sflx_shex, &
589  sflx_lhex => atmos_phy_sf_sflx_lhex, &
590  sflx_qvex => atmos_phy_sf_sflx_qvex, &
591  sflx_gh => atmos_phy_sf_sflx_gh, &
592  sflx_qtrc => atmos_phy_sf_sflx_qtrc, &
593  sflx_engi => atmos_phy_sf_sflx_engi, &
594  u10 => atmos_phy_sf_u10, &
595  v10 => atmos_phy_sf_v10, &
596  t2 => atmos_phy_sf_t2, &
597  q2 => atmos_phy_sf_q2
598  use mod_cpl_admin, only: &
599  cpl_sw
600  use mod_cpl_vars, only: &
602  implicit none
603  !---------------------------------------------------------------------------
604 
605  call prof_rapstart('ATM_SfcExch', 2)
606 
607  if ( cpl_sw ) then
608  call cpl_getsfc_atm( sfc_temp(:,:), & ! [OUT]
609  sfc_albedo(:,:,:,:), & ! [OUT]
610  sfc_z0m(:,:), & ! [OUT]
611  sfc_z0h(:,:), & ! [OUT]
612  sfc_z0e(:,:), & ! [OUT]
613  sflx_mw(:,:), & ! [OUT]
614  sflx_mu(:,:), & ! [OUT]
615  sflx_mv(:,:), & ! [OUT]
616  sflx_sh(:,:), & ! [OUT]
617  sflx_lh(:,:), & ! [OUT]
618  sflx_shex(:,:), & ! [OUT]
619  sflx_lhex(:,:), & ! [OUT]
620  sflx_qvex(:,:), & ! [OUT]
621  sflx_gh(:,:), & ! [OUT]
622  sflx_qtrc(:,:,:), & ! [OUT]
623  sflx_engi(:,:), & ! [OUT]
624  u10(:,:), & ! [OUT]
625  v10(:,:), & ! [OUT]
626  t2(:,:), & ! [OUT]
627  q2(:,:) ) ! [OUT]
628  endif
629 
630  call prof_rapend ('ATM_SfcExch', 2)
631 
632  return
633  end subroutine atmos_surface_get
634 
635  !-----------------------------------------------------------------------------
637  subroutine atmos_surface_set( countup )
639  real_fz => atmos_grid_cartesc_real_fz
640  use scale_atmos_bottom, only: &
641  bottom_estimate => atmos_bottom_estimate
642  use mod_atmos_vars, only: &
643  dens, &
644  qv, &
645  temp, &
646  pres, &
647  w, &
648  u, &
649  v, &
650  prec, &
651  prec_engi
652  use mod_atmos_phy_sf_vars, only: &
653  sfc_temp => atmos_phy_sf_sfc_temp
654  use mod_atmos_phy_mp_vars, only: &
655  sflx_rain_mp => atmos_phy_mp_sflx_rain, &
656  sflx_snow_mp => atmos_phy_mp_sflx_snow, &
657  sflx_engi_mp => atmos_phy_mp_sflx_engi
658  use mod_atmos_phy_cp_vars, only: &
659  sflx_rain_cp => atmos_phy_cp_sflx_rain, &
660  sflx_snow_cp => atmos_phy_cp_sflx_snow, &
661  sflx_engi_cp => atmos_phy_cp_sflx_engi
662  use mod_atmos_phy_rd_vars, only: &
663  sflx_rad_dn => atmos_phy_rd_sflx_down, &
664  cossza => atmos_phy_rd_cossza
665  use mod_atmos_phy_bl_vars, only: &
666  atm_pbl => atmos_phy_bl_zi
667  use mod_cpl_admin, only: &
668  cpl_sw
669  use mod_cpl_vars, only: &
670  cpl_putatm
671  implicit none
672 
673  ! arguments
674  logical, intent(in) :: countup
675 
676  ! works
677  real(rp) :: sfc_dens(ia,ja)
678  real(rp) :: sfc_pres(ia,ja)
679 
680  real(rp) :: temp1(ia,ja)
681  real(rp) :: pres1(ia,ja)
682  real(rp) :: w1 (ia,ja)
683  real(rp) :: u1 (ia,ja)
684  real(rp) :: v1 (ia,ja)
685  real(rp) :: dens1(ia,ja)
686  real(rp) :: qv1 (ia,ja)
687 
688  integer :: i,j
689  !---------------------------------------------------------------------------
690 
691  call prof_rapstart('ATM_SfcExch', 2)
692 
693  ! sum of rainfall from mp and cp
694  !$omp parallel do private(i,j) OMP_SCHEDULE_
695  !$acc kernels
696  do j = js, je
697  do i = is, ie
698  prec(i,j) = sflx_rain_mp(i,j) + sflx_rain_cp(i,j) + sflx_snow_mp(i,j) + sflx_snow_cp(i,j)
699  prec_engi(i,j) = sflx_engi_mp(i,j) + sflx_engi_cp(i,j)
700  enddo
701  enddo
702  !$acc end kernels
703 
704  if ( cpl_sw ) then
705 
706  !$acc data create(SFC_DENS,SFC_PRES,TEMP1,PRES1,W1,U1,V1,DENS1,QV1)
707 
708  ! planetary boundary layer
709  call bottom_estimate( ka, ks, ke, ia, is, ie, ja, js, je, &
710  dens(:,:,:), pres(:,:,:), qv(:,:,:), & ! [IN]
711  sfc_temp(:,:), & ! [IN]
712  real_fz(:,:,:), & ! [IN]
713  sfc_dens(:,:), sfc_pres(:,:) ) ! [OUT]
714 
715  !$omp parallel do
716  !$acc kernels
717  do j = js, je
718  do i = is, ie
719  temp1(i,j) = temp(ks,i,j)
720  pres1(i,j) = pres(ks,i,j)
721  w1(i,j) = w(ks,i,j)
722  u1(i,j) = u(ks,i,j)
723  v1(i,j) = v(ks,i,j)
724  dens1(i,j) = dens(ks,i,j)
725  qv1(i,j) = qv(ks,i,j)
726  end do
727  end do
728  !$acc end kernels
729 
730  call cpl_putatm( temp1(:,:), & ! [IN]
731  pres1(:,:), & ! [IN]
732  w1(:,:), & ! [IN]
733  u1(:,:), & ! [IN]
734  v1(:,:), & ! [IN]
735  dens1(:,:), & ! [IN]
736  qv1(:,:), & ! [IN]
737  atm_pbl(:,:), & ! [IN]
738  sfc_dens(:,:), & ! [IN]
739  sfc_pres(:,:), & ! [IN]
740  sflx_rad_dn(:,:,:,:), & ! [IN]
741  cossza(:,:), & ! [IN]
742  prec(:,:), & ! [IN]
743  prec_engi(:,:), & ! [IN]
744  countup ) ! [IN]
745 
746  !$acc end data
747 
748  endif
749 
750  call prof_rapend ('ATM_SfcExch', 2)
751 
752  return
753  end subroutine atmos_surface_set
754 
756 
757  end subroutine atmos_driver_boundary_update
758 end module mod_atmos_driver
mod_atmos_phy_rd_vars::atmos_phy_rd_sflx_down
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_rd_sflx_down
Definition: mod_atmos_phy_rd_vars.F90:72
mod_atmos_phy_sf_vars::atmos_phy_sf_sfc_z0m
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sfc_z0m
Definition: mod_atmos_phy_sf_vars.F90:67
mod_atmos_phy_mp_vars::atmos_phy_mp_sflx_engi
real(rp), dimension(:,:), allocatable, public atmos_phy_mp_sflx_engi
Definition: mod_atmos_phy_mp_vars.F90:76
mod_admin_time::time_doatmos_phy_mp
logical, public time_doatmos_phy_mp
execute physics in this step? (microphysics)
Definition: mod_admin_time.F90:49
scale_atmos_grid_cartesc_index::isb
integer, public isb
Definition: scale_atmos_grid_cartesC_index.F90:64
mod_atmos_phy_mp_vars
module Atmosphere / Physics Cloud Microphysics
Definition: mod_atmos_phy_mp_vars.F90:12
scale_atmos_grid_cartesc_index::ke
integer, public ke
end point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:52
scale_time::time_nowdaysec
real(dp), public time_nowdaysec
second of current time [sec]
Definition: scale_time.F90:72
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_mu
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_mu
Definition: mod_atmos_phy_sf_vars.F90:78
mod_atmos_bnd_driver::atmos_boundary_update_flag
logical, public atmos_boundary_update_flag
Definition: mod_atmos_bnd_driver.F90:64
mod_atmos_admin::atmos_sw_phy_tb
logical, public atmos_sw_phy_tb
Definition: mod_atmos_admin.F90:57
mod_atmos_phy_mp_vars::qa_mp
integer, public qa_mp
Definition: mod_atmos_phy_mp_vars.F90:78
mod_atmos_dyn_driver::atmos_dyn_driver_finalize
subroutine, public atmos_dyn_driver_finalize
finalize
Definition: mod_atmos_dyn_driver.F90:228
mod_admin_time::time_doatmos_phy_ch
logical, public time_doatmos_phy_ch
execute physics in this step? (chemistry )
Definition: mod_admin_time.F90:54
mod_atmos_vars::rhoq_tp
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
Definition: mod_atmos_vars.F90:121
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_cz
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_cz
geopotential height [m] (zxy)
Definition: scale_atmos_grid_cartesC_real.F90:39
mod_atmos_phy_sf_vars::atmos_phy_sf_v10
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_v10
Definition: mod_atmos_phy_sf_vars.F90:96
mod_atmos_vars::pott
real(rp), dimension(:,:,:), allocatable, target, public pott
Definition: mod_atmos_vars.F90:133
mod_atmos_vars::atmos_vars_fillhalo
subroutine, public atmos_vars_fillhalo(FILL_BND)
HALO Communication.
Definition: mod_atmos_vars.F90:879
mod_atmos_driver::atmos_driver_tracer_setup
subroutine, public atmos_driver_tracer_setup
Tracer setup.
Definition: mod_atmos_driver.F90:54
mod_atmos_phy_sf_vars::atmos_phy_sf_sfc_z0e
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sfc_z0e
Definition: mod_atmos_phy_sf_vars.F90:69
mod_atmos_phy_ch_driver::atmos_phy_ch_driver_tracer_setup
subroutine, public atmos_phy_ch_driver_tracer_setup
Config.
Definition: mod_atmos_phy_ch_driver.F90:54
mod_atmos_bnd_driver::atmos_boundary_driver_finalize
subroutine, public atmos_boundary_driver_finalize
Finalize boundary value.
Definition: mod_atmos_bnd_driver.F90:1553
mod_cpl_vars
module COUPLER Variables
Definition: mod_cpl_vars.F90:12
mod_atmos_phy_cp_vars::atmos_phy_cp_sflx_engi
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_engi
Definition: mod_atmos_phy_cp_vars.F90:65
mod_atmos_phy_bl_driver::atmos_phy_bl_driver_tracer_setup
subroutine, public atmos_phy_bl_driver_tracer_setup
Config.
Definition: mod_atmos_phy_bl_driver.F90:52
scale_precision
module PRECISION
Definition: scale_precision.F90:14
mod_atmos_vars::rhov_tp
real(rp), dimension(:,:,:), allocatable, public rhov_tp
Definition: mod_atmos_vars.F90:118
scale_atmos_grid_cartesc_index::ka
integer, public ka
Definition: scale_atmos_grid_cartesC_index.F90:47
mod_atmos_phy_bl_vars::atmos_phy_bl_zi
real(rp), dimension(:,:), allocatable, public atmos_phy_bl_zi
Definition: mod_atmos_phy_bl_vars.F90:67
mod_atmos_admin
module ATMOS admin
Definition: mod_atmos_admin.F90:11
scale_atmos_solarins::atmos_solarins_setup
subroutine, public atmos_solarins_setup(basepoint_lon, basepoint_lat, iyear)
setup solar incidence module
Definition: scale_atmos_solarins.F90:570
mod_atmos_phy_ae_driver::atmos_phy_ae_driver_setup
subroutine, public atmos_phy_ae_driver_setup
Setup.
Definition: mod_atmos_phy_ae_driver.F90:105
mod_atmos_phy_mp_vars::qs_mp
integer, public qs_mp
Definition: mod_atmos_phy_mp_vars.F90:79
mod_atmos_admin::atmos_sw_dyn
logical, public atmos_sw_dyn
Definition: mod_atmos_admin.F90:51
mod_atmos_phy_bl_driver::atmos_phy_bl_driver_setup
subroutine, public atmos_phy_bl_driver_setup
Setup.
Definition: mod_atmos_phy_bl_driver.F90:109
mod_atmos_bnd_driver::atmos_boundary_driver_send
subroutine, public atmos_boundary_driver_send
Send data to child domain.
Definition: mod_atmos_bnd_driver.F90:1678
mod_atmos_bnd_driver::atmos_boundary_driver_update
subroutine, public atmos_boundary_driver_update(time)
Update boundary value with a constant time boundary.
Definition: mod_atmos_bnd_driver.F90:1632
mod_admin_time::time_doatmos_dyn
logical, public time_doatmos_dyn
execute dynamics in this step?
Definition: mod_admin_time.F90:47
mod_atmos_phy_rd_vars::atmos_phy_rd_cossza
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_cossza
Definition: mod_atmos_phy_rd_vars.F90:75
scale_prof::prof_rapstart
subroutine, public prof_rapstart(rapname_base, level, disable_barrier)
Start raptime.
Definition: scale_prof.F90:174
mod_atmos_admin::atmos_sw_phy_mp
logical, public atmos_sw_phy_mp
Definition: mod_atmos_admin.F90:52
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
mod_admin_time::time_doatmos_phy_tb
logical, public time_doatmos_phy_tb
execute physics in this step? (turbulence )
Definition: mod_admin_time.F90:52
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_mv
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_mv
Definition: mod_atmos_phy_sf_vars.F90:79
mod_atmos_phy_rd_vars
module Atmosphere / Physics Radiation
Definition: mod_atmos_phy_rd_vars.F90:12
scale_atmos_refstate
module atmosphere / reference state
Definition: scale_atmos_refstate.F90:12
mod_atmos_phy_ch_driver::atmos_phy_ch_driver_setup
subroutine, public atmos_phy_ch_driver_setup
Setup.
Definition: mod_atmos_phy_ch_driver.F90:109
mod_atmos_phy_sf_vars
module ATMOSPHERIC Surface Variables
Definition: mod_atmos_phy_sf_vars.F90:12
mod_atmos_phy_mp_vars::atmos_phy_mp_sflx_rain
real(rp), dimension(:,:), allocatable, public atmos_phy_mp_sflx_rain
Definition: mod_atmos_phy_mp_vars.F90:74
mod_atmos_vars::prec_engi
real(rp), dimension(:,:), allocatable, public prec_engi
Definition: mod_atmos_vars.F90:146
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_mw
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_mw
Definition: mod_atmos_phy_sf_vars.F90:77
scale_atmos_hydrometeor::atmos_hydrometeor_dry
logical, public atmos_hydrometeor_dry
Definition: scale_atmos_hydrometeor.F90:114
mod_atmos_phy_ae_driver::atmos_phy_ae_driver_finalize
subroutine, public atmos_phy_ae_driver_finalize
finalize
Definition: mod_atmos_phy_ae_driver.F90:140
scale_atmos_solarins
module atmosphere / SOLARINS
Definition: scale_atmos_solarins.F90:14
scale_atmos_grid_cartesc::atmos_grid_cartesc_rcdz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_rcdz
reciprocal of center-dz
Definition: scale_atmos_grid_cartesC.F90:45
mod_atmos_bnd_driver::atmos_boundary_driver_setup
subroutine, public atmos_boundary_driver_setup
Setup.
Definition: mod_atmos_bnd_driver.F90:179
mod_atmos_phy_sf_vars::atmos_phy_sf_sfc_z0h
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sfc_z0h
Definition: mod_atmos_phy_sf_vars.F90:68
scale_atmos_grid_cartesc_real
module Atmosphere GRID CartesC Real(real space)
Definition: scale_atmos_grid_cartesC_real.F90:11
mod_atmos_driver
module ATMOSPHERE driver
Definition: mod_atmos_driver.F90:12
mod_atmos_phy_sf_vars::atmos_phy_sf_sfc_temp
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sfc_temp
Definition: mod_atmos_phy_sf_vars.F90:65
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_basepoint_lat
real(rp), public atmos_grid_cartesc_real_basepoint_lat
position of base point in real world [rad,-pi,pi]
Definition: scale_atmos_grid_cartesC_real.F90:37
mod_admin_time::time_doatmos_phy_cp
logical, public time_doatmos_phy_cp
execute physics in this step? (cumulus )
Definition: mod_admin_time.F90:48
mod_admin_time::time_doatmos_phy_ae
logical, public time_doatmos_phy_ae
execute physics in this step? (aerosol )
Definition: mod_admin_time.F90:55
mod_cpl_vars::cpl_getsfc_atm
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_SHEX, SFLX_LHEX, SFLX_QVEX, SFLX_GH, SFLX_QTRC, SFLX_ENGI, U10, V10, T2, Q2)
Definition: mod_cpl_vars.F90:1150
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_basepoint_lon
real(rp), public atmos_grid_cartesc_real_basepoint_lon
position of base point in real world [rad,0-2pi]
Definition: scale_atmos_grid_cartesC_real.F90:36
scale_atmos_refstate::atmos_refstate_update
subroutine, public atmos_refstate_update(KA, KS, KE, IA, IS, IE, ISB, IEB, JA, JS, JE, JSB, JEB, DENS, POTT, TEMP, PRES, QV, CZ, FZ, FDZ, RCDZ, REAL_CZ, REAL_FZ, REAL_PHI, AREA, nowsec)
Update reference state profile (Horizontal average)
Definition: scale_atmos_refstate.F90:644
mod_atmos_phy_bl_driver::atmos_phy_bl_driver_calc_tendency
subroutine, public atmos_phy_bl_driver_calc_tendency(update_flag)
calculate tendency
Definition: mod_atmos_phy_bl_driver.F90:409
scale_atmos_grid_cartesc_index::jeb
integer, public jeb
Definition: scale_atmos_grid_cartesC_index.F90:67
mod_atmos_phy_mp_driver
module atmosphere / physics / cloud microphysics
Definition: mod_atmos_phy_mp_driver.F90:12
mod_atmos_phy_ae_driver::atmos_phy_ae_driver_adjustment
subroutine, public atmos_phy_ae_driver_adjustment
adjustment
Definition: mod_atmos_phy_ae_driver.F90:165
mod_atmos_phy_tb_driver::atmos_phy_tb_driver_calc_tendency
subroutine, public atmos_phy_tb_driver_calc_tendency(update_flag)
calclate tendency
Definition: mod_atmos_phy_tb_driver.F90:203
mod_atmos_phy_cp_vars::atmos_phy_cp_sflx_rain
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
Definition: mod_atmos_phy_cp_vars.F90:63
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_qvex
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_qvex
Definition: mod_atmos_phy_sf_vars.F90:84
mod_atmos_admin::atmos_sw_phy_ae
logical, public atmos_sw_phy_ae
Definition: mod_atmos_admin.F90:53
mod_atmos_phy_sf_vars::atmos_phy_sf_u10
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_u10
Definition: mod_atmos_phy_sf_vars.F90:95
mod_atmos_phy_sf_driver::atmos_phy_sf_driver_calc_tendency
subroutine, public atmos_phy_sf_driver_calc_tendency(update_flag)
calculation tendency
Definition: mod_atmos_phy_sf_driver.F90:149
mod_cpl_vars::cpl_putatm
subroutine, public cpl_putatm(TEMP, PRES, W, U, V, DENS, QV, PBL, SFC_DENS, SFC_PRES, SFLX_rad_dn, cosSZA, SFLX_water, SFLX_ENGI, countup)
Definition: mod_cpl_vars.F90:596
mod_atmos_vars::rhou_tp
real(rp), dimension(:,:,:), allocatable, public rhou_tp
Definition: mod_atmos_vars.F90:117
mod_admin_time::time_doatmos_phy_sf
logical, public time_doatmos_phy_sf
execute physics in this step? (surface flux)
Definition: mod_admin_time.F90:51
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
mod_atmos_driver::atmos_driver_boundary_update
subroutine atmos_driver_boundary_update
Definition: mod_atmos_driver.F90:756
scale_atmos_grid_cartesc_index::ie
integer, public ie
end point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:54
mod_atmos_phy_cp_vars::atmos_phy_cp_sflx_snow
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_snow
Definition: mod_atmos_phy_cp_vars.F90:64
mod_atmos_vars::prec
real(rp), dimension(:,:), allocatable, target, public prec
Definition: mod_atmos_vars.F90:145
scale_io
module STDIO
Definition: scale_io.F90:10
mod_atmos_phy_lt_driver::atmos_phy_lt_driver_finalize
subroutine, public atmos_phy_lt_driver_finalize
Definition: mod_atmos_phy_lt_driver.F90:251
mod_atmos_phy_bl_vars
module atmosphere / physics / PBL
Definition: mod_atmos_phy_bl_vars.F90:12
mod_atmos_vars::dens
real(rp), dimension(:,:,:), allocatable, target, public dens
Definition: mod_atmos_vars.F90:76
mod_atmos_dyn_driver
module Atmosphere / Dynamics
Definition: mod_atmos_dyn_driver.F90:11
mod_atmos_phy_lt_driver
module ATMOSPHERE / Physics Chemistry
Definition: mod_atmos_phy_lt_driver.F90:12
scale_atmos_grid_cartesc_index
module atmosphere / grid / cartesC index
Definition: scale_atmos_grid_cartesC_index.F90:12
scale_atmos_grid_cartesc_index::ia
integer, public ia
Definition: scale_atmos_grid_cartesC_index.F90:48
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_shex
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_shex
Definition: mod_atmos_phy_sf_vars.F90:82
mod_atmos_driver::atmos_driver_finalize
subroutine, public atmos_driver_finalize(init)
Finalize.
Definition: mod_atmos_driver.F90:523
mod_atmos_phy_sf_vars::atmos_phy_sf_sfc_albedo
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_sf_sfc_albedo
Definition: mod_atmos_phy_sf_vars.F90:66
mod_atmos_phy_lt_driver::atmos_phy_lt_driver_adjustment
subroutine, public atmos_phy_lt_driver_adjustment
Driver.
Definition: mod_atmos_phy_lt_driver.F90:282
mod_atmos_driver::atmos_driver_update
subroutine, public atmos_driver_update
advance atmospheric state
Definition: mod_atmos_driver.F90:397
mod_atmos_phy_sf_driver::atmos_phy_sf_driver_setup
subroutine, public atmos_phy_sf_driver_setup
Setup.
Definition: mod_atmos_phy_sf_driver.F90:54
mod_atmos_admin::atmos_sw_phy_lt
logical, public atmos_sw_phy_lt
Definition: mod_atmos_admin.F90:60
mod_atmos_phy_mp_driver::atmos_phy_mp_user_qhyd2qtrc
procedure(qhyd2qtrc), pointer, public atmos_phy_mp_user_qhyd2qtrc
Definition: mod_atmos_phy_mp_driver.F90:55
mod_atmos_phy_ch_driver::atmos_phy_ch_driver_finalize
subroutine, public atmos_phy_ch_driver_finalize
finalize
Definition: mod_atmos_phy_ch_driver.F90:144
mod_atmos_phy_bl_driver::atmos_phy_bl_driver_finalize
subroutine, public atmos_phy_bl_driver_finalize
Finalize.
Definition: mod_atmos_phy_bl_driver.F90:158
mod_atmos_phy_mp_driver::atmos_phy_mp_driver_tracer_setup
subroutine, public atmos_phy_mp_driver_tracer_setup
Config.
Definition: mod_atmos_phy_mp_driver.F90:94
mod_admin_time::time_doatmos_phy_rd
logical, public time_doatmos_phy_rd
execute physics in this step? (radiation )
Definition: mod_admin_time.F90:50
mod_atmos_phy_tb_driver::atmos_phy_tb_driver_tracer_setup
subroutine, public atmos_phy_tb_driver_tracer_setup
Tracer setup.
Definition: mod_atmos_phy_tb_driver.F90:56
mod_atmos_vars::v
real(rp), dimension(:,:,:), allocatable, target, public v
Definition: mod_atmos_vars.F90:131
mod_atmos_bnd_driver
module ATMOSPHERE / Boundary treatment
Definition: mod_atmos_bnd_driver.F90:13
mod_atmos_vars::w
real(rp), dimension(:,:,:), allocatable, target, public w
Definition: mod_atmos_vars.F90:129
scale_prof
module profiler
Definition: scale_prof.F90:11
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_area
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_area
horizontal area ( xy, normal z) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:66
mod_atmos_vars::momz_tp
real(rp), dimension(:,:,:), allocatable, public momz_tp
Definition: mod_atmos_vars.F90:116
mod_atmos_phy_mp_driver::atmos_phy_mp_driver_adjustment
subroutine, public atmos_phy_mp_driver_adjustment
adjustment
Definition: mod_atmos_phy_mp_driver.F90:496
scale_atmos_grid_cartesc_index::is
integer, public is
start point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:53
mod_atmos_phy_tb_driver
module ATMOSPHERE / Physics Turbulence
Definition: mod_atmos_phy_tb_driver.F90:12
mod_atmos_admin::atmos_sw_phy_cp
logical, public atmos_sw_phy_cp
Definition: mod_atmos_admin.F90:59
mod_atmos_admin::atmos_sw_phy_ch
logical, public atmos_sw_phy_ch
Definition: mod_atmos_admin.F90:54
mod_atmos_vars::temp
real(rp), dimension(:,:,:), allocatable, target, public temp
Definition: mod_atmos_vars.F90:134
mod_atmos_vars::dens_tp
real(rp), dimension(:,:,:), allocatable, public dens_tp
Definition: mod_atmos_vars.F90:115
scale_atmos_grid_cartesc_index::ja
integer, public ja
Definition: scale_atmos_grid_cartesC_index.F90:49
mod_atmos_phy_tb_driver::atmos_phy_tb_driver_setup
subroutine, public atmos_phy_tb_driver_setup
Setup.
Definition: mod_atmos_phy_tb_driver.F90:97
scale_time
module TIME
Definition: scale_time.F90:11
mod_atmos_vars::qv
real(rp), dimension(:,:,:), allocatable, pointer, target, public qv
Definition: mod_atmos_vars.F90:97
mod_atmos_admin::atmos_use_qv
logical, public atmos_use_qv
Definition: mod_atmos_admin.F90:48
mod_atmos_phy_mp_driver::atmos_phy_mp_driver_finalize
subroutine, public atmos_phy_mp_driver_finalize
finalize
Definition: mod_atmos_phy_mp_driver.F90:460
mod_atmos_dyn_driver::atmos_dyn_driver
subroutine, public atmos_dyn_driver(do_flag)
Dynamical Process (Wrapper)
Definition: mod_atmos_dyn_driver.F90:242
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_qtrc
real(rp), dimension(:,:,:), allocatable, target, public atmos_phy_sf_sflx_qtrc
Definition: mod_atmos_phy_sf_vars.F90:86
mod_atmos_phy_cp_driver
module ATMOSPHERE / Physics Cumulus
Definition: mod_atmos_phy_cp_driver.F90:12
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_lhex
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_lhex
Definition: mod_atmos_phy_sf_vars.F90:83
mod_atmos_phy_rd_driver
module ATMOSPHERE / Physics Radiation
Definition: mod_atmos_phy_rd_driver.F90:12
mod_atmos_phy_ae_driver::atmos_phy_ae_driver_tracer_setup
subroutine, public atmos_phy_ae_driver_tracer_setup
Setup.
Definition: mod_atmos_phy_ae_driver.F90:51
mod_atmos_dyn_driver::atmos_dyn_driver_setup
subroutine, public atmos_dyn_driver_setup
Setup.
Definition: mod_atmos_dyn_driver.F90:91
mod_atmos_vars::pres
real(rp), dimension(:,:,:), allocatable, target, public pres
Definition: mod_atmos_vars.F90:135
mod_atmos_phy_sf_driver
module ATMOSPHERE / Physics Surface fluxes
Definition: mod_atmos_phy_sf_driver.F90:12
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_engi
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_engi
Definition: mod_atmos_phy_sf_vars.F90:87
mod_atmos_admin::atmos_sw_phy_rd
logical, public atmos_sw_phy_rd
Definition: mod_atmos_admin.F90:55
mod_atmos_phy_mp_driver::atmos_phy_mp_driver_setup
subroutine, public atmos_phy_mp_driver_setup
Setup.
Definition: mod_atmos_phy_mp_driver.F90:227
mod_admin_time
module ADMIN TIME
Definition: mod_admin_time.F90:11
mod_atmos_vars::u
real(rp), dimension(:,:,:), allocatable, target, public u
Definition: mod_atmos_vars.F90:130
scale_atmos_grid_cartesc_index::ks
integer, public ks
start point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:51
mod_atmos_phy_bl_driver
module atmosphere / physics / PBL
Definition: mod_atmos_phy_bl_driver.F90:12
mod_atmos_phy_sf_vars::atmos_phy_sf_t2
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_t2
Definition: mod_atmos_phy_sf_vars.F90:97
mod_atmos_phy_cp_driver::atmos_phy_cp_driver_setup
subroutine, public atmos_phy_cp_driver_setup
Setup.
Definition: mod_atmos_phy_cp_driver.F90:50
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_lh
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_lh
Definition: mod_atmos_phy_sf_vars.F90:81
mod_atmos_phy_ch_driver
module ATMOSPHERE / Physics Chemistry
Definition: mod_atmos_phy_ch_driver.F90:12
mod_atmos_phy_mp_driver::atmos_phy_mp_driver_calc_tendency
subroutine, public atmos_phy_mp_driver_calc_tendency(update_flag)
calculate tendency
Definition: mod_atmos_phy_mp_driver.F90:651
mod_atmos_vars::rhoh_p
real(rp), dimension(:,:,:), allocatable, public rhoh_p
Definition: mod_atmos_vars.F90:120
scale_atmos_grid_cartesc::atmos_grid_cartesc_fz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fz
face coordinate [m]: z, local
Definition: scale_atmos_grid_cartesC.F90:42
mod_atmos_driver::atmos_surface_set
subroutine, public atmos_surface_set(countup)
Set surface boundary condition.
Definition: mod_atmos_driver.F90:638
mod_atmos_driver::atmos_driver_setup
subroutine, public atmos_driver_setup(init)
Setup.
Definition: mod_atmos_driver.F90:111
scale_time::time_dtsec
real(dp), public time_dtsec
time interval of model [sec]
Definition: scale_time.F90:33
mod_atmos_vars
module ATMOSPHERIC Variables
Definition: mod_atmos_vars.F90:12
scale_atmos_bottom
module atmosphere / bottom boundary extrapolation
Definition: scale_atmos_bottom.F90:12
mod_atmos_phy_ae_driver
module ATMOSPHERE / Physics Aerosol Microphysics
Definition: mod_atmos_phy_ae_driver.F90:12
scale_time::time_nowdate
integer, dimension(6), public time_nowdate
current time [YYYY MM DD HH MM SS]
Definition: scale_time.F90:68
mod_atmos_vars::rhot_tp
real(rp), dimension(:,:,:), allocatable, public rhot_tp
Definition: mod_atmos_vars.F90:119
mod_atmos_driver::atmos_surface_get
subroutine, public atmos_surface_get
Get surface boundary condition.
Definition: mod_atmos_driver.F90:577
scale_atmos_grid_cartesc_index::js
integer, public js
start point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:55
mod_atmos_phy_cp_driver::atmos_phy_cp_driver_finalize
subroutine, public atmos_phy_cp_driver_finalize
finalize
Definition: mod_atmos_phy_cp_driver.F90:106
mod_atmos_phy_mp_vars::atmos_phy_mp_sflx_snow
real(rp), dimension(:,:), allocatable, public atmos_phy_mp_sflx_snow
Definition: mod_atmos_phy_mp_vars.F90:75
mod_atmos_vars::momy_tp
real(rp), dimension(:,:,:), allocatable, public momy_tp
Definition: mod_atmos_vars.F90:125
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_sh
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_sh
Definition: mod_atmos_phy_sf_vars.F90:80
scale_atmos_refstate::atmos_refstate_finalize
subroutine, public atmos_refstate_finalize
Definition: scale_atmos_refstate.F90:220
mod_atmos_phy_cp_driver::atmos_phy_cp_driver_calc_tendency
subroutine, public atmos_phy_cp_driver_calc_tendency(update_flag)
Driver.
Definition: mod_atmos_phy_cp_driver.F90:132
mod_atmos_admin::atmos_sw_phy_bl
logical, public atmos_sw_phy_bl
Definition: mod_atmos_admin.F90:58
scale_atmos_grid_cartesc_index::ieb
integer, public ieb
Definition: scale_atmos_grid_cartesC_index.F90:65
scale_atmos_hydrometeor::atmos_hydrometeor_regist
subroutine, public atmos_hydrometeor_regist(NL, NI, NAME, DESC, UNIT, Q0, ADVC)
ATMOS_HYDROMETEOR_regist Regist tracer.
Definition: scale_atmos_hydrometeor.F90:279
mod_atmos_vars::momx_tp
real(rp), dimension(:,:,:), allocatable, public momx_tp
Definition: mod_atmos_vars.F90:124
mod_atmos_phy_rd_driver::atmos_phy_rd_driver_finalize
subroutine, public atmos_phy_rd_driver_finalize
finalize
Definition: mod_atmos_phy_rd_driver.F90:137
mod_admin_time::time_doatmos_phy_bl
logical, public time_doatmos_phy_bl
execute physics in this step? (boudary layer )
Definition: mod_admin_time.F90:53
mod_atmos_vars::atmos_vars_calc_diagnostics
subroutine, public atmos_vars_calc_diagnostics
Calc diagnostic variables.
Definition: mod_atmos_vars.F90:1747
mod_atmos_phy_sf_vars::atmos_phy_sf_q2
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_q2
Definition: mod_atmos_phy_sf_vars.F90:98
mod_admin_time::time_doatmos_phy_lt
logical, public time_doatmos_phy_lt
execute physics in this step? (lightning )
Definition: mod_admin_time.F90:56
scale_prof::prof_rapend
subroutine, public prof_rapend(rapname_base, level, disable_barrier)
Save raptime.
Definition: scale_prof.F90:246
mod_atmos_phy_mp_vars::qe_mp
integer, public qe_mp
Definition: mod_atmos_phy_mp_vars.F90:80
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_phi
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_phi
geopotential [m2/s2] (cell center)
Definition: scale_atmos_grid_cartesC_real.F90:64
mod_atmos_phy_lt_driver::atmos_phy_lt_driver_tracer_setup
subroutine, public atmos_phy_lt_driver_tracer_setup
Config.
Definition: mod_atmos_phy_lt_driver.F90:72
mod_atmos_phy_rd_driver::atmos_phy_rd_driver_setup
subroutine, public atmos_phy_rd_driver_setup
Setup.
Definition: mod_atmos_phy_rd_driver.F90:53
mod_atmos_phy_mp_driver::atmos_phy_mp_driver_qhyd2qtrc_onlyqv
subroutine, public atmos_phy_mp_driver_qhyd2qtrc_onlyqv(KA, KS, KE, IA, IS, IE, JA, JS, JE, QV, QHYD, QTRC, QNUM)
Definition: mod_atmos_phy_mp_driver.F90:1669
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_fz
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fz
geopotential height [m] (wxy)
Definition: scale_atmos_grid_cartesC_real.F90:43
mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_gh
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_gh
Definition: mod_atmos_phy_sf_vars.F90:85
scale_atmos_grid_cartesc
module atmosphere / grid / cartesC
Definition: scale_atmos_grid_cartesC.F90:12
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdz
z-length of grid(i+1) to grid(i) [m]
Definition: scale_atmos_grid_cartesC.F90:44
scale_atmos_grid_cartesc::atmos_grid_cartesc_cz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cz
center coordinate [m]: z, local
Definition: scale_atmos_grid_cartesC.F90:41
scale_atmos_refstate::atmos_refstate_setup
subroutine, public atmos_refstate_setup(KA, KS, KE, IA, IS, IE, JA, JS, JE, CZ, FZ, REAL_CZ, REAL_FZ, REAL_PHI)
Setup.
Definition: scale_atmos_refstate.F90:83
scale_atmos_grid_cartesc_index::jsb
integer, public jsb
Definition: scale_atmos_grid_cartesC_index.F90:66
mod_atmos_phy_ch_driver::atmos_phy_ch_driver_calc_tendency
subroutine, public atmos_phy_ch_driver_calc_tendency(update_flag)
Driver.
Definition: mod_atmos_phy_ch_driver.F90:170
mod_atmos_phy_cp_vars
module Atmosphere / Physics Cumulus
Definition: mod_atmos_phy_cp_vars.F90:12
scale_atmos_grid_cartesc_index::je
integer, public je
end point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:56
mod_cpl_admin::cpl_sw
logical, public cpl_sw
Definition: mod_cpl_admin.F90:33
mod_atmos_phy_rd_driver::atmos_phy_rd_driver_calc_tendency
subroutine, public atmos_phy_rd_driver_calc_tendency(update_flag)
Driver.
Definition: mod_atmos_phy_rd_driver.F90:166
scale_atmos_bottom::atmos_bottom_estimate
subroutine, public atmos_bottom_estimate(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS, PRES, QV, SFC_TEMP, FZ, SFC_DENS, SFC_PRES)
Calc bottom boundary of atmosphere (just above surface)
Definition: scale_atmos_bottom.F90:51
mod_atmos_driver::atmos_driver_calc_tendency_from_sflux
subroutine, public atmos_driver_calc_tendency_from_sflux(force)
Calculation tendency from surface flux with coupler.
Definition: mod_atmos_driver.F90:354
mod_cpl_admin
module Coupler admin
Definition: mod_cpl_admin.F90:11
mod_atmos_driver::atmos_driver_calc_tendency
subroutine, public atmos_driver_calc_tendency(force)
Calculation tendency.
Definition: mod_atmos_driver.F90:199
mod_atmos_phy_ae_driver::atmos_phy_ae_driver_calc_tendency
subroutine, public atmos_phy_ae_driver_calc_tendency(update_flag)
Driver.
Definition: mod_atmos_phy_ae_driver.F90:194
mod_atmos_phy_lt_driver::atmos_phy_lt_driver_setup
subroutine, public atmos_phy_lt_driver_setup
Setup.
Definition: mod_atmos_phy_lt_driver.F90:159
mod_atmos_phy_tb_driver::atmos_phy_tb_driver_finalize
subroutine, public atmos_phy_tb_driver_finalize
finalize
Definition: mod_atmos_phy_tb_driver.F90:175
mod_atmos_admin::atmos_sw_phy_sf
logical, public atmos_sw_phy_sf
Definition: mod_atmos_admin.F90:56