SCALE-RM
mod_atmos_phy_mp_vars.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
20  use scale_debug
22  use scale_tracer
23  !-----------------------------------------------------------------------------
24  implicit none
25  private
26  !-----------------------------------------------------------------------------
27  !
28  !++ Public procedure
29  !
30  public :: atmos_phy_mp_vars_setup
34 
40 
42 
45 
46  !-----------------------------------------------------------------------------
47  !
48  !++ Public parameters & variables
49  !
50  logical, public :: atmos_phy_mp_restart_output = .false.
51 
52  character(len=H_LONG), public :: atmos_phy_mp_restart_in_basename = ''
54  logical, public :: atmos_phy_mp_restart_in_postfix_timelabel = .false.
55  character(len=H_LONG), public :: atmos_phy_mp_restart_out_basename = ''
57  logical, public :: atmos_phy_mp_restart_out_postfix_timelabel = .true.
58  character(len=H_MID), public :: atmos_phy_mp_restart_out_title = 'ATMOS_PHY_MP restart'
59  character(len=H_SHORT), public :: atmos_phy_mp_restart_out_dtype = 'DEFAULT'
60 
62 
63  real(rp), public, allocatable :: atmos_phy_mp_dens_t(:,:,:) ! tendency DENS [kg/m3/s]
64  real(rp), public, allocatable :: atmos_phy_mp_momz_t(:,:,:) ! tendency MOMZ [kg/m2/s2]
65  real(rp), public, allocatable :: atmos_phy_mp_rhou_t(:,:,:) ! tendency dens*U [kg/m2/s2]
66  real(rp), public, allocatable :: atmos_phy_mp_rhov_t(:,:,:) ! tendency dens*V [kg/m2/s2]
67  real(rp), public, allocatable :: atmos_phy_mp_rhot_t(:,:,:) ! tendency RHOT [K*kg/m3/s]
68  real(rp), public, allocatable :: atmos_phy_mp_rhoq_t(:,:,:,:) ! tendency rho*QTRC [kg/m3/s]
69  real(rp), public, allocatable :: atmos_phy_mp_rhoc_t(:,:,:,:) ! tendency rho*QTRC (charge) [fC/m3/s]
70  real(rp), public, allocatable :: atmos_phy_mp_rhoh (:,:,:) ! diabatic heating rate [J/kg/s]
71 
72  real(rp), public, allocatable :: atmos_phy_mp_evaporate(:,:,:) ! number concentration of evaporated cloud [/m3]
73  real(rp), public, allocatable :: atmos_phy_mp_sflx_rain(:,:) ! precipitation flux (liquid) [kg/m2/s]
74  real(rp), public, allocatable :: atmos_phy_mp_sflx_snow(:,:) ! precipitation flux (solid) [kg/m2/s]
75  real(rp), public, allocatable :: atmos_phy_mp_sflx_engi(:,:) ! internal energy flux [J/m2/s]
76 
77  integer, public :: qa_mp = 0
78  integer, public :: qs_mp = -1
79  integer, public :: qe_mp = -2
80 
81  !-----------------------------------------------------------------------------
82  !
83  !++ Private procedure
84  !
85  !-----------------------------------------------------------------------------
86  !
87  !++ Private parameters & variables
88  !
89  integer, private, parameter :: vmax = 0
90 
91  character(len=H_SHORT), private :: var_name(vmax)
92  character(len=H_MID), private :: var_desc(vmax)
93  character(len=H_SHORT), private :: var_unit(vmax)
94  integer, private :: var_id(vmax)
95  integer, private :: restart_fid = -1 ! file ID
96 
97 ! data VAR_NAME / /
98 ! data VAR_DESC / /
99 ! data VAR_UNIT / /
100 
101 
102  ! for diagnostics
103  real(rp), private, allocatable :: atmos_phy_mp_cldfrac(:,:,:)
104  real(rp), private, allocatable :: atmos_phy_mp_re (:,:,:,:)
105  real(rp), private, allocatable :: atmos_phy_mp_qe (:,:,:,:)
106  real(rp), private, allocatable :: atmos_phy_mp_ne (:,:,:,:)
107  logical, private :: diag_cldfrac
108  logical, private :: diag_re
109  logical, private :: diag_qe
110  logical, private :: diag_ne
111 
112  ! for history
113  integer, private :: hist_cldfrac_id
114  logical, private :: hist_re
115  logical, private :: hist_qe
116  logical, private :: hist_ne
117  integer, private, allocatable :: hist_re_id(:)
118  integer, private, allocatable :: hist_qe_id(:)
119  integer, private, allocatable :: hist_ne_id(:)
120 
121  !-----------------------------------------------------------------------------
122 contains
123  !-----------------------------------------------------------------------------
125  subroutine atmos_phy_mp_vars_setup
126  use scale_prc, only: &
127  prc_abort
128  use scale_const, only: &
129  undef => const_undef
130  use scale_atmos_hydrometeor, only: &
131  n_hyd, &
132  qha, &
133  hyd_name, &
134  num_name, &
135  hyd_desc
136  use scale_file_history, only: &
138  implicit none
139 
140  namelist / param_atmos_phy_mp_vars / &
150 
151  integer :: ierr
152  integer :: iv, ih
153  !---------------------------------------------------------------------------
154 
155  log_newline
156  log_info("ATMOS_PHY_MP_vars_setup",*) 'Setup'
157 
158  allocate( atmos_phy_mp_dens_t(ka,ia,ja) )
159  allocate( atmos_phy_mp_momz_t(ka,ia,ja) )
160  allocate( atmos_phy_mp_rhou_t(ka,ia,ja) )
161  allocate( atmos_phy_mp_rhov_t(ka,ia,ja) )
162  allocate( atmos_phy_mp_rhot_t(ka,ia,ja) )
163  allocate( atmos_phy_mp_rhoq_t(ka,ia,ja,qs_mp:qe_mp) )
164  allocate( atmos_phy_mp_rhoh(ka,ia,ja) )
165  allocate( atmos_phy_mp_evaporate(ka,ia,ja) )
166  ! tentative approach
167  atmos_phy_mp_dens_t(:,:,:) = 0.0_rp
168  atmos_phy_mp_momz_t(:,:,:) = 0.0_rp
169  atmos_phy_mp_rhou_t(:,:,:) = 0.0_rp
170  atmos_phy_mp_rhov_t(:,:,:) = 0.0_rp
171  atmos_phy_mp_rhot_t(:,:,:) = 0.0_rp
172  atmos_phy_mp_rhoq_t(:,:,:,:) = 0.0_rp
173  atmos_phy_mp_rhoh(:,:,:) = 0.0_rp
174  atmos_phy_mp_evaporate(:,:,:) = 0.0_rp
175 
176  allocate( atmos_phy_mp_sflx_rain(ia,ja) )
177  allocate( atmos_phy_mp_sflx_snow(ia,ja) )
178  allocate( atmos_phy_mp_sflx_engi(ia,ja) )
179  atmos_phy_mp_sflx_rain(:,:) = undef
180  atmos_phy_mp_sflx_snow(:,:) = undef
181  atmos_phy_mp_sflx_engi(:,:) = undef
182 
183  !--- read namelist
184  rewind(io_fid_conf)
185  read(io_fid_conf,nml=param_atmos_phy_mp_vars,iostat=ierr)
186  if( ierr < 0 ) then !--- missing
187  log_info("ATMOS_PHY_MP_vars_setup",*) 'Not found namelist. Default used.'
188  elseif( ierr > 0 ) then !--- fatal error
189  log_error("ATMOS_PHY_MP_vars_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_PHY_MP_VARS. Check!'
190  call prc_abort
191  endif
192  log_nml(param_atmos_phy_mp_vars)
193 
194  log_newline
195  log_info("ATMOS_PHY_MP_vars_setup",*) '[ATMOS_PHY_MP] prognostic/diagnostic variables'
196  log_info_cont('(1x,A,A24,A,A48,A,A12,A)') &
197  ' |', 'VARNAME ','|', &
198  'DESCRIPTION ', '[', 'UNIT ', ']'
199  do iv = 1, vmax
200  log_info_cont('(1x,A,I3,A,A24,A,A48,A,A12,A)') &
201  'NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
202  enddo
203 
204  log_newline
205  if ( atmos_phy_mp_restart_in_basename /= '' ) then
206  log_info("ATMOS_PHY_MP_vars_setup",*) 'Restart input? : YES, file = ', trim(atmos_phy_mp_restart_in_basename)
207  log_info("ATMOS_PHY_MP_vars_setup",*) 'Add timelabel? : ', atmos_phy_mp_restart_in_postfix_timelabel
208  else
209  log_info("ATMOS_PHY_MP_vars_setup",*) 'Restart input? : NO'
210  endif
212  .AND. atmos_phy_mp_restart_out_basename /= '' ) then
213  log_info("ATMOS_PHY_MP_vars_setup",*) 'Restart output? : YES, file = ', trim(atmos_phy_mp_restart_out_basename)
214  log_info("ATMOS_PHY_MP_vars_setup",*) 'Add timelabel? : ', atmos_phy_mp_restart_out_postfix_timelabel
215  else
216  log_info("ATMOS_PHY_MP_vars_setup",*) 'Restart output? : NO'
218  endif
219 
220 
221  ! diagnostices
222  allocate( atmos_phy_mp_cldfrac(ka,ia,ja) )
223  allocate( atmos_phy_mp_re(ka,ia,ja,n_hyd) )
224  allocate( atmos_phy_mp_qe(ka,ia,ja,n_hyd) )
225  allocate( atmos_phy_mp_ne(ka,ia,ja,n_hyd) )
226 !OCL XFILL
227  atmos_phy_mp_cldfrac(:,:,:) = undef
228 !OCL XFILL
229  atmos_phy_mp_re(:,:,:,:) = undef
230 !OCL XFILL
231  atmos_phy_mp_qe(:,:,:,:) = undef
232  atmos_phy_mp_ne(:,:,:,:) = undef
233  diag_cldfrac = .false.
234  diag_re = .false.
235  diag_qe = .false.
236  diag_ne = .false.
237 
238  ! history
239  allocate( hist_re_id(n_hyd) )
240  allocate( hist_qe_id(n_hyd) )
241  allocate( hist_ne_id(n_hyd) )
242 
243  call file_history_reg( 'CLDFRAC', 'cloud fraction', '1', hist_cldfrac_id, fill_halo=.true., dim_type='ZXY' )
244 
245  hist_re = .false.
246  do ih = 1, n_hyd
247  call file_history_reg( 'Re_'//trim(hyd_name(ih)), 'effective radius of '//trim(hyd_desc(ih)), 'cm', hist_re_id(ih), fill_halo=.true., dim_type='ZXY' )
248  if( hist_re_id(ih) > 0 ) hist_re = .true.
249  enddo
250 
251  hist_qe = .false.
252  do ih = 1, n_hyd
253  call file_history_reg( trim(hyd_name(ih))//'_hyd', 'mass ratio of '//trim(hyd_desc(ih)), 'kg/kg', hist_qe_id(ih), fill_halo=.true., dim_type='ZXY' )
254  if( hist_qe_id(ih) > 0 ) hist_qe = .true.
255  enddo
256 
257  hist_ne = .false.
258  do ih = 1, n_hyd
259  call file_history_reg( trim(num_name(ih))//'_hyd', 'number concentration of '//trim(hyd_desc(ih)), '1/m3', hist_ne_id(ih), fill_halo=.true., dim_type='ZXY' )
260  if( hist_ne_id(ih) > 0 ) hist_ne = .true.
261  enddo
262 
263  return
264  end subroutine atmos_phy_mp_vars_setup
265 
266  !-----------------------------------------------------------------------------
268  subroutine atmos_phy_mp_vars_fillhalo
269  use scale_comm_cartesc, only: &
270  comm_vars8, &
271  comm_wait
272  implicit none
273  !---------------------------------------------------------------------------
274 
275  call comm_vars8( atmos_phy_mp_sflx_rain(:,:), 1 )
276  call comm_vars8( atmos_phy_mp_sflx_snow(:,:), 2 )
277  call comm_vars8( atmos_phy_mp_sflx_engi(:,:), 3 )
278  call comm_wait ( atmos_phy_mp_sflx_rain(:,:), 1 )
279  call comm_wait ( atmos_phy_mp_sflx_snow(:,:), 2 )
280  call comm_wait ( atmos_phy_mp_sflx_engi(:,:), 3 )
281 
282  return
283  end subroutine atmos_phy_mp_vars_fillhalo
284 
285  !-----------------------------------------------------------------------------
288  use scale_time, only: &
290  use scale_file_cartesc, only: &
292  implicit none
293 
294  character(len=19) :: timelabel
295  character(len=H_LONG) :: basename
296  !---------------------------------------------------------------------------
297 
298 !!$ LOG_NEWLINE
299 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_open",*) 'Open restart file (ATMOS_PHY_MP) '
300 !!$
301 !!$ if ( ATMOS_PHY_MP_RESTART_IN_BASENAME /= '' ) then
302 !!$
303 !!$ if ( ATMOS_PHY_MP_RESTART_IN_POSTFIX_TIMELABEL ) then
304 !!$ call TIME_gettimelabel( timelabel )
305 !!$ basename = trim(ATMOS_PHY_MP_RESTART_IN_BASENAME)//'_'//trim(timelabel)
306 !!$ else
307 !!$ basename = trim(ATMOS_PHY_MP_RESTART_IN_BASENAME)
308 !!$ endif
309 !!$
310 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_open",*) 'basename: ', trim(basename)
311 !!$
312 !!$ call FILE_CARTESC_open( basename, restart_fid, aggregate=ATMOS_PHY_MP_RESTART_IN_AGGREGATE )
313 !!$ else
314 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_open",*) 'restart file for ATMOS_PHY_MP is not specified.'
315 !!$ endif
316 
317  return
318  end subroutine atmos_phy_mp_vars_restart_open
319 
320  !-----------------------------------------------------------------------------
323  use scale_file, only: &
325  use scale_file_cartesc, only: &
326  file_cartesc_read, &
328  implicit none
329 
330  !---------------------------------------------------------------------------
331 
332 !!$ if ( restart_fid /= -1 ) then
333 !!$ LOG_NEWLINE
334 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_read",*) 'Read from restart file (ATMOS_PHY_MP) '
335 !!$
336 !!$ call FILE_CARTESC_read( restart_fid, VAR_NAME(1), 'XY', & ! [IN]
337 !!$ ATMOS_PHY_MP_hoge(:,:) ) ! [OUT]
338 !!$
339 !!$ if ( FILE_get_AGGREGATE(restart_fid) ) then
340 !!$ call FILE_CARTESC_flush( restart_fid ) ! X/Y halos have been read from file
341 !!$ else
342 !!$ call ATMOS_PHY_MP_vars_fillhalo
343 !!$ end if
344 !!$
345 !!$ call ATMOS_PHY_MP_vars_check
346 !!$
347 !!$ else
348 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_read",*) 'invalid restart file ID for ATMOS_PHY_MP.'
349 !!$ endif
350 
351  return
352  end subroutine atmos_phy_mp_vars_restart_read
353 
354  !-----------------------------------------------------------------------------
357  use scale_time, only: &
359  use scale_file_cartesc, only: &
361  implicit none
362 
363  character(len=19) :: timelabel
364  character(len=H_LONG) :: basename
365  !---------------------------------------------------------------------------
366 
367 !!$ if ( ATMOS_PHY_MP_RESTART_OUT_BASENAME /= '' ) then
368 !!$
369 !!$ LOG_NEWLINE
370 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_create",*) 'Create restart file (ATMOS_PHY_AE) '
371 !!$
372 !!$ if ( ATMOS_PHY_MP_RESTART_OUT_POSTFIX_TIMELABEL ) then
373 !!$ call TIME_gettimelabel( timelabel )
374 !!$ basename = trim(ATMOS_PHY_MP_RESTART_OUT_BASENAME)//'_'//trim(timelabel)
375 !!$ else
376 !!$ basename = trim(ATMOS_PHY_MP_RESTART_OUT_BASENAME)
377 !!$ endif
378 !!$
379 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_create",*) 'basename: ', trim(basename)
380 !!$
381 !!$ call FILE_CARTESC_create( &
382 !!$ basename, ATMOS_PHY_MP_RESTART_OUT_TITLE, ATMOS_PHY_MP_RESTART_OUT_DTYPE, & ! [IN]
383 !!$ restart_fid, & ! [OUT]
384 !!$ aggregate=ATMOS_PHY_MP_RESTART_OUT_AGGREGATE ) ! [IN]
385 !!$
386 !!$ endif
387 
388  return
389  end subroutine atmos_phy_mp_vars_restart_create
390 
391  !-----------------------------------------------------------------------------
394  use scale_file_cartesc, only: &
396  implicit none
397 
398 !!$ if ( restart_fid /= -1 ) then
399 !!$ call FILE_CARTESC_enddef( restart_fid ) ! [IN]
400 !!$ endif
401 
402  return
403  end subroutine atmos_phy_mp_vars_restart_enddef
404 
405  !-----------------------------------------------------------------------------
408  use scale_file_cartesc, only: &
410  implicit none
411  !---------------------------------------------------------------------------
412 
413 !!$ if ( restart_fid /= -1 ) then
414 !!$ LOG_NEWLINE
415 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_close",*) 'Close restart file (ATMOS_PHY_MP) '
416 !!$
417 !!$ call FILE_CARTESC_close( restart_fid ) ! [IN]
418 !!$
419 !!$ restart_fid = -1
420 !!$ endif
421 
422  return
423  end subroutine atmos_phy_mp_vars_restart_close
424 
425  !-----------------------------------------------------------------------------
428  use scale_file_cartesc, only: &
430  implicit none
431  integer :: iv
432  !---------------------------------------------------------------------------
433 
434 !!$ if ( restart_fid /= -1 ) then
435 !!$
436 !!$ do iv = 1, VMAX
437 !!$ call FILE_CARTESC_def_var( restart_fid, VAR_NAME(iv), VAR_DESC(iv), VAR_UNIT(iv), &
438 !!$ 'XY', ATMOS_PHY_MP_RESTART_OUT_DTYPE, &
439 !!$ VAR_ID(iv) )
440 !!$ end do
441 !!$
442 !!$ endif
443 
444  return
445  end subroutine atmos_phy_mp_vars_restart_def_var
446 
447  !-----------------------------------------------------------------------------
450  use scale_file_cartesc, only: &
451  file_cartesc_write_var
452  implicit none
453  !---------------------------------------------------------------------------
454 
455 !!$ if ( restart_fid /= -1 ) then
456 !!$
457 !!$ call ATMOS_PHY_MP_vars_fillhalo
458 !!$
459 !!$ call ATMOS_PHY_MP_vars_check
460 !!$
461 !!$ call FILE_CARTESC_write_var( restart_fid, VAR_ID(1), ATMOS_PHY_MP_hoge(:,:), &
462 !!$ VAR_NAME(1), 'XY' ) ! [IN]
463 !!$
464 !!$ endif
465 
466  return
467  end subroutine atmos_phy_mp_vars_restart_write
468 
469  !-----------------------------------------------------------------------------
470  subroutine atmos_phy_mp_vars_history( &
471  DENS, TEMP, QTRC )
473  n_hyd
474  use scale_file_history, only: &
475  file_history_query, &
476  file_history_put
477  use mod_atmos_admin, only: &
479  implicit none
480 
481  real(rp), intent(in) :: dens(ka,ia,ja)
482  real(rp), intent(in) :: temp(ka,ia,ja)
483  real(rp), intent(in) :: qtrc(ka,ia,ja,qa)
484 
485  real(rp) :: work (ka,ia,ja,n_hyd)
486  logical :: do_put
487  integer :: ih
488  !---------------------------------------------------------------------------
489 
490  if ( hist_cldfrac_id > 0 ) then
491  call file_history_query( hist_cldfrac_id, do_put )
492 
493  if ( do_put ) then
495  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,:), & ! [IN]
496  cldfrac=work(:,:,:,1) ) ! [OUT]
497  call file_history_put( hist_cldfrac_id, work(:,:,:,1) )
498  end if
499  end if
500 
501  if ( hist_re ) then
502  do ih = 1, n_hyd
503  if ( hist_re_id(ih) > 0 ) then
504  call file_history_query( hist_re_id(ih), do_put )
505  if ( do_put ) then
507  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,:), & ! [IN]
508  re=work(:,:,:,:) ) ! [OUT]
509  exit
510  end if
511  end if
512  end do
513  if ( do_put ) then
514  do ih = 1, n_hyd
515  if ( hist_re_id(ih) > 0 ) then
516  call file_history_query( hist_re_id(ih), do_put )
517  if ( do_put ) call file_history_put( hist_re_id(ih), work(:,:,:,ih) )
518  end if
519  end do
520  end if
521  end if
522 
523  if ( hist_qe ) then
524  do ih = 1, n_hyd
525  if ( hist_qe_id(ih) > 0 ) then
526  call file_history_query( hist_qe_id(ih), do_put )
527  if ( do_put ) then
529  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,:), & ! [IN]
530  qe=work(:,:,:,:) ) ! [OUT]
531  exit
532  end if
533  end if
534  end do
535  if ( do_put ) then
536  do ih = 1, n_hyd
537  if ( hist_qe_id(ih) > 0 ) then
538  call file_history_query( hist_qe_id(ih), do_put )
539  if( do_put ) call file_history_put( hist_qe_id(ih), work(:,:,:,ih) )
540  end if
541  end do
542  end if
543  end if
544 
545  if ( hist_ne ) then
546  do ih = 1, n_hyd
547  if ( hist_ne_id(ih) > 0 ) then
548  call file_history_query( hist_ne_id(ih), do_put )
549  if ( do_put ) then
551  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,:), & ! [IN]
552  ne=work(:,:,:,:) ) ! [OUT]
553  exit
554  end if
555  end if
556  end do
557  if ( do_put ) then
558  do ih = 1, n_hyd
559  if ( hist_ne_id(ih) > 0 ) then
560  call file_history_query( hist_ne_id(ih), do_put )
561  if( do_put ) call file_history_put( hist_ne_id(ih), work(:,:,:,ih) )
562  end if
563  end do
564  end if
565  end if
566 
567  return
568  end subroutine atmos_phy_mp_vars_history
569 
571  DENS, TEMP, QTRC, &
572  CLDFRAC, Re, Qe, Ne )
574  n_hyd, &
575  i_hc, &
576  i_hr, &
577  i_hi, &
578  i_hs, &
579  i_hg, &
580  i_hh
581  use scale_atmos_phy_mp_kessler, only: &
585  use scale_atmos_phy_mp_tomita08, only: &
589  use scale_atmos_phy_mp_sn14, only: &
594  use scale_atmos_phy_mp_suzuki10, only: &
599  use mod_atmos_admin, only: &
601  implicit none
602 
603  real(rp), intent(in) :: dens(ka,ia,ja)
604  real(rp), intent(in) :: temp(ka,ia,ja)
605  real(rp), intent(in) :: qtrc(ka,ia,ja,qa)
606  real(rp), intent(out), optional :: cldfrac(ka,ia,ja)
607  real(rp), intent(out), optional :: re (ka,ia,ja,n_hyd)
608  real(rp), intent(out), optional :: qe (ka,ia,ja,n_hyd)
609  real(rp), intent(out), optional :: ne (ka,ia,ja,n_hyd)
610 
611  integer :: k, i, j, ih
612 
613  if ( present(cldfrac) ) then
614  if ( .not. diag_cldfrac ) then
615  select case ( atmos_phy_mp_type )
616  case ( 'KESSLER' )
618  ka, ks, ke, ia, is, ie, ja, js, je, &
619  qtrc(:,:,:,qs_mp+1:qe_mp), atmos_phy_mp_cldfrac_thleshold, & ! [IN]
620  atmos_phy_mp_cldfrac(:,:,:) ) ! [OUT]
621  case ( 'TOMITA08' )
623  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
624  qtrc(:,:,:,qs_mp+1:qe_mp), atmos_phy_mp_cldfrac_thleshold, & ! [IN]
625  atmos_phy_mp_cldfrac(:,:,:) ) ! [OUT]
626  case ( 'SN14' )
628  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
629  qtrc(:,:,:,qs_mp+1:qe_mp), atmos_phy_mp_cldfrac_thleshold, & ! [IN]
630  atmos_phy_mp_cldfrac(:,:,:) ) ! [OUT]
631  case ( 'SUZUKI10' )
633  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
634  qtrc(:,:,:,qs_mp+1:qe_mp), atmos_phy_mp_cldfrac_thleshold, & ! [IN]
635  atmos_phy_mp_cldfrac(:,:,:) ) ! [OUT]
636  case default
637 !OCL XFILL
638  atmos_phy_mp_cldfrac(:,:,:) = 0.0_rp
639  end select
640  diag_cldfrac = .true.
641  end if
642 !OCL XFILL
643  do j = jsb, jeb
644  do i = isb, ieb
645  do k = ks, ke
646  cldfrac(k,i,j) = atmos_phy_mp_cldfrac(k,i,j)
647  end do
648  end do
649  end do
650  end if
651 
652  if ( present(re) ) then
653  if ( .not. diag_re ) then
654  select case ( atmos_phy_mp_type )
655  case ( 'KESSLER' )
657  ka, ks, ke, ia, is, ie, ja, js, je, &
658  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
659  atmos_phy_mp_re(:,:,:,:) ) ! [OUT]
660  case ( 'TOMITA08' )
662  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
663  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
664  atmos_phy_mp_re(:,:,:,:) ) ! [OUT]
665  case ( 'SN14' )
667  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
668  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
669  atmos_phy_mp_re(:,:,:,:) ) ! [OUT]
670  case ( 'SUZUKI10' )
672  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
673  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
674  atmos_phy_mp_re(:,:,:,:) ) ! [OUT]
675  case default
676 !OCL XFILL
677  atmos_phy_mp_re(:,:,:,:) = 0.0_rp
678  end select
679  diag_re = .true.
680  end if
681 !OCL XFILL
682  do ih = 1, n_hyd
683  do j = jsb, jeb
684  do i = isb, ieb
685  do k = ks, ke
686  re(k,i,j,ih) = atmos_phy_mp_re(k,i,j,ih)
687  end do
688  end do
689  end do
690  end do
691  end if
692 
693  if ( present(qe) ) then
694  if ( .not. diag_qe ) then
695  select case ( atmos_phy_mp_type )
696  case ( 'KESSLER' )
698  ka, ks, ke, ia, is, ie, ja, js, je, &
699  qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
700  atmos_phy_mp_qe(:,:,:,:) ) ! [OUT]
701  case ( 'TOMITA08' )
703  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
704  qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
705  atmos_phy_mp_qe(:,:,:,:) ) ! [OUT]
706  case ( 'SN14' )
708  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
709  qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
710  atmos_phy_mp_qe(:,:,:,:) ) ! [OUT]
711  case ( 'SUZUKI10' )
713  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
714  qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
715  atmos_phy_mp_qe(:,:,:,:) ) ! [OUT]
716  case default
717 !OCL XFILL
718  atmos_phy_mp_qe(:,:,:,:) = 0.0_rp
719  end select
720  diag_qe = .true.
721  end if
722 !OCL XFILL
723  do ih = 1, n_hyd
724  do j = jsb, jeb
725  do i = isb, ieb
726  do k = ks, ke
727  qe(k,i,j,ih) = atmos_phy_mp_qe(k,i,j,ih)
728  end do
729  end do
730  end do
731  end do
732  end if
733 
734  if ( present(ne) ) then
735  if ( .not. diag_ne ) then
736  select case ( atmos_phy_mp_type )
737  case ( 'KESSLER', 'TOMITA08' )
738  ! do nothing
739  case ( 'SN14' )
741  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
742  qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
743  atmos_phy_mp_ne(:,:,:,:) ) ! [OUT]
744  case ( 'SUZUKI10' )
746  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
747  dens(:,:,:), qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
748  atmos_phy_mp_ne(:,:,:,:) ) ! [OUT]
749  end select
750  diag_ne = .true.
751  end if
752 !OCL XFILL
753  do ih = 1, n_hyd
754  do j = jsb, jeb
755  do i = isb, ieb
756  do k = ks, ke
757  ne(k,i,j,ih) = atmos_phy_mp_ne(k,i,j,ih)
758  end do
759  end do
760  end do
761  end do
762  end if
763 
764  return
765  end subroutine atmos_phy_mp_vars_get_diagnostic
766 
768  diag_cldfrac = .false.
769  diag_re = .false.
770  diag_qe = .false.
771  diag_ne = .false.
772 
773  return
775 
776  subroutine atmos_phy_mp_vars_check
777  use scale_statistics, only: &
778  statistics_total
779  use scale_atmos_grid_cartesc_real, only: &
784  implicit none
785 
786 !!$ call VALCHECK( IA, IS, IE, JA, JS, JE, &
787 !!$ ATMOS_PHY_MP_hoge(:,:), & ! (in)
788 !!$ 0.0_RP, 0.0_RP, VAR_NAME(1), & ! (in)
789 !!$ __FILE__, __LINE__ ) ! (in)
790 !!$
791 !!$ call STATISTICS_total( IA, IS, IE, JA, JS, JE, &
792 !!$ ATMOS_PHY_MP_hoge(:,:), VAR_NAME(1), & ! (in)
793 !!$ ATMOS_GRID_CARTESC_REAL_AREA(:,:), & ! (in)
794 !!$ ATMOS_GRID_CARTESC_REAL_TOTAREA ) ! (in)
795 
796  return
797  end subroutine atmos_phy_mp_vars_check
798 
799 
800 end module mod_atmos_phy_mp_vars
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:75
scale_atmos_grid_cartesc_index::isb
integer, public isb
Definition: scale_atmos_grid_cartesC_index.F90:63
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_cloud_fraction
subroutine, public atmos_phy_mp_kessler_cloud_fraction(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC, mask_criterion, cldfrac)
Calculate Cloud Fraction.
Definition: scale_atmos_phy_mp_kessler.F90:392
scale_atmos_hydrometeor::num_name
character(len=h_short), dimension(n_hyd), parameter, public num_name
Definition: scale_atmos_hydrometeor.F90:92
scale_statistics
module Statistics
Definition: scale_statistics.F90:11
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_atmos_hydrometeor::hyd_desc
character(len=h_mid), dimension(n_hyd), parameter, public hyd_desc
Definition: scale_atmos_hydrometeor.F90:90
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
scale_atmos_hydrometeor::i_hr
integer, parameter, public i_hr
liquid water rain
Definition: scale_atmos_hydrometeor.F90:82
mod_atmos_phy_mp_vars::qa_mp
integer, public qa_mp
Definition: mod_atmos_phy_mp_vars.F90:77
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_get_diagnostic
subroutine, public atmos_phy_mp_vars_get_diagnostic(DENS, TEMP, QTRC, CLDFRAC, Re, Qe, Ne)
Definition: mod_atmos_phy_mp_vars.F90:573
scale_tracer::qa
integer, public qa
Definition: scale_tracer.F90:34
mod_atmos_phy_mp_vars::atmos_phy_mp_restart_in_postfix_timelabel
logical, public atmos_phy_mp_restart_in_postfix_timelabel
Add timelabel to the basename of input file?
Definition: mod_atmos_phy_mp_vars.F90:54
scale_atmos_hydrometeor::i_hs
integer, parameter, public i_hs
snow
Definition: scale_atmos_hydrometeor.F90:84
scale_atmos_hydrometeor::hyd_name
character(len=h_short), dimension(n_hyd), parameter, public hyd_name
Definition: scale_atmos_hydrometeor.F90:88
scale_atmos_phy_mp_tomita08
module atmosphere / physics / microphysics / Tomita08
Definition: scale_atmos_phy_mp_tomita08.F90:13
scale_file_cartesc::file_cartesc_enddef
subroutine, public file_cartesc_enddef(fid)
Exit netCDF file define mode.
Definition: scale_file_cartesC.F90:943
scale_file_cartesc::file_cartesc_def_var
subroutine, public file_cartesc_def_var(fid, varname, desc, unit, dim_type, datatype, vid, standard_name, timeintv, nsteps, cell_measures)
Define a variable to file.
Definition: scale_file_cartesC.F90:3307
mod_atmos_phy_mp_vars::atmos_phy_mp_momz_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_mp_momz_t
Definition: mod_atmos_phy_mp_vars.F90:64
scale_precision
module PRECISION
Definition: scale_precision.F90:14
scale_atmos_grid_cartesc_index::ka
integer, public ka
Definition: scale_atmos_grid_cartesC_index.F90:47
mod_atmos_admin
module ATMOS admin
Definition: mod_atmos_admin.F90:11
mod_atmos_phy_mp_vars::qs_mp
integer, public qs_mp
Definition: mod_atmos_phy_mp_vars.F90:78
scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_qtrc2qhyd
subroutine, public atmos_phy_mp_suzuki10_qtrc2qhyd(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC0, Qe)
Calculate mass ratio of each category.
Definition: scale_atmos_phy_mp_suzuki10.F90:1567
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totarea
real(rp), public atmos_grid_cartesc_real_totarea
total area (xy, local) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:77
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
mod_atmos_phy_mp_vars::atmos_phy_mp_restart_out_title
character(len=h_mid), public atmos_phy_mp_restart_out_title
title of the output file
Definition: mod_atmos_phy_mp_vars.F90:58
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:73
mod_atmos_phy_mp_vars::atmos_phy_mp_restart_in_aggregate
logical, public atmos_phy_mp_restart_in_aggregate
Switch to use aggregate file.
Definition: mod_atmos_phy_mp_vars.F90:53
scale_atmos_hydrometeor::i_hh
integer, parameter, public i_hh
hail
Definition: scale_atmos_hydrometeor.F90:86
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_def_var
subroutine, public atmos_phy_mp_vars_restart_def_var
Define variables in restart file.
Definition: mod_atmos_phy_mp_vars.F90:428
scale_atmos_grid_cartesc_real
module Atmosphere GRID CartesC Real(real space)
Definition: scale_atmos_grid_cartesC_real.F90:11
scale_file_history
module file_history
Definition: scale_file_history.F90:15
scale_file
module file
Definition: scale_file.F90:15
mod_atmos_phy_mp_vars::atmos_phy_mp_restart_in_basename
character(len=h_long), public atmos_phy_mp_restart_in_basename
Basename of the input file.
Definition: mod_atmos_phy_mp_vars.F90:52
scale_atmos_phy_mp_sn14
module ATMOSPHERE / Physics Cloud Microphysics
Definition: scale_atmos_phy_mp_sn14.F90:51
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_create
subroutine, public atmos_phy_mp_vars_restart_create
Create restart file.
Definition: mod_atmos_phy_mp_vars.F90:357
scale_atmos_grid_cartesc_index::jeb
integer, public jeb
Definition: scale_atmos_grid_cartesC_index.F90:66
mod_atmos_phy_mp_vars::atmos_phy_mp_dens_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_mp_dens_t
Definition: mod_atmos_phy_mp_vars.F90:63
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
scale_atmos_hydrometeor::i_hi
integer, parameter, public i_hi
ice water cloud
Definition: scale_atmos_hydrometeor.F90:83
scale_atmos_grid_cartesc_index::ie
integer, public ie
end point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:54
scale_io
module STDIO
Definition: scale_io.F90:10
mod_atmos_phy_mp_vars::atmos_phy_mp_restart_out_basename
character(len=h_long), public atmos_phy_mp_restart_out_basename
Basename of the output file.
Definition: mod_atmos_phy_mp_vars.F90:55
scale_atmos_phy_mp_tomita08::atmos_phy_mp_tomita08_qtrc2qhyd
subroutine, public atmos_phy_mp_tomita08_qtrc2qhyd(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC, Qe)
Calculate mass ratio of each category.
Definition: scale_atmos_phy_mp_tomita08.F90:2534
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_reset_diagnostics
subroutine, public atmos_phy_mp_vars_reset_diagnostics
Definition: mod_atmos_phy_mp_vars.F90:768
scale_tracer::k
real(rp), public k
Definition: scale_tracer.F90:44
scale_atmos_grid_cartesc_index
module atmosphere / grid / cartesC index
Definition: scale_atmos_grid_cartesC_index.F90:12
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_atmos_grid_cartesc_index::ia
integer, public ia
Definition: scale_atmos_grid_cartesC_index.F90:48
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_vol
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_vol
control volume (zxy) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:83
mod_atmos_phy_mp_vars::atmos_phy_mp_rhoc_t
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_mp_rhoc_t
Definition: mod_atmos_phy_mp_vars.F90:69
scale_atmos_phy_mp_sn14::atmos_phy_mp_sn14_qtrc2nhyd
subroutine, public atmos_phy_mp_sn14_qtrc2nhyd(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC0, Ne)
Calculate number concentration of each category.
Definition: scale_atmos_phy_mp_sn14.F90:952
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_effective_radius
subroutine, public atmos_phy_mp_kessler_effective_radius(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS0, TEMP0, QTRC0, Re)
Calculate Effective Radius.
Definition: scale_atmos_phy_mp_kessler.F90:424
mod_atmos_phy_mp_vars::atmos_phy_mp_restart_out_aggregate
logical, public atmos_phy_mp_restart_out_aggregate
Switch to use aggregate file.
Definition: mod_atmos_phy_mp_vars.F90:56
mod_atmos_phy_mp_vars::atmos_phy_mp_rhot_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_mp_rhot_t
Definition: mod_atmos_phy_mp_vars.F90:67
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_fillhalo
subroutine, public atmos_phy_mp_vars_fillhalo
HALO Communication.
Definition: mod_atmos_phy_mp_vars.F90:269
scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_qtrc2nhyd
subroutine, public atmos_phy_mp_suzuki10_qtrc2nhyd(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS, QTRC0, Ne)
Calculate number concentration of each category.
Definition: scale_atmos_phy_mp_suzuki10.F90:1635
mod_atmos_phy_mp_vars::atmos_phy_mp_restart_out_dtype
character(len=h_short), public atmos_phy_mp_restart_out_dtype
REAL4 or REAL8.
Definition: mod_atmos_phy_mp_vars.F90:59
scale_atmos_phy_mp_tomita08::atmos_phy_mp_tomita08_effective_radius
subroutine, public atmos_phy_mp_tomita08_effective_radius(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS0, TEMP0, QTRC0, Re)
Calculate Effective Radius.
Definition: scale_atmos_phy_mp_tomita08.F90:2245
scale_file_cartesc::file_cartesc_close
subroutine, public file_cartesc_close(fid)
Close a netCDF file.
Definition: scale_file_cartesC.F90:1023
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_qtrc2qhyd
subroutine, public atmos_phy_mp_kessler_qtrc2qhyd(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC, Qe)
Calculate mass ratio of each category.
Definition: scale_atmos_phy_mp_kessler.F90:458
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:65
scale_atmos_grid_cartesc_index::is
integer, public is
start point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:53
scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_effective_radius
subroutine, public atmos_phy_mp_suzuki10_effective_radius(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS0, TEMP0, QTRC0, Re)
Calculate Effective Radius.
Definition: scale_atmos_phy_mp_suzuki10.F90:1431
scale_atmos_phy_mp_suzuki10
module Spectran Bin Microphysics
Definition: scale_atmos_phy_mp_suzuki10.F90:23
scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_cloud_fraction
subroutine, public atmos_phy_mp_suzuki10_cloud_fraction(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC0, mask_criterion, cldfrac)
Calculate Cloud Fraction.
Definition: scale_atmos_phy_mp_suzuki10.F90:1374
scale_atmos_hydrometeor::qha
integer, public qha
Definition: scale_atmos_hydrometeor.F90:114
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_write
subroutine, public atmos_phy_mp_vars_restart_write
Write restart.
Definition: mod_atmos_phy_mp_vars.F90:450
scale_atmos_phy_mp_kessler
module atmosphere / physics / microphysics / Kessler
Definition: scale_atmos_phy_mp_kessler.F90:14
scale_atmos_grid_cartesc_index::ja
integer, public ja
Definition: scale_atmos_grid_cartesC_index.F90:49
scale_time
module TIME
Definition: scale_time.F90:11
scale_atmos_hydrometeor::i_hc
integer, parameter, public i_hc
liquid water cloud
Definition: scale_atmos_hydrometeor.F90:81
scale_tracer
module TRACER
Definition: scale_tracer.F90:12
scale_atmos_phy_mp_sn14::atmos_phy_mp_sn14_effective_radius
subroutine, public atmos_phy_mp_sn14_effective_radius(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS0, TEMP0, QTRC0, Re)
ATMOS_PHY_MP_sn14_effective_radius Calculate Effective Radius.
Definition: scale_atmos_phy_mp_sn14.F90:780
mod_atmos_phy_mp_vars::atmos_phy_mp_rhoh
real(rp), dimension(:,:,:), allocatable, public atmos_phy_mp_rhoh
Definition: mod_atmos_phy_mp_vars.F90:70
mod_atmos_phy_mp_vars::atmos_phy_mp_evaporate
real(rp), dimension(:,:,:), allocatable, public atmos_phy_mp_evaporate
Definition: mod_atmos_phy_mp_vars.F90:72
scale_atmos_phy_mp_sn14::atmos_phy_mp_sn14_qtrc2qhyd
subroutine, public atmos_phy_mp_sn14_qtrc2qhyd(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC0, Qe)
ATMOS_PHY_MP_sn14_qtrc2qhyd Calculate mass ratio of each category.
Definition: scale_atmos_phy_mp_sn14.F90:909
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_mp_vars::atmos_phy_mp_vars_setup
subroutine, public atmos_phy_mp_vars_setup
Setup.
Definition: mod_atmos_phy_mp_vars.F90:126
scale_debug
module DEBUG
Definition: scale_debug.F90:11
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_read
subroutine, public atmos_phy_mp_vars_restart_read
Read restart.
Definition: mod_atmos_phy_mp_vars.F90:323
scale_file_cartesc::file_cartesc_create
subroutine, public file_cartesc_create(basename, title, datatype, fid, date, subsec, haszcoord, append, aggregate, single)
Create/open a netCDF file.
Definition: scale_file_cartesC.F90:780
mod_atmos_phy_mp_vars::atmos_phy_mp_rhov_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_mp_rhov_t
Definition: mod_atmos_phy_mp_vars.F90:66
scale_file_cartesc::file_cartesc_open
subroutine, public file_cartesc_open(basename, fid, aggregate)
open a netCDF file for read
Definition: scale_file_cartesC.F90:746
scale_file_cartesc::file_cartesc_flush
subroutine, public file_cartesc_flush(fid)
Flush all pending requests to a netCDF file (PnetCDF only)
Definition: scale_file_cartesC.F90:997
scale_time::time_gettimelabel
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:91
scale_comm_cartesc
module COMMUNICATION
Definition: scale_comm_cartesC.F90:11
mod_atmos_phy_mp_vars::atmos_phy_mp_rhou_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_mp_rhou_t
Definition: mod_atmos_phy_mp_vars.F90:65
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_mp_vars::atmos_phy_mp_restart_output
logical, public atmos_phy_mp_restart_output
output restart file?
Definition: mod_atmos_phy_mp_vars.F90:50
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:74
scale_atmos_grid_cartesc_index::ieb
integer, public ieb
Definition: scale_atmos_grid_cartesC_index.F90:64
scale_file::file_get_aggregate
logical function, public file_get_aggregate(fid)
Definition: scale_file.F90:4844
mod_atmos_phy_mp_vars::atmos_phy_mp_restart_out_postfix_timelabel
logical, public atmos_phy_mp_restart_out_postfix_timelabel
Add timelabel to the basename of output file?
Definition: mod_atmos_phy_mp_vars.F90:57
mod_atmos_admin::atmos_phy_mp_type
character(len=h_short), public atmos_phy_mp_type
Definition: mod_atmos_admin.F90:36
scale_file_history::file_history_reg
subroutine, public file_history_reg(name, desc, unit, itemid, standard_name, ndims, dim_type, cell_measures, fill_halo)
Register/Append variable to history file.
Definition: scale_file_history.F90:650
mod_atmos_phy_mp_vars::qe_mp
integer, public qe_mp
Definition: mod_atmos_phy_mp_vars.F90:79
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_open
subroutine, public atmos_phy_mp_vars_restart_open
Open restart file for read.
Definition: mod_atmos_phy_mp_vars.F90:288
mod_atmos_phy_mp_vars::atmos_phy_mp_cldfrac_thleshold
real(rp), public atmos_phy_mp_cldfrac_thleshold
Definition: mod_atmos_phy_mp_vars.F90:61
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvol
real(rp), public atmos_grid_cartesc_real_totvol
total volume (zxy, local) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:87
scale_atmos_phy_mp_sn14::atmos_phy_mp_sn14_cloud_fraction
subroutine, public atmos_phy_mp_sn14_cloud_fraction(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC, mask_criterion, cldfrac)
ATMOS_PHY_MP_sn14_cloud_fraction Calculate Cloud Fraction.
Definition: scale_atmos_phy_mp_sn14.F90:742
mod_atmos_phy_mp_vars::atmos_phy_mp_rhoq_t
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_mp_rhoq_t
Definition: mod_atmos_phy_mp_vars.F90:68
scale_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:41
scale_atmos_grid_cartesc_index::jsb
integer, public jsb
Definition: scale_atmos_grid_cartesC_index.F90:65
scale_atmos_phy_mp_tomita08::atmos_phy_mp_tomita08_cloud_fraction
subroutine, public atmos_phy_mp_tomita08_cloud_fraction(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC, mask_criterion, cldfrac)
Calculate Cloud Fraction.
Definition: scale_atmos_phy_mp_tomita08.F90:2210
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_close
subroutine, public atmos_phy_mp_vars_restart_close
Close restart file.
Definition: mod_atmos_phy_mp_vars.F90:408
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_history
subroutine, public atmos_phy_mp_vars_history(DENS, TEMP, QTRC)
Definition: mod_atmos_phy_mp_vars.F90:472
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:56
scale_atmos_grid_cartesc_index::je
integer, public je
end point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:56
scale_file_cartesc
module file / cartesianC
Definition: scale_file_cartesC.F90:11
scale_atmos_hydrometeor::n_hyd
integer, parameter, public n_hyd
Definition: scale_atmos_hydrometeor.F90:79
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_enddef
subroutine, public atmos_phy_mp_vars_restart_enddef
Exit netCDF define mode.
Definition: mod_atmos_phy_mp_vars.F90:394
scale_atmos_hydrometeor::i_hg
integer, parameter, public i_hg
graupel
Definition: scale_atmos_hydrometeor.F90:85