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
35 
41 
43 
46 
47  !-----------------------------------------------------------------------------
48  !
49  !++ Public parameters & variables
50  !
51  logical, public :: atmos_phy_mp_restart_output = .false.
52 
53  character(len=H_LONG), public :: atmos_phy_mp_restart_in_basename = ''
55  logical, public :: atmos_phy_mp_restart_in_postfix_timelabel = .false.
56  character(len=H_LONG), public :: atmos_phy_mp_restart_out_basename = ''
58  logical, public :: atmos_phy_mp_restart_out_postfix_timelabel = .true.
59  character(len=H_MID), public :: atmos_phy_mp_restart_out_title = 'ATMOS_PHY_MP restart'
60  character(len=H_SHORT), public :: atmos_phy_mp_restart_out_dtype = 'DEFAULT'
61 
63 
64  real(rp), public, allocatable :: atmos_phy_mp_dens_t(:,:,:) ! tendency DENS [kg/m3/s]
65  real(rp), public, allocatable :: atmos_phy_mp_momz_t(:,:,:) ! tendency MOMZ [kg/m2/s2]
66  real(rp), public, allocatable :: atmos_phy_mp_rhou_t(:,:,:) ! tendency dens*U [kg/m2/s2]
67  real(rp), public, allocatable :: atmos_phy_mp_rhov_t(:,:,:) ! tendency dens*V [kg/m2/s2]
68  real(rp), public, allocatable :: atmos_phy_mp_rhot_t(:,:,:) ! tendency RHOT [K*kg/m3/s]
69  real(rp), public, allocatable :: atmos_phy_mp_rhoq_t(:,:,:,:) ! tendency rho*QTRC [kg/m3/s]
70  real(rp), public, allocatable :: atmos_phy_mp_rhoc_t(:,:,:,:) ! tendency rho*QTRC (charge) [fC/m3/s]
71  real(rp), public, allocatable :: atmos_phy_mp_rhoh (:,:,:) ! diabatic heating rate [J/kg/s]
72 
73  real(rp), public, allocatable :: atmos_phy_mp_evaporate(:,:,:) ! number concentration of evaporated cloud [/m3]
74  real(rp), public, allocatable :: atmos_phy_mp_sflx_rain(:,:) ! precipitation flux (liquid) [kg/m2/s]
75  real(rp), public, allocatable :: atmos_phy_mp_sflx_snow(:,:) ! precipitation flux (solid) [kg/m2/s]
76  real(rp), public, allocatable :: atmos_phy_mp_sflx_engi(:,:) ! internal energy flux [J/m2/s]
77 
78  integer, public :: qa_mp = 0
79  integer, public :: qs_mp = -1
80  integer, public :: qe_mp = -2
81 
82  !-----------------------------------------------------------------------------
83  !
84  !++ Private procedure
85  !
86  !-----------------------------------------------------------------------------
87  !
88  !++ Private parameters & variables
89  !
90  integer, private, parameter :: vmax = 0
91 
92  character(len=H_SHORT), private :: var_name(vmax)
93  character(len=H_MID), private :: var_desc(vmax)
94  character(len=H_SHORT), private :: var_unit(vmax)
95  integer, private :: var_id(vmax)
96  integer, private :: restart_fid = -1 ! file ID
97 
98 ! data VAR_NAME / /
99 ! data VAR_DESC / /
100 ! data VAR_UNIT / /
101 
102 
103  ! for diagnostics
104  real(rp), private, allocatable :: atmos_phy_mp_cldfrac(:,:,:)
105  real(rp), private, allocatable :: atmos_phy_mp_re (:,:,:,:)
106  real(rp), private, allocatable :: atmos_phy_mp_qe (:,:,:,:)
107  real(rp), private, allocatable :: atmos_phy_mp_ne (:,:,:,:)
108  logical, private :: diag_cldfrac
109  logical, private :: diag_re
110  logical, private :: diag_qe
111  logical, private :: diag_ne
112 
113  ! for history
114  integer, private :: hist_cldfrac_id
115  logical, private :: hist_re
116  logical, private :: hist_qe
117  logical, private :: hist_ne
118  integer, private, allocatable :: hist_re_id(:)
119  integer, private, allocatable :: hist_qe_id(:)
120  integer, private, allocatable :: hist_ne_id(:)
121 
122  !-----------------------------------------------------------------------------
123 contains
124  !-----------------------------------------------------------------------------
126  subroutine atmos_phy_mp_vars_setup
127  use scale_prc, only: &
128  prc_abort
129  use scale_const, only: &
130  undef => const_undef
131  use scale_atmos_hydrometeor, only: &
132  n_hyd, &
133  qha, &
134  hyd_name, &
135  num_name, &
136  hyd_desc
137  use scale_file_history, only: &
139  implicit none
140 
141  namelist / param_atmos_phy_mp_vars / &
151 
152  integer :: ierr
153  integer :: iv, ih
154  !---------------------------------------------------------------------------
155 
156  log_newline
157  log_info("ATMOS_PHY_MP_vars_setup",*) 'Setup'
158 
159  allocate( atmos_phy_mp_dens_t(ka,ia,ja) )
160  allocate( atmos_phy_mp_momz_t(ka,ia,ja) )
161  allocate( atmos_phy_mp_rhou_t(ka,ia,ja) )
162  allocate( atmos_phy_mp_rhov_t(ka,ia,ja) )
163  allocate( atmos_phy_mp_rhot_t(ka,ia,ja) )
164  allocate( atmos_phy_mp_rhoq_t(ka,ia,ja,qs_mp:qe_mp) )
165  allocate( atmos_phy_mp_rhoh(ka,ia,ja) )
166  allocate( atmos_phy_mp_evaporate(ka,ia,ja) )
167  ! tentative approach
168 
169  atmos_phy_mp_dens_t(:,:,:) = 0.0_rp
170  atmos_phy_mp_momz_t(:,:,:) = 0.0_rp
171  atmos_phy_mp_rhou_t(:,:,:) = 0.0_rp
172  atmos_phy_mp_rhov_t(:,:,:) = 0.0_rp
173  atmos_phy_mp_rhot_t(:,:,:) = 0.0_rp
174  atmos_phy_mp_rhoq_t(:,:,:,:) = 0.0_rp
175  atmos_phy_mp_rhoh(:,:,:) = 0.0_rp
176  atmos_phy_mp_evaporate(:,:,:) = 0.0_rp
177  !$acc enter data copyin(ATMOS_PHY_MP_DENS_t, ATMOS_PHY_MP_MOMZ_t, ATMOS_PHY_MP_RHOU_t, ATMOS_PHY_MP_RHOV_t, ATMOS_PHY_MP_RHOT_t, ATMOS_PHY_MP_RHOQ_t, ATMOS_PHY_MP_RHOH, ATMOS_PHY_MP_EVAPORATE)
178 
179  allocate( atmos_phy_mp_sflx_rain(ia,ja) )
180  allocate( atmos_phy_mp_sflx_snow(ia,ja) )
181  allocate( atmos_phy_mp_sflx_engi(ia,ja) )
182  atmos_phy_mp_sflx_rain(:,:) = undef
183  atmos_phy_mp_sflx_snow(:,:) = undef
184  atmos_phy_mp_sflx_engi(:,:) = undef
185  !$acc enter data create(ATMOS_PHY_MP_SFLX_rain, ATMOS_PHY_MP_SFLX_snow, ATMOS_PHY_MP_SFLX_ENGI)
186 
187  !--- read namelist
188  rewind(io_fid_conf)
189  read(io_fid_conf,nml=param_atmos_phy_mp_vars,iostat=ierr)
190  if( ierr < 0 ) then !--- missing
191  log_info("ATMOS_PHY_MP_vars_setup",*) 'Not found namelist. Default used.'
192  elseif( ierr > 0 ) then !--- fatal error
193  log_error("ATMOS_PHY_MP_vars_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_PHY_MP_VARS. Check!'
194  call prc_abort
195  endif
196  log_nml(param_atmos_phy_mp_vars)
197 
198  log_newline
199  log_info("ATMOS_PHY_MP_vars_setup",*) '[ATMOS_PHY_MP] prognostic/diagnostic variables'
200  log_info_cont('(1x,A,A24,A,A48,A,A12,A)') &
201  ' |', 'VARNAME ','|', &
202  'DESCRIPTION ', '[', 'UNIT ', ']'
203  do iv = 1, vmax
204  log_info_cont('(1x,A,I3,A,A24,A,A48,A,A12,A)') &
205  'NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
206  enddo
207 
208  log_newline
209  if ( atmos_phy_mp_restart_in_basename /= '' ) then
210  log_info("ATMOS_PHY_MP_vars_setup",*) 'Restart input? : YES, file = ', trim(atmos_phy_mp_restart_in_basename)
211  log_info("ATMOS_PHY_MP_vars_setup",*) 'Add timelabel? : ', atmos_phy_mp_restart_in_postfix_timelabel
212  else
213  log_info("ATMOS_PHY_MP_vars_setup",*) 'Restart input? : NO'
214  endif
216  .AND. atmos_phy_mp_restart_out_basename /= '' ) then
217  log_info("ATMOS_PHY_MP_vars_setup",*) 'Restart output? : YES, file = ', trim(atmos_phy_mp_restart_out_basename)
218  log_info("ATMOS_PHY_MP_vars_setup",*) 'Add timelabel? : ', atmos_phy_mp_restart_out_postfix_timelabel
219  else
220  log_info("ATMOS_PHY_MP_vars_setup",*) 'Restart output? : NO'
222  endif
223 
224 
225  ! diagnostices
226  allocate( atmos_phy_mp_cldfrac(ka,ia,ja) )
227  allocate( atmos_phy_mp_re(ka,ia,ja,n_hyd) )
228  allocate( atmos_phy_mp_qe(ka,ia,ja,n_hyd) )
229  allocate( atmos_phy_mp_ne(ka,ia,ja,n_hyd) )
230 !OCL XFILL
231  atmos_phy_mp_cldfrac(:,:,:) = undef
232 !OCL XFILL
233  atmos_phy_mp_re(:,:,:,:) = undef
234 !OCL XFILL
235  atmos_phy_mp_qe(:,:,:,:) = undef
236  atmos_phy_mp_ne(:,:,:,:) = undef
237  diag_cldfrac = .false.
238  diag_re = .false.
239  diag_qe = .false.
240  diag_ne = .false.
241  !$acc enter data create(ATMOS_PHY_MP_CLDFRAC, ATMOS_PHY_MP_Re, ATMOS_PHY_MP_Qe, ATMOS_PHY_MP_Ne)
242 
243  ! history
244  allocate( hist_re_id(n_hyd) )
245  allocate( hist_qe_id(n_hyd) )
246  allocate( hist_ne_id(n_hyd) )
247 
248  call file_history_reg( 'CLDFRAC', 'cloud fraction', '1', hist_cldfrac_id, fill_halo=.true., dim_type='ZXY' )
249 
250  hist_re = .false.
251  do ih = 1, n_hyd
252  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' )
253  if( hist_re_id(ih) > 0 ) hist_re = .true.
254  enddo
255 
256  hist_qe = .false.
257  do ih = 1, n_hyd
258  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' )
259  if( hist_qe_id(ih) > 0 ) hist_qe = .true.
260  enddo
261 
262  hist_ne = .false.
263  do ih = 1, n_hyd
264  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' )
265  if( hist_ne_id(ih) > 0 ) hist_ne = .true.
266  enddo
267 
268  return
269  end subroutine atmos_phy_mp_vars_setup
270 
271  !-----------------------------------------------------------------------------
273  subroutine atmos_phy_mp_vars_finalize
274  implicit none
275  !---------------------------------------------------------------------------
276 
277  log_newline
278  log_info("ATMOS_PHY_MP_vars_finalize",*) 'Finalize'
279 
280  !$acc exit data delete(ATMOS_PHY_MP_DENS_t,ATMOS_PHY_MP_MOMZ_t,ATMOS_PHY_MP_RHOU_t,ATMOS_PHY_MP_RHOV_t,ATMOS_PHY_MP_RHOT_t,ATMOS_PHY_MP_RHOH,ATMOS_PHY_MP_EVAPORATE)
281  deallocate( atmos_phy_mp_dens_t )
282  deallocate( atmos_phy_mp_momz_t )
283  deallocate( atmos_phy_mp_rhou_t )
284  deallocate( atmos_phy_mp_rhov_t )
285  deallocate( atmos_phy_mp_rhot_t )
286  deallocate( atmos_phy_mp_rhoq_t )
287  deallocate( atmos_phy_mp_rhoh )
288  deallocate( atmos_phy_mp_evaporate )
289 
290  !$acc exit data delete(ATMOS_PHY_MP_SFLX_rain,ATMOS_PHY_MP_SFLX_snow,ATMOS_PHY_MP_SFLX_ENGI)
291  deallocate( atmos_phy_mp_sflx_rain )
292  deallocate( atmos_phy_mp_sflx_snow )
293  deallocate( atmos_phy_mp_sflx_engi )
294 
295  ! diagnostices
296  !$acc exit data delete(ATMOS_PHY_MP_CLDFRAC,ATMOS_PHY_MP_Re,ATMOS_PHY_MP_Qe,ATMOS_PHY_MP_Ne)
297  deallocate( atmos_phy_mp_cldfrac )
298  deallocate( atmos_phy_mp_re )
299  deallocate( atmos_phy_mp_qe )
300  deallocate( atmos_phy_mp_ne )
301 
302 
303  ! history
304  deallocate( hist_re_id )
305  deallocate( hist_qe_id )
306  deallocate( hist_ne_id )
307 
308  return
309  end subroutine atmos_phy_mp_vars_finalize
310 
311  !-----------------------------------------------------------------------------
313  subroutine atmos_phy_mp_vars_fillhalo
314  use scale_comm_cartesc, only: &
315  comm_vars8, &
316  comm_wait
317  implicit none
318  !---------------------------------------------------------------------------
319 
320  call comm_vars8( atmos_phy_mp_sflx_rain(:,:), 1 )
321  call comm_vars8( atmos_phy_mp_sflx_snow(:,:), 2 )
322  call comm_vars8( atmos_phy_mp_sflx_engi(:,:), 3 )
323  call comm_wait ( atmos_phy_mp_sflx_rain(:,:), 1 )
324  call comm_wait ( atmos_phy_mp_sflx_snow(:,:), 2 )
325  call comm_wait ( atmos_phy_mp_sflx_engi(:,:), 3 )
326 
327  return
328  end subroutine atmos_phy_mp_vars_fillhalo
329 
330  !-----------------------------------------------------------------------------
333  use scale_time, only: &
335  use scale_file_cartesc, only: &
337  implicit none
338 
339  character(len=19) :: timelabel
340  character(len=H_LONG) :: basename
341  !---------------------------------------------------------------------------
342 
343 !!$ LOG_NEWLINE
344 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_open",*) 'Open restart file (ATMOS_PHY_MP) '
345 !!$
346 !!$ if ( ATMOS_PHY_MP_RESTART_IN_BASENAME /= '' ) then
347 !!$
348 !!$ if ( ATMOS_PHY_MP_RESTART_IN_POSTFIX_TIMELABEL ) then
349 !!$ call TIME_gettimelabel( timelabel )
350 !!$ basename = trim(ATMOS_PHY_MP_RESTART_IN_BASENAME)//'_'//trim(timelabel)
351 !!$ else
352 !!$ basename = trim(ATMOS_PHY_MP_RESTART_IN_BASENAME)
353 !!$ endif
354 !!$
355 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_open",*) 'basename: ', trim(basename)
356 !!$
357 !!$ call FILE_CARTESC_open( basename, restart_fid, aggregate=ATMOS_PHY_MP_RESTART_IN_AGGREGATE )
358 !!$ else
359 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_open",*) 'restart file for ATMOS_PHY_MP is not specified.'
360 !!$ endif
361 
362  return
363  end subroutine atmos_phy_mp_vars_restart_open
364 
365  !-----------------------------------------------------------------------------
368  use scale_file, only: &
370  use scale_file_cartesc, only: &
371  file_cartesc_read, &
373  implicit none
374 
375  !---------------------------------------------------------------------------
376 
377 !!$ if ( restart_fid /= -1 ) then
378 !!$ LOG_NEWLINE
379 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_read",*) 'Read from restart file (ATMOS_PHY_MP) '
380 !!$
381 !!$ call FILE_CARTESC_read( restart_fid, VAR_NAME(1), 'XY', & ! [IN]
382 !!$ ATMOS_PHY_MP_hoge(:,:) ) ! [OUT]
383 !!$
384 !!$ if ( FILE_get_AGGREGATE(restart_fid) ) then
385 !!$ call FILE_CARTESC_flush( restart_fid ) ! X/Y halos have been read from file
386 !!$ !$acc update device(ATMOS_PHY_MP_hoge)
387 !!$ else
388 !!$ call ATMOS_PHY_MP_vars_fillhalo
389 !!$ end if
390 !!$
391 !!$ call ATMOS_PHY_MP_vars_check
392 !!$
393 !!$ else
394 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_read",*) 'invalid restart file ID for ATMOS_PHY_MP.'
395 !!$ endif
396 
397  return
398  end subroutine atmos_phy_mp_vars_restart_read
399 
400  !-----------------------------------------------------------------------------
403  use scale_time, only: &
405  use scale_file_cartesc, only: &
407  implicit none
408 
409  character(len=19) :: timelabel
410  character(len=H_LONG) :: basename
411  !---------------------------------------------------------------------------
412 
413 !!$ if ( ATMOS_PHY_MP_RESTART_OUT_BASENAME /= '' ) then
414 !!$
415 !!$ LOG_NEWLINE
416 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_create",*) 'Create restart file (ATMOS_PHY_AE) '
417 !!$
418 !!$ if ( ATMOS_PHY_MP_RESTART_OUT_POSTFIX_TIMELABEL ) then
419 !!$ call TIME_gettimelabel( timelabel )
420 !!$ basename = trim(ATMOS_PHY_MP_RESTART_OUT_BASENAME)//'_'//trim(timelabel)
421 !!$ else
422 !!$ basename = trim(ATMOS_PHY_MP_RESTART_OUT_BASENAME)
423 !!$ endif
424 !!$
425 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_create",*) 'basename: ', trim(basename)
426 !!$
427 !!$ call FILE_CARTESC_create( &
428 !!$ basename, ATMOS_PHY_MP_RESTART_OUT_TITLE, ATMOS_PHY_MP_RESTART_OUT_DTYPE, & ! [IN]
429 !!$ restart_fid, & ! [OUT]
430 !!$ aggregate=ATMOS_PHY_MP_RESTART_OUT_AGGREGATE ) ! [IN]
431 !!$
432 !!$ endif
433 
434  return
435  end subroutine atmos_phy_mp_vars_restart_create
436 
437  !-----------------------------------------------------------------------------
440  use scale_file_cartesc, only: &
442  implicit none
443 
444 !!$ if ( restart_fid /= -1 ) then
445 !!$ call FILE_CARTESC_enddef( restart_fid ) ! [IN]
446 !!$ endif
447 
448  return
449  end subroutine atmos_phy_mp_vars_restart_enddef
450 
451  !-----------------------------------------------------------------------------
454  use scale_file_cartesc, only: &
456  implicit none
457  !---------------------------------------------------------------------------
458 
459 !!$ if ( restart_fid /= -1 ) then
460 !!$ LOG_NEWLINE
461 !!$ LOG_INFO("ATMOS_PHY_MP_vars_restart_close",*) 'Close restart file (ATMOS_PHY_MP) '
462 !!$
463 !!$ call FILE_CARTESC_close( restart_fid ) ! [IN]
464 !!$
465 !!$ restart_fid = -1
466 !!$ endif
467 
468  return
469  end subroutine atmos_phy_mp_vars_restart_close
470 
471  !-----------------------------------------------------------------------------
474  use scale_file_cartesc, only: &
476  implicit none
477  integer :: iv
478  !---------------------------------------------------------------------------
479 
480 !!$ if ( restart_fid /= -1 ) then
481 !!$
482 !!$ do iv = 1, VMAX
483 !!$ call FILE_CARTESC_def_var( restart_fid, VAR_NAME(iv), VAR_DESC(iv), VAR_UNIT(iv), &
484 !!$ 'XY', ATMOS_PHY_MP_RESTART_OUT_DTYPE, &
485 !!$ VAR_ID(iv) )
486 !!$ end do
487 !!$
488 !!$ endif
489 
490  return
491  end subroutine atmos_phy_mp_vars_restart_def_var
492 
493  !-----------------------------------------------------------------------------
496  use scale_file_cartesc, only: &
497  file_cartesc_write_var
498  implicit none
499  !---------------------------------------------------------------------------
500 
501 !!$ if ( restart_fid /= -1 ) then
502 !!$
503 !!$ call ATMOS_PHY_MP_vars_fillhalo
504 !!$
505 !!$ call ATMOS_PHY_MP_vars_check
506 !!$
507 !!$ call FILE_CARTESC_write_var( restart_fid, VAR_ID(1), ATMOS_PHY_MP_hoge(:,:), &
508 !!$ VAR_NAME(1), 'XY' ) ! [IN]
509 !!$
510 !!$ endif
511 
512  return
513  end subroutine atmos_phy_mp_vars_restart_write
514 
515  !-----------------------------------------------------------------------------
516  subroutine atmos_phy_mp_vars_history( &
517  DENS, TEMP, QTRC )
519  n_hyd
520  use scale_file_history, only: &
521  file_history_query, &
522  file_history_put
523  use mod_atmos_admin, only: &
525  implicit none
526 
527  real(rp), intent(in) :: dens(ka,ia,ja)
528  real(rp), intent(in) :: temp(ka,ia,ja)
529  real(rp), intent(in) :: qtrc(ka,ia,ja,qa)
530 
531  real(rp) :: work (ka,ia,ja,n_hyd)
532  logical :: do_put
533  integer :: ih
534  !---------------------------------------------------------------------------
535 
536  !$acc data create(WORK)
537 
538  if ( hist_cldfrac_id > 0 ) then
539  call file_history_query( hist_cldfrac_id, do_put )
540 
541  if ( do_put ) then
543  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,:), & ! [IN]
544  cldfrac=work(:,:,:,1) ) ! [OUT]
545  call file_history_put( hist_cldfrac_id, work(:,:,:,1) )
546  end if
547  end if
548 
549  if ( hist_re ) then
550  do ih = 1, n_hyd
551  if ( hist_re_id(ih) > 0 ) then
552  call file_history_query( hist_re_id(ih), do_put )
553  if ( do_put ) then
555  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,:), & ! [IN]
556  re=work(:,:,:,:) ) ! [OUT]
557  exit
558  end if
559  end if
560  end do
561  if ( do_put ) then
562  do ih = 1, n_hyd
563  if ( hist_re_id(ih) > 0 ) then
564  call file_history_query( hist_re_id(ih), do_put )
565  if ( do_put ) then
566  call file_history_put( hist_re_id(ih), work(:,:,:,ih) )
567  end if
568  end if
569  end do
570  end if
571  end if
572 
573  if ( hist_qe ) then
574  do ih = 1, n_hyd
575  if ( hist_qe_id(ih) > 0 ) then
576  call file_history_query( hist_qe_id(ih), do_put )
577  if ( do_put ) then
579  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,:), & ! [IN]
580  qe=work(:,:,:,:) ) ! [OUT]
581  exit
582  end if
583  end if
584  end do
585  if ( do_put ) then
586  do ih = 1, n_hyd
587  if ( hist_qe_id(ih) > 0 ) then
588  call file_history_query( hist_qe_id(ih), do_put )
589  if( do_put ) then
590  call file_history_put( hist_qe_id(ih), work(:,:,:,ih) )
591  end if
592  end if
593  end do
594  end if
595  end if
596 
597  if ( hist_ne ) then
598  do ih = 1, n_hyd
599  if ( hist_ne_id(ih) > 0 ) then
600  call file_history_query( hist_ne_id(ih), do_put )
601  if ( do_put ) then
603  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,:), & ! [IN]
604  ne=work(:,:,:,:) ) ! [OUT]
605  exit
606  end if
607  end if
608  end do
609  if ( do_put ) then
610  do ih = 1, n_hyd
611  if ( hist_ne_id(ih) > 0 ) then
612  call file_history_query( hist_ne_id(ih), do_put )
613  if( do_put ) then
614  call file_history_put( hist_ne_id(ih), work(:,:,:,ih) )
615  end if
616  end if
617  end do
618  end if
619  end if
620 
621  !$acc end data
622 
623  return
624  end subroutine atmos_phy_mp_vars_history
625 
627  DENS, TEMP, QTRC, &
628  CLDFRAC, Re, Qe, Ne )
630  n_hyd, &
631  i_hc, &
632  i_hr, &
633  i_hi, &
634  i_hs, &
635  i_hg, &
636  i_hh
637  use scale_atmos_phy_mp_kessler, only: &
641  use scale_atmos_phy_mp_tomita08, only: &
645  use scale_atmos_phy_mp_sn14, only: &
650  use scale_atmos_phy_mp_suzuki10, only: &
655  use mod_atmos_admin, only: &
657  implicit none
658 
659  real(rp), intent(in) :: dens(ka,ia,ja)
660  real(rp), intent(in) :: temp(ka,ia,ja)
661  real(rp), intent(in) :: qtrc(ka,ia,ja,qa)
662  real(rp), intent(out), optional :: cldfrac(ka,ia,ja)
663  real(rp), intent(out), optional :: re (ka,ia,ja,n_hyd)
664  real(rp), intent(out), optional :: qe (ka,ia,ja,n_hyd)
665  real(rp), intent(out), optional :: ne (ka,ia,ja,n_hyd)
666 
667  integer :: k, i, j, ih
668 
669  if ( present(cldfrac) ) then
670  !$acc data copyout(CLDFRAC)
671  if ( .not. diag_cldfrac ) then
672  select case ( atmos_phy_mp_type )
673  case ( 'KESSLER' )
674  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
676  ka, ks, ke, ia, is, ie, ja, js, je, &
677  qtrc(:,:,:,qs_mp+1:qe_mp), atmos_phy_mp_cldfrac_thleshold, & ! [IN]
678  atmos_phy_mp_cldfrac(:,:,:) ) ! [OUT]
679  !$acc update device(ATMOS_PHY_MP_CLDFRAC)
680  case ( 'TOMITA08' )
682  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
683  qtrc(:,:,:,qs_mp+1:qe_mp), atmos_phy_mp_cldfrac_thleshold, & ! [IN]
684  atmos_phy_mp_cldfrac(:,:,:) ) ! [OUT]
685  case ( 'SN14' )
686  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
688  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
689  qtrc(:,:,:,qs_mp+1:qe_mp), atmos_phy_mp_cldfrac_thleshold, & ! [IN]
690  atmos_phy_mp_cldfrac(:,:,:) ) ! [OUT]
691  !$acc update device(ATMOS_PHY_MP_CLDFRAC)
692  case ( 'SUZUKI10' )
693  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
695  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
696  qtrc(:,:,:,qs_mp+1:qe_mp), atmos_phy_mp_cldfrac_thleshold, & ! [IN]
697  atmos_phy_mp_cldfrac(:,:,:) ) ! [OUT]
698  !$acc update device(ATMOS_PHY_MP_CLDFRAC)
699  case default
700 !OCL XFILL
701  !$acc kernels
702  atmos_phy_mp_cldfrac(:,:,:) = 0.0_rp
703  !$acc end kernels
704  end select
705  diag_cldfrac = .true.
706  end if
707 !OCL XFILL
708  !$acc kernels
709  do j = jsb, jeb
710  do i = isb, ieb
711  do k = ks, ke
712  cldfrac(k,i,j) = atmos_phy_mp_cldfrac(k,i,j)
713  end do
714  end do
715  end do
716  !$acc end kernels
717 
718  !$acc end data
719  end if
720 
721  if ( present(re) ) then
722  !$acc data copyout(Re)
723  if ( .not. diag_re ) then
724  select case ( atmos_phy_mp_type )
725  case ( 'KESSLER' )
726  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
728  ka, ks, ke, ia, is, ie, ja, js, je, &
729  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
730  atmos_phy_mp_re(:,:,:,:) ) ! [OUT]
731  !$acc update device(ATMOS_PHY_MP_Re)
732  case ( 'TOMITA08' )
734  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
735  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
736  atmos_phy_mp_re(:,:,:,:) ) ! [OUT]
737  case ( 'SN14' )
738  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
740  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
741  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
742  atmos_phy_mp_re(:,:,:,:) ) ! [OUT]
743  !$acc update device(ATMOS_PHY_MP_Re)
744  case ( 'SUZUKI10' )
745  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
747  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
748  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
749  atmos_phy_mp_re(:,:,:,:) ) ! [OUT]
750  !$acc update device(ATMOS_PHY_MP_Re)
751  case default
752 !OCL XFILL
753  !$acc kernels
754  atmos_phy_mp_re(:,:,:,:) = 0.0_rp
755  !$acc end kernels
756  end select
757  diag_re = .true.
758  end if
759 !OCL XFILL
760  !$acc kernels
761  do ih = 1, n_hyd
762  do j = jsb, jeb
763  do i = isb, ieb
764  do k = ks, ke
765  re(k,i,j,ih) = atmos_phy_mp_re(k,i,j,ih)
766  end do
767  end do
768  end do
769  end do
770  !$acc end kernels
771 
772  !$acc end data
773  end if
774 
775  if ( present(qe) ) then
776  !$acc data copyout(Qe)
777  if ( .not. diag_qe ) then
778  select case ( atmos_phy_mp_type )
779  case ( 'KESSLER' )
780  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
782  ka, ks, ke, ia, is, ie, ja, js, je, &
783  qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
784  atmos_phy_mp_qe(:,:,:,:) ) ! [OUT]
785  !$acc update device(ATMOS_PHY_MP_Qe)
786  case ( 'TOMITA08' )
788  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
789  qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
790  atmos_phy_mp_qe(:,:,:,:) ) ! [OUT]
791  case ( 'SN14' )
792  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
794  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
795  qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
796  atmos_phy_mp_qe(:,:,:,:) ) ! [OUT]
797  !$acc update device(ATMOS_PHY_MP_Qe)
798  case ( 'SUZUKI10' )
799  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
801  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
802  qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
803  atmos_phy_mp_qe(:,:,:,:) ) ! [OUT]
804  !$acc update device(ATMOS_PHY_MP_Qe)
805  case default
806 !OCL XFILL
807  !$acc kernels
808  atmos_phy_mp_qe(:,:,:,:) = 0.0_rp
809  !$acc end kernels
810  end select
811  diag_qe = .true.
812  end if
813 !OCL XFILL
814  !$acc kernels
815  do ih = 1, n_hyd
816  do j = jsb, jeb
817  do i = isb, ieb
818  do k = ks, ke
819  qe(k,i,j,ih) = atmos_phy_mp_qe(k,i,j,ih)
820  end do
821  end do
822  end do
823  end do
824  !$acc end kernels
825 
826  !$acc end data
827  end if
828 
829  if ( present(ne) ) then
830  !$acc data copyout(Ne)
831  if ( .not. diag_ne ) then
832  select case ( atmos_phy_mp_type )
833  case ( 'KESSLER', 'TOMITA08' )
834  ! do nothing
835  case ( 'SN14' )
836  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
838  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
839  qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
840  atmos_phy_mp_ne(:,:,:,:) ) ! [OUT]
841  !$acc update device(ATMOS_PHY_MP_Ne)
842  case ( 'SUZUKI10' )
843  !$acc update host(QTRC(:,:,:,QS_MP+1:QE_MP))
845  ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
846  dens(:,:,:), qtrc(:,:,:,qs_mp+1:qe_mp), & ! [IN]
847  atmos_phy_mp_ne(:,:,:,:) ) ! [OUT]
848  !$acc update device(ATMOS_PHY_MP_Ne)
849  end select
850  diag_ne = .true.
851  end if
852 !OCL XFILL
853  !$acc kernels
854  do ih = 1, n_hyd
855  do j = jsb, jeb
856  do i = isb, ieb
857  do k = ks, ke
858  ne(k,i,j,ih) = atmos_phy_mp_ne(k,i,j,ih)
859  end do
860  end do
861  end do
862  end do
863  !$acc end kernels
864 
865  !$acc end data
866  end if
867 
868  return
869  end subroutine atmos_phy_mp_vars_get_diagnostic
870 
872  diag_cldfrac = .false.
873  diag_re = .false.
874  diag_qe = .false.
875  diag_ne = .false.
876 
877  return
879 
880  subroutine atmos_phy_mp_vars_check
881  use scale_statistics, only: &
882  statistics_total
883  use scale_atmos_grid_cartesc_real, only: &
888  implicit none
889 
890 !!$ call VALCHECK( IA, IS, IE, JA, JS, JE, &
891 !!$ ATMOS_PHY_MP_hoge(:,:), & ! (in)
892 !!$ 0.0_RP, 0.0_RP, VAR_NAME(1), & ! (in)
893 !!$ __FILE__, __LINE__ ) ! (in)
894 !!$
895 !!$ call STATISTICS_total( IA, IS, IE, JA, JS, JE, &
896 !!$ ATMOS_PHY_MP_hoge(:,:), VAR_NAME(1), & ! (in)
897 !!$ ATMOS_GRID_CARTESC_REAL_AREA(:,:), & ! (in)
898 !!$ ATMOS_GRID_CARTESC_REAL_TOTAREA ) ! (in)
899 
900  return
901  end subroutine atmos_phy_mp_vars_check
902 
903 
904 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:76
scale_atmos_grid_cartesc_index::isb
integer, public isb
Definition: scale_atmos_grid_cartesC_index.F90:64
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:393
scale_atmos_hydrometeor::num_name
character(len=h_short), dimension(n_hyd), parameter, public num_name
Definition: scale_atmos_hydrometeor.F90:108
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:106
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
scale_atmos_hydrometeor::i_hr
integer, parameter, public i_hr
liquid water rain
Definition: scale_atmos_hydrometeor.F90:98
mod_atmos_phy_mp_vars::qa_mp
integer, public qa_mp
Definition: mod_atmos_phy_mp_vars.F90:78
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:629
scale_tracer::qa
integer, public qa
Definition: scale_tracer.F90:35
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:55
scale_atmos_hydrometeor::i_hs
integer, parameter, public i_hs
snow
Definition: scale_atmos_hydrometeor.F90:100
scale_atmos_hydrometeor::hyd_name
character(len=h_short), dimension(n_hyd), parameter, public hyd_name
Definition: scale_atmos_hydrometeor.F90:104
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:964
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:3360
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:65
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:79
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:1646
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:78
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:59
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_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:54
scale_atmos_hydrometeor::i_hh
integer, parameter, public i_hh
hail
Definition: scale_atmos_hydrometeor.F90:102
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:474
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_finalize
subroutine, public atmos_phy_mp_vars_finalize
Finalize.
Definition: mod_atmos_phy_mp_vars.F90:274
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:53
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:403
scale_atmos_grid_cartesc_index::jeb
integer, public jeb
Definition: scale_atmos_grid_cartesC_index.F90:67
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:64
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:99
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:56
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:2836
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:872
scale_tracer::k
real(rp), public k
Definition: scale_tracer.F90:45
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:84
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:70
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:1089
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:425
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:57
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:68
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:314
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:1717
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:60
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:2565
scale_file_cartesc::file_cartesc_close
subroutine, public file_cartesc_close(fid)
Close a netCDF file.
Definition: scale_file_cartesC.F90:1044
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:459
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
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:1508
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:1449
scale_atmos_hydrometeor::qha
integer, public qha
Definition: scale_atmos_hydrometeor.F90:131
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:496
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:97
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:917
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:71
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:73
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:1046
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:127
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:368
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:796
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:67
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:1018
scale_time::time_gettimelabel
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:93
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:66
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:51
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
scale_atmos_grid_cartesc_index::ieb
integer, public ieb
Definition: scale_atmos_grid_cartesC_index.F90:65
scale_file::file_get_aggregate
logical function, public file_get_aggregate(fid)
Definition: scale_file.F90:6316
scale_file_cartesc::file_cartesc_open
subroutine, public file_cartesc_open(basename, fid, single, aggregate)
open a netCDF file for read
Definition: scale_file_cartesC.F90:760
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:58
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:685
mod_atmos_phy_mp_vars::qe_mp
integer, public qe_mp
Definition: mod_atmos_phy_mp_vars.F90:80
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:333
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:62
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:88
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:879
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:69
scale_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:43
scale_atmos_grid_cartesc_index::jsb
integer, public jsb
Definition: scale_atmos_grid_cartesC_index.F90:66
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:2528
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:454
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:518
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:57
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:95
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:440
scale_atmos_hydrometeor::i_hg
integer, parameter, public i_hg
graupel
Definition: scale_atmos_hydrometeor.F90:101