SCALE-RM
mod_atmos_phy_cp_vars.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
12 !-------------------------------------------------------------------------------
13 #include "inc_openmp.h"
15  !-----------------------------------------------------------------------------
16  !
17  !++ used modules
18  !
19  use scale_precision
20  use scale_stdio
21  use scale_prof
23  use scale_tracer
24  !-----------------------------------------------------------------------------
25  implicit none
26  private
27  !-----------------------------------------------------------------------------
28  !
29  !++ Public procedure
30  !
31  public :: atmos_phy_cp_vars_setup
35 
41 
42  !-----------------------------------------------------------------------------
43  !
44  !++ Public parameters & variables
45  !
46  logical, public :: atmos_phy_cp_restart_output = .false.
47 
48  character(len=H_LONG), public :: atmos_phy_cp_restart_in_basename = ''
49  logical, public :: atmos_phy_cp_restart_in_postfix_timelabel = .false.
50  character(len=H_LONG), public :: atmos_phy_cp_restart_out_basename = ''
51  logical, public :: atmos_phy_cp_restart_out_postfix_timelabel = .true.
52  character(len=H_MID), public :: atmos_phy_cp_restart_out_title = 'ATMOS_PHY_CP restart'
53  character(len=H_SHORT), public :: atmos_phy_cp_restart_out_dtype = 'DEFAULT'
54 
55  real(RP), public, allocatable :: atmos_phy_cp_dens_t(:,:,:) ! tendency DENS [kg/m3/s]
56  real(RP), public, allocatable :: atmos_phy_cp_momz_t(:,:,:) ! tendency MOMZ [kg/m2/s2]
57  real(RP), public, allocatable :: atmos_phy_cp_momx_t(:,:,:) ! tendency MOMX [kg/m2/s2]
58  real(RP), public, allocatable :: atmos_phy_cp_momy_t(:,:,:) ! tendency MOMY [kg/m2/s2]
59  real(RP), public, allocatable :: atmos_phy_cp_rhot_t(:,:,:) ! tendency RHOT [K*kg/m3/s]
60  real(RP), public, allocatable :: atmos_phy_cp_rhoq_t(:,:,:,:) ! tendency rho*QTRC [kg/kg/s]
61 
62  real(RP), public, allocatable :: atmos_phy_cp_mflx_cloudbase(:,:) ! cloud base mass flux [kg/m2/s]
63  real(RP), public, allocatable :: atmos_phy_cp_sflx_rain (:,:) ! convective rain [kg/m2/s]
64  real(RP), public, allocatable :: atmos_phy_cp_cloudtop (:,:) ! cloud top height [m]
65  real(RP), public, allocatable :: atmos_phy_cp_cloudbase (:,:) ! cloud base height [m]
66  real(RP), public, allocatable :: atmos_phy_cp_cldfrac_dp (:,:,:) ! cloud fraction (deep convection) (0-1)
67  real(RP), public, allocatable :: atmos_phy_cp_cldfrac_sh (:,:,:) ! cloud fraction (shallow convection) (0-1)
68  ! only for K-F scheme
69  real(RP), public, allocatable :: atmos_phy_cp_kf_nca (:,:) ! advection/cumulus convection timescale/dt for KF[step]
70  real(RP), public, allocatable :: atmos_phy_cp_kf_w0avg (:,:,:) ! running mean vertical wind velocity for KF[m/s]
71 
72  !-----------------------------------------------------------------------------
73  !
74  !++ Private procedure
75  !
76  !-----------------------------------------------------------------------------
77  !
78  !++ Private parameters & variables
79  !
80  integer, private, parameter :: vmax = 8
81  integer, private, parameter :: i_mflx_cloudbase = 1
82  integer, private, parameter :: i_sflx_convrain = 2
83  integer, private, parameter :: i_cloudtop = 3
84  integer, private, parameter :: i_cloudbase = 4
85  integer, private, parameter :: i_cldfrac_dp = 5
86  integer, private, parameter :: i_cldfrac_sh = 6
87  integer, private, parameter :: i_kf_nca = 7
88  integer, private, parameter :: i_kf_w0avg = 8
89 
90  character(len=H_SHORT), private :: var_name(vmax)
91  character(len=H_MID), private :: var_desc(vmax)
92  character(len=H_SHORT), private :: var_unit(vmax)
93  integer, private :: var_id (vmax)
94  integer, private :: restart_fid = -1 ! file ID
95 
96  data var_name / 'MFLX_cloudbase', &
97  'SFLX_convrain', &
98  'cloudtop', &
99  'cloudbase', &
100  'cldfrac_dp', &
101  'cldfrac_sh', &
102  'kf_nca', &
103  'kf_w0avg' /
104  data var_desc / 'cloud base mass flux', &
105  'convective rain', &
106  'cloud top height', &
107  'cloud base height', &
108  'cloud fraction (deep convection)', &
109  'cloud fraction (shallow convection)', &
110  'advection/cumulus convection timescale/dt for KF', &
111  'running mean vertical wind velocity for KF' /
112  data var_unit / 'kg/m2/s', &
113  'kg/m2/s', &
114  'm', &
115  'm', &
116  '1', &
117  '1', &
118  'step', &
119  'm/s' /
120 
121  ! tendency names
122  integer, private :: vmax_t
123  integer, private :: i_cp_dens_t = 1
124  integer, private :: i_cp_rhot_t = 2
125 
126  character(len=H_SHORT), private, allocatable :: var_t_name(:)
127  character(len=H_MID), private, allocatable :: var_t_desc(:)
128  character(len=H_SHORT), private, allocatable :: var_t_unit(:)
129  integer, private, allocatable :: var_t_id (:)
130 
131  !-----------------------------------------------------------------------------
132 contains
133  !-----------------------------------------------------------------------------
135  subroutine atmos_phy_cp_vars_setup
136  use scale_process, only: &
138  use scale_const, only: &
139  undef => const_undef
140  use scale_atmos_phy_mp, only: &
141  aq_name => atmos_phy_mp_name, &
142  qs_mp, &
143  qe_mp, &
144  qa_mp
145  implicit none
146 
147  namelist / param_atmos_phy_cp_vars / &
155 
156  integer :: ierr
157  integer :: iv
158  integer :: iq
159  !---------------------------------------------------------------------------
160 
161  if( io_l ) write(io_fid_log,*)
162  if( io_l ) write(io_fid_log,*) '++++++ Module[VARS] / Categ[ATMOS PHY_CP] / Origin[SCALE-RM]'
163 
164  allocate( atmos_phy_cp_dens_t(ka,ia,ja) )
165  allocate( atmos_phy_cp_momz_t(ka,ia,ja) )
166  allocate( atmos_phy_cp_momx_t(ka,ia,ja) )
167  allocate( atmos_phy_cp_momy_t(ka,ia,ja) )
168  allocate( atmos_phy_cp_rhot_t(ka,ia,ja) )
169  allocate( atmos_phy_cp_rhoq_t(ka,ia,ja,qs_mp:qe_mp) )
170  atmos_phy_cp_dens_t(:,:,:) = 0.0_rp
171  atmos_phy_cp_momz_t(:,:,:) = undef
172  atmos_phy_cp_momx_t(:,:,:) = undef
173  atmos_phy_cp_momy_t(:,:,:) = undef
174  atmos_phy_cp_rhot_t(:,:,:) = 0.0_rp
175  atmos_phy_cp_rhoq_t(:,:,:,:) = 0.0_rp
176 
177  allocate( atmos_phy_cp_mflx_cloudbase(ia,ja) )
178  allocate( atmos_phy_cp_sflx_rain(ia,ja) )
179  allocate( atmos_phy_cp_cloudtop(ia,ja) )
180  allocate( atmos_phy_cp_cloudbase(ia,ja) )
181  allocate( atmos_phy_cp_cldfrac_dp(ka,ia,ja) )
182  allocate( atmos_phy_cp_cldfrac_sh(ka,ia,ja) )
183  allocate( atmos_phy_cp_kf_nca(ia,ja) )
184  allocate( atmos_phy_cp_kf_w0avg(ka,ia,ja) )
185  atmos_phy_cp_mflx_cloudbase(:,:) = 0.0_rp
186  atmos_phy_cp_sflx_rain(:,:) = 0.0_rp
187  atmos_phy_cp_cloudtop(:,:) = 0.0_rp
188  atmos_phy_cp_cloudbase(:,:) = 0.0_rp
189  atmos_phy_cp_cldfrac_dp(:,:,:) = 0.0_rp
190  atmos_phy_cp_cldfrac_sh(:,:,:) = 0.0_rp
191  atmos_phy_cp_kf_nca(:,:) = -100.0_rp
192  atmos_phy_cp_kf_w0avg(:,:,:) = 0.0_rp
193 
194  ! for tendency restart
195  vmax_t = 2 + qa_mp
196  allocate( var_t_name(vmax_t) )
197  allocate( var_t_desc(vmax_t) )
198  allocate( var_t_unit(vmax_t) )
199  allocate( var_t_id(vmax_t) )
200 
201  var_t_name(i_cp_dens_t) = 'DENS_t_CP'
202  var_t_desc(i_cp_dens_t) = 'tendency DENS in CP'
203  var_t_unit(i_cp_dens_t) = 'kg/m3/s'
204  var_t_name(i_cp_rhot_t) = 'RHOT_t_CP'
205  var_t_desc(i_cp_rhot_t) = 'tendency RHOT in CP'
206  var_t_unit(i_cp_rhot_t) = 'K*kg/m3/s'
207 
208  do iq = 1, qa_mp
209  var_t_name(2+iq) = trim(aq_name(iq))//'_t_CP'
210  var_t_desc(2+iq) = 'tendency rho*'//trim(aq_name(iq))//' in CP'
211  var_t_unit(2+iq) = 'kg/m3/s'
212  enddo
213 
214  !--- read namelist
215  rewind(io_fid_conf)
216  read(io_fid_conf,nml=param_atmos_phy_cp_vars,iostat=ierr)
217  if( ierr < 0 ) then !--- missing
218  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
219  elseif( ierr > 0 ) then !--- fatal error
220  write(*,*) 'xxx Not appropriate names in namelist PARAM_ATMOS_PHY_CP_VARS. Check!'
221  call prc_mpistop
222  endif
223  if( io_nml ) write(io_fid_nml,nml=param_atmos_phy_cp_vars)
224 
225  if( io_l ) write(io_fid_log,*)
226  if( io_l ) write(io_fid_log,*) '*** [ATMOS_PHY_CP] prognostic/diagnostic variables'
227  if( io_l ) write(io_fid_log,'(1x,A,A24,A,A48,A,A12,A)') &
228  '*** |', 'VARNAME ','|', &
229  'DESCRIPTION ', '[', 'UNIT ', ']'
230  do iv = 1, vmax
231  if( io_l ) write(io_fid_log,'(1x,A,I3,A,A24,A,A48,A,A12,A)') &
232  '*** NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
233  enddo
234 
235  ! tendency
236  do iv = 1, vmax_t
237  if( io_l ) write(io_fid_log,'(1x,A,I3,A,A24,A,A48,A,A12,A)') &
238  '*** NO.',iv+vmax,'|',var_t_name(iv),'|',var_t_desc(iv),'[',var_t_unit(iv),']'
239  enddo
240 
241  if( io_l ) write(io_fid_log,*)
242  if ( atmos_phy_cp_restart_in_basename /= '' ) then
243  if( io_l ) write(io_fid_log,*) '*** Restart input? : YES, file = ', trim(atmos_phy_cp_restart_in_basename)
244  if( io_l ) write(io_fid_log,*) '*** Add timelabel? : ', atmos_phy_cp_restart_in_postfix_timelabel
245  else
246  if( io_l ) write(io_fid_log,*) '*** Restart input? : NO'
247  endif
249  .AND. atmos_phy_cp_restart_out_basename /= '' ) then
250  if( io_l ) write(io_fid_log,*) '*** Restart output? : YES, file = ', trim(atmos_phy_cp_restart_out_basename)
251  if( io_l ) write(io_fid_log,*) '*** Add timelabel? : ', atmos_phy_cp_restart_out_postfix_timelabel
252  else
253  if( io_l ) write(io_fid_log,*) '*** Restart output? : NO'
255  endif
256 
257  return
258  end subroutine atmos_phy_cp_vars_setup
259 
260  !-----------------------------------------------------------------------------
262  subroutine atmos_phy_cp_vars_fillhalo
263  use scale_comm, only: &
264  comm_vars8, &
265  comm_wait
266  use scale_atmos_phy_mp, only: &
267  qa_mp
268  implicit none
269 
270  integer :: i, j
271  integer :: iq
272  !---------------------------------------------------------------------------
273 
274  do j = js, je
275  do i = is, ie
286  enddo
287  enddo
288 
289  do iq = 1, qa_mp
290  do j = js, je
291  do i = is, ie
292  atmos_phy_cp_rhoq_t( 1:ks-1,i,j,iq) = atmos_phy_cp_rhoq_t(ks,i,j,iq)
293  atmos_phy_cp_rhoq_t(ke+1:ka ,i,j,iq) = atmos_phy_cp_rhoq_t(ke,i,j,iq)
294  enddo
295  enddo
296  end do
297 
298  call comm_vars8( atmos_phy_cp_mflx_cloudbase(:,:) , 1 )
299  call comm_vars8( atmos_phy_cp_sflx_rain(:,:) , 2 )
300  call comm_vars8( atmos_phy_cp_cloudtop(:,:) , 3 )
301  call comm_vars8( atmos_phy_cp_cloudbase(:,:) , 4 )
302  call comm_vars8( atmos_phy_cp_cldfrac_dp(:,:,:), 5 )
303  call comm_vars8( atmos_phy_cp_cldfrac_sh(:,:,:), 6 )
304  call comm_vars8( atmos_phy_cp_kf_nca(:,:) , 7 )
305  call comm_vars8( atmos_phy_cp_kf_w0avg(:,:,:), 8 )
306 
307  ! tendency
308  call comm_vars8( atmos_phy_cp_dens_t(:,:,:), vmax+1 )
309  call comm_vars8( atmos_phy_cp_rhot_t(:,:,:), vmax+2 )
310 
311  do iq = 1, qa_mp
312  call comm_vars8( atmos_phy_cp_rhoq_t(:,:,:,iq), vmax+2+iq )
313  enddo
314 
315  call comm_wait ( atmos_phy_cp_mflx_cloudbase(:,:) , 1 )
316  call comm_wait ( atmos_phy_cp_sflx_rain(:,:) , 2 )
317  call comm_wait ( atmos_phy_cp_cloudtop(:,:) , 3 )
318  call comm_wait ( atmos_phy_cp_cloudbase(:,:) , 4 )
319  call comm_wait ( atmos_phy_cp_cldfrac_dp(:,:,:), 5 )
320  call comm_wait ( atmos_phy_cp_cldfrac_sh(:,:,:), 6 )
321  call comm_wait ( atmos_phy_cp_kf_nca(:,:) , 7 )
322  call comm_wait ( atmos_phy_cp_kf_w0avg(:,:,:), 8 )
323 
324  call comm_wait ( atmos_phy_cp_dens_t(:,:,:), vmax+1 )
325  call comm_wait ( atmos_phy_cp_rhot_t(:,:,:), vmax+2 )
326 
327  do iq = 1, qa_mp
328  call comm_wait ( atmos_phy_cp_rhoq_t(:,:,:,iq), vmax+2+iq )
329  enddo
330 
331  return
332  end subroutine atmos_phy_cp_vars_fillhalo
333 
334  !-----------------------------------------------------------------------------
337  use scale_time, only: &
339  use scale_fileio, only: &
341  implicit none
342 
343  character(len=19) :: timelabel
344  character(len=H_LONG) :: basename
345  !---------------------------------------------------------------------------
346 
347  if( io_l ) write(io_fid_log,*)
348  if( io_l ) write(io_fid_log,*) '*** Open restart file (ATMOS_PHY_CP) ***'
349 
350  if ( atmos_phy_cp_restart_in_basename /= '' ) then
351 
353  call time_gettimelabel( timelabel )
354  basename = trim(atmos_phy_cp_restart_in_basename)//'_'//trim(timelabel)
355  else
356  basename = trim(atmos_phy_cp_restart_in_basename)
357  endif
358 
359  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
360 
361  call fileio_open( restart_fid, basename )
362  else
363  if( io_l ) write(io_fid_log,*) '*** restart file for ATMOS_PHY_CP is not specified.'
364  endif
365 
366  return
367  end subroutine atmos_phy_cp_vars_restart_open
368 
369  !-----------------------------------------------------------------------------
372  use scale_rm_statistics, only: &
374  stat_total
375  use scale_fileio, only: &
376  fileio_read, &
378  use scale_atmos_phy_mp, only: &
379  qa_mp
380  implicit none
381 
382  real(RP) :: total
383  integer :: i, j, iq
384  !---------------------------------------------------------------------------
385 
386  if ( restart_fid /= -1 ) then
387  if( io_l ) write(io_fid_log,*)
388  if( io_l ) write(io_fid_log,*) '*** Read from restart file (ATMOS_PHY_CP) ***'
389 
390  call fileio_read( atmos_phy_cp_mflx_cloudbase(:,:), & ! [OUT]
391  restart_fid, var_name(1), 'XY', step=1 ) ! [IN]
392  call fileio_read( atmos_phy_cp_sflx_rain(:,:), & ! [OUT]
393  restart_fid, var_name(2), 'XY', step=1 ) ! [IN]
394  call fileio_read( atmos_phy_cp_cloudtop(:,:), & ! [OUT]
395  restart_fid, var_name(3), 'XY', step=1 ) ! [IN]
396  call fileio_read( atmos_phy_cp_cloudbase(:,:), & ! [OUT]
397  restart_fid, var_name(4), 'XY', step=1 ) ! [IN]
398  call fileio_read( atmos_phy_cp_cldfrac_dp(:,:,:), & ! [OUT]
399  restart_fid, var_name(5), 'ZXY', step=1 ) ! [IN]
400  call fileio_read( atmos_phy_cp_cldfrac_sh(:,:,:), & ! [OUT]
401  restart_fid, var_name(6), 'ZXY', step=1 ) ! [IN]
402  call fileio_read( atmos_phy_cp_kf_nca(:,:), & ! [OUT]
403  restart_fid, var_name(7), 'XY', step=1 ) ! [IN]
404  call fileio_read( atmos_phy_cp_kf_w0avg(:,:,:), & ! [OUT]
405  restart_fid, var_name(8), 'ZXY', step=1 ) ! [IN]
406  ! tendency
407  call fileio_read( atmos_phy_cp_dens_t(:,:,:), & ! [OUT]
408  restart_fid, var_t_name(1), 'ZXY', step=1 ) ! [IN]
409  call fileio_read( atmos_phy_cp_rhot_t(:,:,:), & ! [OUT]
410  restart_fid, var_t_name(2), 'ZXY', step=1 ) ! [IN]
411  do iq = 1, qa_mp
412  call fileio_read( atmos_phy_cp_rhoq_t(:,:,:,iq), & ! [OUT]
413  restart_fid, var_t_name(2+iq), 'ZXY', step=1 ) ! [IN]
414  enddo
415 
416  if ( io_aggregate ) then
417  call fileio_flush( restart_fid ) ! X/Y halos have been read from file
418 
419  ! fill K halos
420  do j = 1, ja
421  do i = 1, ia
432  enddo
433  enddo
434 
435  do iq = 1, qa_mp
436  do j = 1, ja
437  do i = 1, ia
438  atmos_phy_cp_rhoq_t( 1:ks-1,i,j,iq) = atmos_phy_cp_rhoq_t(ks,i,j,iq)
439  atmos_phy_cp_rhoq_t(ke+1:ka, i,j,iq) = atmos_phy_cp_rhoq_t(ke,i,j,iq)
440  enddo
441  enddo
442  enddo
443  else
445  end if
446 
447  if ( statistics_checktotal ) then
448  call stat_total( total, atmos_phy_cp_mflx_cloudbase(:,:) , var_name(1) )
449  call stat_total( total, atmos_phy_cp_sflx_rain(:,:) , var_name(2) )
450  call stat_total( total, atmos_phy_cp_cloudtop(:,:) , var_name(3) )
451  call stat_total( total, atmos_phy_cp_cloudbase(:,:) , var_name(4) )
452  call stat_total( total, atmos_phy_cp_cldfrac_dp(:,:,:), var_name(5) )
453  call stat_total( total, atmos_phy_cp_cldfrac_sh(:,:,:), var_name(6) )
454  call stat_total( total, atmos_phy_cp_kf_nca(:,:) , var_name(7) )
455  call stat_total( total, atmos_phy_cp_kf_w0avg(:,:,:), var_name(8) )
456  ! tendency
457  call stat_total( total, atmos_phy_cp_dens_t(:,:,:), var_t_name(1) )
458  call stat_total( total, atmos_phy_cp_rhot_t(:,:,:), var_t_name(2) )
459  do iq = 1, qa_mp
460  call stat_total( total, atmos_phy_cp_rhoq_t(:,:,:,iq), var_t_name(2+iq) )
461  enddo
462  endif
463  else
464  if( io_l ) write(io_fid_log,*) '*** invalid restart file ID for ATMOS_PHY_CP.'
465  endif
466 
467  return
468  end subroutine atmos_phy_cp_vars_restart_read
469 
470  !-----------------------------------------------------------------------------
473  use scale_time, only: &
475  use scale_fileio, only: &
477  implicit none
478 
479  character(len=19) :: timelabel
480  character(len=H_LONG) :: basename
481  !---------------------------------------------------------------------------
482 
483  if ( atmos_phy_cp_restart_out_basename /= '' ) then
484 
485  if( io_l ) write(io_fid_log,*)
486  if( io_l ) write(io_fid_log,*) '*** Create restart file (ATMOS_PHY_AE) ***'
487 
489  call time_gettimelabel( timelabel )
490  basename = trim(atmos_phy_cp_restart_out_basename)//'_'//trim(timelabel)
491  else
492  basename = trim(atmos_phy_cp_restart_out_basename)
493  endif
494 
495  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
496 
497  call fileio_create( restart_fid, & ! [OUT]
499 
500  endif
501 
502  return
503  end subroutine atmos_phy_cp_vars_restart_create
504 
505  !-----------------------------------------------------------------------------
508  use scale_fileio, only: &
510  implicit none
511 
512  if ( restart_fid /= -1 ) then
513  call fileio_enddef( restart_fid ) ! [IN]
514  endif
515 
516  return
517  end subroutine atmos_phy_cp_vars_restart_enddef
518 
519  !-----------------------------------------------------------------------------
522  use scale_fileio, only: &
524  implicit none
525  !---------------------------------------------------------------------------
526 
527  if ( restart_fid /= -1 ) then
528  if( io_l ) write(io_fid_log,*)
529  if( io_l ) write(io_fid_log,*) '*** Close restart file (ATMOS_PHY_CP) ***'
530 
531  call fileio_close( restart_fid ) ! [IN]
532 
533  restart_fid = -1
534  endif
535 
536  return
537  end subroutine atmos_phy_cp_vars_restart_close
538 
539  !-----------------------------------------------------------------------------
542  use scale_fileio, only: &
544  use scale_atmos_phy_mp, only: &
545  qa_mp
546  implicit none
547 
548  integer :: iq
549  !---------------------------------------------------------------------------
550 
551  if ( restart_fid /= -1 ) then
552 
553  call fileio_def_var( restart_fid, var_id(1), var_name(1), var_desc(1), &
554  var_unit(1), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
555  call fileio_def_var( restart_fid, var_id(2), var_name(2), var_desc(2), &
556  var_unit(2), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
557  call fileio_def_var( restart_fid, var_id(3), var_name(3), var_desc(3), &
558  var_unit(3), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
559  call fileio_def_var( restart_fid, var_id(4), var_name(4), var_desc(4), &
560  var_unit(4), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
561  call fileio_def_var( restart_fid, var_id(5), var_name(5), var_desc(5), &
562  var_unit(5), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
563  call fileio_def_var( restart_fid, var_id(6), var_name(6), var_desc(6), &
564  var_unit(6), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
565  call fileio_def_var( restart_fid, var_id(7), var_name(7), var_desc(7), &
566  var_unit(7), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
567  call fileio_def_var( restart_fid, var_id(8), var_name(8), var_desc(8), &
568  var_unit(8), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
569 
570  call fileio_def_var( restart_fid, var_t_id(1), var_t_name(1), var_t_desc(1), &
571  var_t_unit(1), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
572  call fileio_def_var( restart_fid, var_t_id(2), var_t_name(2), var_t_desc(2), &
573  var_t_unit(2), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
574 
575  do iq = 1, qa_mp
576  call fileio_def_var( restart_fid, var_t_id(2+iq), var_t_name(2+iq), var_t_desc(2+iq), &
577  var_t_unit(2+iq), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
578  enddo
579 
580  endif
581 
582  return
583  end subroutine atmos_phy_cp_vars_restart_def_var
584 
585  !-----------------------------------------------------------------------------
588  use scale_rm_statistics, only: &
590  stat_total
591  use scale_fileio, only: &
592  fileio_write => fileio_write_var
593  use scale_atmos_phy_mp, only: &
594  qa_mp
595  implicit none
596 
597  real(RP) :: total
598  integer :: iq
599  !---------------------------------------------------------------------------
600 
601  if ( restart_fid /= -1 ) then
602 
604 
605  if ( statistics_checktotal ) then
606  call stat_total( total, atmos_phy_cp_mflx_cloudbase(:,:) , var_name(1) )
607  call stat_total( total, atmos_phy_cp_sflx_rain(:,:) , var_name(2) )
608  call stat_total( total, atmos_phy_cp_cloudtop(:,:) , var_name(3) )
609  call stat_total( total, atmos_phy_cp_cloudbase(:,:) , var_name(4) )
610  call stat_total( total, atmos_phy_cp_cldfrac_dp(:,:,:), var_name(5) )
611  call stat_total( total, atmos_phy_cp_cldfrac_sh(:,:,:), var_name(6) )
612  call stat_total( total, atmos_phy_cp_kf_nca(:,:) , var_name(7) )
613  call stat_total( total, atmos_phy_cp_kf_w0avg(:,:,:), var_name(8) )
614  ! tendency
615  call stat_total( total, atmos_phy_cp_dens_t(:,:,:), var_t_name(1) )
616  call stat_total( total, atmos_phy_cp_rhot_t(:,:,:), var_t_name(2) )
617  do iq = 1, qa_mp
618  call stat_total( total, atmos_phy_cp_rhoq_t(:,:,:,iq), var_t_name(2+iq) )
619  enddo
620  endif
621 
622  call fileio_write( restart_fid, var_id(1), atmos_phy_cp_mflx_cloudbase(:,:), & ! [IN]
623  var_name(1), 'XY' ) ! [IN]
624  call fileio_write( restart_fid, var_id(2), atmos_phy_cp_sflx_rain(:,:), & ! [IN]
625  var_name(2), 'XY' ) ! [IN]
626  call fileio_write( restart_fid, var_id(3), atmos_phy_cp_cloudtop(:,:), & ! [IN]
627  var_name(3), 'XY' ) ! [IN]
628  call fileio_write( restart_fid, var_id(4), atmos_phy_cp_cloudbase(:,:), & ! [IN]
629  var_name(4), 'XY' ) ! [IN]
630  call fileio_write( restart_fid, var_id(5), atmos_phy_cp_cldfrac_dp(:,:,:), & ! [IN]
631  var_name(5), 'ZXY' ) ! [IN]
632  call fileio_write( restart_fid, var_id(6), atmos_phy_cp_cldfrac_sh(:,:,:), & ! [IN]
633  var_name(6), 'ZXY' ) ! [IN]
634  call fileio_write( restart_fid, var_id(7), atmos_phy_cp_kf_nca(:,:), & ! [IN]
635  var_name(7), 'XY' ) ! [IN]
636  call fileio_write( restart_fid, var_id(8), atmos_phy_cp_kf_w0avg(:,:,:), & ! [IN]
637  var_name(8), 'ZXY' ) ! [IN]
638 
639  ! tendency
640  call fileio_write( restart_fid, var_t_id(1), atmos_phy_cp_dens_t(:,:,:), & ! [IN]
641  var_t_name(1), 'ZXY' ) ! [IN]
642  call fileio_write( restart_fid, var_t_id(2), atmos_phy_cp_rhot_t(:,:,:), & ! [IN]
643  var_t_name(2), 'ZXY' ) ! [IN]
644  do iq = 1, qa_mp
645  call fileio_write( restart_fid, var_t_id(2+iq), atmos_phy_cp_rhoq_t(:,:,:,iq), & ! [IN]
646  var_t_name(2+iq), 'ZXY' ) ! [IN]
647  enddo
648 
649  endif
650 
651  return
652  end subroutine atmos_phy_cp_vars_restart_write
653 
654 end module mod_atmos_phy_cp_vars
integer, public is
start point of inner domain: x, local
subroutine, public atmos_phy_cp_vars_restart_def_var
Write restart.
logical, public statistics_checktotal
calc&report variable totals to logfile?
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momy_t
integer, public je
end point of inner domain: y, local
module Atmosphere / Physics Cumulus
character(len=h_mid), public atmos_phy_cp_restart_out_title
title of the output file
subroutine, public prc_mpistop
Abort MPI.
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momx_t
character(len=h_long), public atmos_phy_cp_restart_in_basename
Basename of the input file.
subroutine, public atmos_phy_cp_vars_restart_enddef
Exit netCDF define mode.
subroutine, public atmos_phy_cp_vars_restart_open
Open restart file for read.
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:61
subroutine, public atmos_phy_cp_vars_restart_write
Write restart.
logical, public atmos_phy_cp_restart_output
output restart file?
subroutine, public fileio_flush(fid)
Flush all pending requests to a netCDF file (PnetCDF only)
module ATMOSPHERE / Physics Cloud Microphysics
logical, public atmos_phy_cp_restart_in_postfix_timelabel
Add timelabel to the basename of input file?
character(len=h_long), public atmos_phy_cp_restart_out_basename
Basename of the output file.
module STDIO
Definition: scale_stdio.F90:12
integer, public ke
end point of inner domain: z, local
subroutine, public atmos_phy_cp_vars_restart_create
Create restart file.
logical, public atmos_phy_cp_restart_out_postfix_timelabel
Add timelabel to the basename of output file?
character(len=h_short), dimension(:), pointer, public atmos_phy_mp_name
module FILE I/O (netcdf)
character(len=h_short), public atmos_phy_cp_restart_out_dtype
REAL4 or REAL8.
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_dens_t
real(rp), public const_undef
Definition: scale_const.F90:43
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhoq_t
subroutine, public atmos_phy_cp_vars_restart_close
Close restart file.
module Statistics
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_cldfrac_dp
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_kf_w0avg
module grid index
logical, public io_nml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:62
subroutine, public atmos_phy_cp_vars_setup
Setup.
module TRACER
integer, public ia
of whole cells: x, local, with HALO
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
integer, public ka
of whole cells: z, local, with HALO
subroutine, public atmos_phy_cp_vars_fillhalo
HALO Communication.
subroutine, public fileio_create(fid, basename, title, datatype, date, subsec, append, nozcoord)
Create/open a netCDF file.
module COMMUNICATION
Definition: scale_comm.F90:23
integer, public js
start point of inner domain: y, local
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momz_t
module PROCESS
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t
module CONSTANT
Definition: scale_const.F90:14
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_cloudtop
integer, public ks
start point of inner domain: z, local
subroutine, public fileio_enddef(fid)
Exit netCDF file define mode.
module profiler
Definition: scale_prof.F90:10
integer, public ie
end point of inner domain: x, local
logical, public io_aggregate
do parallel I/O through PnetCDF
Definition: scale_stdio.F90:66
subroutine, public fileio_open(fid, basename)
open a netCDF file for read
module PRECISION
subroutine, public fileio_def_var(fid, vid, varname, desc, unit, axistype, datatype, timeintv, nsteps)
Define a variable to file.
subroutine, public atmos_phy_cp_vars_restart_read
Read restart.
subroutine, public fileio_close(fid)
Close a netCDF file.
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_cloudbase
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_cldfrac_sh
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
integer, public io_fid_nml
Log file ID (only for output namelist)
Definition: scale_stdio.F90:57
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_kf_nca
integer, public ja
of whole cells: y, local, with HALO