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  character(len=H_LONG), public :: atmos_phy_cp_restart_out_basename = ''
50  character(len=H_MID), public :: atmos_phy_cp_restart_out_title = 'ATMOS_PHY_CP restart'
51  character(len=H_MID), public :: atmos_phy_cp_restart_out_dtype = 'DEFAULT'
52 
53  real(RP), public, allocatable :: atmos_phy_cp_dens_t(:,:,:) ! tendency DENS [kg/m3/s]
54  real(RP), public, allocatable :: atmos_phy_cp_momz_t(:,:,:) ! tendency MOMZ [kg/m2/s2]
55  real(RP), public, allocatable :: atmos_phy_cp_momx_t(:,:,:) ! tendency MOMX [kg/m2/s2]
56  real(RP), public, allocatable :: atmos_phy_cp_momy_t(:,:,:) ! tendency MOMY [kg/m2/s2]
57  real(RP), public, allocatable :: atmos_phy_cp_rhot_t(:,:,:) ! tendency RHOT [K*kg/m3/s]
58  real(RP), public, allocatable :: atmos_phy_cp_rhoq_t(:,:,:,:) ! tendency rho*QTRC [kg/kg/s]
59 
60  real(RP), public, allocatable :: atmos_phy_cp_mflx_cloudbase(:,:) ! cloud base mass flux [kg/m2/s]
61  real(RP), public, allocatable :: atmos_phy_cp_sflx_rain (:,:) ! convective rain [kg/m2/s]
62  real(RP), public, allocatable :: atmos_phy_cp_cloudtop (:,:) ! cloud top height [m]
63  real(RP), public, allocatable :: atmos_phy_cp_cloudbase (:,:) ! cloud base height [m]
64  real(RP), public, allocatable :: atmos_phy_cp_cldfrac_dp (:,:,:) ! cloud fraction (deep convection) [0-1]
65  real(RP), public, allocatable :: atmos_phy_cp_cldfrac_sh (:,:,:) ! cloud fraction (shallow convection) [0-1]
66  ! only for K-F scheme
67  real(RP), public, allocatable :: atmos_phy_cp_kf_nca (:,:) ! advection/cumulus convection timescale/dt for KF[step]
68  real(RP), public, allocatable :: atmos_phy_cp_kf_w0avg (:,:,:) ! running mean vertical wind velocity for KF[m/s]
69 
70  !-----------------------------------------------------------------------------
71  !
72  !++ Private procedure
73  !
74  !-----------------------------------------------------------------------------
75  !
76  !++ Private parameters & variables
77  !
78  integer, private, parameter :: vmax = 8
79  integer, private, parameter :: i_mflx_cloudbase = 1
80  integer, private, parameter :: i_sflx_convrain = 2
81  integer, private, parameter :: i_cloudtop = 3
82  integer, private, parameter :: i_cloudbase = 4
83  integer, private, parameter :: i_cldfrac_dp = 5
84  integer, private, parameter :: i_cldfrac_sh = 6
85  integer, private, parameter :: i_kf_nca = 7
86  integer, private, parameter :: i_kf_w0avg = 8
87 
88  character(len=H_SHORT), private :: var_name(vmax)
89  character(len=H_MID), private :: var_desc(vmax)
90  character(len=H_SHORT), private :: var_unit(vmax)
91  integer, private :: var_id (vmax)
92  integer, private :: restart_fid = -1 ! file ID
93 
94  data var_name / 'MFLX_cloudbase', &
95  'SFLX_convrain', &
96  'cloudtop', &
97  'cloudbase', &
98  'cldfrac_dp', &
99  'cldfrac_sh', &
100  'kf_nca', &
101  'kf_w0avg' /
102  data var_desc / 'cloud base mass flux', &
103  'convective rain', &
104  'cloud top height', &
105  'cloud base height', &
106  'cloud fraction (deep convection)', &
107  'cloud fraction (shallow convection)', &
108  'advection/cumulus convection timescale/dt for KF', &
109  'running mean vertical wind velocity for KF' /
110  data var_unit / 'kg/m2/s', &
111  'kg/m2/s', &
112  'm', &
113  'm', &
114  '0-1', &
115  '0-1', &
116  'step', &
117  'm/s' /
118 
119  ! tendency names
120  integer, private :: vmax_t
121  integer, private :: i_cp_dens_t = 1
122  integer, private :: i_cp_rhot_t = 2
123 
124  character(len=H_SHORT), private, allocatable :: var_t_name(:)
125  character(len=H_MID), private, allocatable :: var_t_desc(:)
126  character(len=H_SHORT), private, allocatable :: var_t_unit(:)
127  integer, private, allocatable :: var_t_id (:)
128 
129  !-----------------------------------------------------------------------------
130 contains
131  !-----------------------------------------------------------------------------
133  subroutine atmos_phy_cp_vars_setup
134  use scale_process, only: &
136  use scale_const, only: &
137  undef => const_undef
138  implicit none
139 
140  namelist / param_atmos_phy_cp_vars / &
146 
147  integer :: ierr
148  integer :: iv
149  integer :: iq
150  !---------------------------------------------------------------------------
151 
152  if( io_l ) write(io_fid_log,*)
153  if( io_l ) write(io_fid_log,*) '++++++ Module[VARS] / Categ[ATMOS PHY_CP] / Origin[SCALE-RM]'
154 
155  allocate( atmos_phy_cp_dens_t(ka,ia,ja) )
156  allocate( atmos_phy_cp_momz_t(ka,ia,ja) )
157  allocate( atmos_phy_cp_momx_t(ka,ia,ja) )
158  allocate( atmos_phy_cp_momy_t(ka,ia,ja) )
159  allocate( atmos_phy_cp_rhot_t(ka,ia,ja) )
160  allocate( atmos_phy_cp_rhoq_t(ka,ia,ja,qa) )
161  atmos_phy_cp_dens_t(:,:,:) = 0.0_rp
162  atmos_phy_cp_momz_t(:,:,:) = undef
163  atmos_phy_cp_momx_t(:,:,:) = undef
164  atmos_phy_cp_momy_t(:,:,:) = undef
165  atmos_phy_cp_rhot_t(:,:,:) = 0.0_rp
166  atmos_phy_cp_rhoq_t(:,:,:,:) = 0.0_rp
167 
168  allocate( atmos_phy_cp_mflx_cloudbase(ia,ja) )
169  allocate( atmos_phy_cp_sflx_rain(ia,ja) )
170  allocate( atmos_phy_cp_cloudtop(ia,ja) )
171  allocate( atmos_phy_cp_cloudbase(ia,ja) )
172  allocate( atmos_phy_cp_cldfrac_dp(ka,ia,ja) )
173  allocate( atmos_phy_cp_cldfrac_sh(ka,ia,ja) )
174  allocate( atmos_phy_cp_kf_nca(ia,ja) )
175  allocate( atmos_phy_cp_kf_w0avg(ka,ia,ja) )
176  atmos_phy_cp_mflx_cloudbase(:,:) = 0.0_rp
177  atmos_phy_cp_sflx_rain(:,:) = 0.0_rp
178  atmos_phy_cp_cloudtop(:,:) = 0.0_rp
179  atmos_phy_cp_cloudbase(:,:) = 0.0_rp
180  atmos_phy_cp_cldfrac_dp(:,:,:) = 0.0_rp
181  atmos_phy_cp_cldfrac_sh(:,:,:) = 0.0_rp
182  atmos_phy_cp_kf_nca(:,:) = -100.0_rp
183  atmos_phy_cp_kf_w0avg(:,:,:) = 0.0_rp
184 
185  ! for tendency restart
186  vmax_t = 2 + qa
187  allocate( var_t_name(vmax_t) )
188  allocate( var_t_desc(vmax_t) )
189  allocate( var_t_unit(vmax_t) )
190  allocate( var_t_id(vmax_t) )
191 
192  var_t_name(i_cp_dens_t) = 'DENS_t_CP'
193  var_t_desc(i_cp_dens_t) = 'tendency DENS in CP'
194  var_t_unit(i_cp_dens_t) = 'kg/m3/s'
195  var_t_name(i_cp_rhot_t) = 'RHOT_t_CP'
196  var_t_desc(i_cp_rhot_t) = 'tendency RHOT in CP'
197  var_t_unit(i_cp_rhot_t) = 'K*kg/m3/s'
198 
199  do iq = 1, qa
200  var_t_name(2+iq) = trim(aq_name(iq))//'_t_CP'
201  var_t_desc(2+iq) = 'tendency rho*'//trim(aq_name(iq))//'in CP'
202  var_t_unit(2+iq) = 'kg/m3/s'
203  enddo
204 
205  !--- read namelist
206  rewind(io_fid_conf)
207  read(io_fid_conf,nml=param_atmos_phy_cp_vars,iostat=ierr)
208  if( ierr < 0 ) then !--- missing
209  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
210  elseif( ierr > 0 ) then !--- fatal error
211  write(*,*) 'xxx Not appropriate names in namelist PARAM_ATMOS_PHY_CP_VARS. Check!'
212  call prc_mpistop
213  endif
214  if( io_lnml ) write(io_fid_log,nml=param_atmos_phy_cp_vars)
215 
216  if( io_l ) write(io_fid_log,*)
217  if( io_l ) write(io_fid_log,*) '*** [ATMOS_PHY_CP] prognostic/diagnostic variables'
218  if( io_l ) write(io_fid_log,'(1x,A,A15,A,A32,3(A))') &
219  '*** |','VARNAME ','|', 'DESCRIPTION ','[', 'UNIT ',']'
220  do iv = 1, vmax
221  if( io_l ) write(io_fid_log,'(1x,A,i3,A,A15,A,A32,3(A))') &
222  '*** NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
223  enddo
224 
225  ! tendency
226  do iv = 1, vmax_t
227  if( io_l ) write(io_fid_log,'(1x,A,i3,A,A15,A,A32,3(A))') &
228  '*** NO.',iv+vmax,'|',var_t_name(iv),'|',var_t_desc(iv),'[',var_t_unit(iv),']'
229  enddo
230 
231  if( io_l ) write(io_fid_log,*)
232  if ( atmos_phy_cp_restart_in_basename /= '' ) then
233  if( io_l ) write(io_fid_log,*) '*** Restart input? : ', trim(atmos_phy_cp_restart_in_basename)
234  else
235  if( io_l ) write(io_fid_log,*) '*** Restart input? : NO'
236  endif
238  .AND. atmos_phy_cp_restart_out_basename /= '' ) then
239  if( io_l ) write(io_fid_log,*) '*** Restart output? : ', trim(atmos_phy_cp_restart_out_basename)
240  else
241  if( io_l ) write(io_fid_log,*) '*** Restart output? : NO'
243  endif
244 
245  return
246  end subroutine atmos_phy_cp_vars_setup
247 
248  !-----------------------------------------------------------------------------
250  subroutine atmos_phy_cp_vars_fillhalo
251  use scale_comm, only: &
252  comm_vars8, &
253  comm_wait
254  implicit none
255 
256  integer :: i, j
257  integer :: iq
258  !---------------------------------------------------------------------------
259 
260  do j = js, je
261  do i = is, ie
272  do iq = 1, qa
273  atmos_phy_cp_rhoq_t( 1:ks-1,i,j,iq) = atmos_phy_cp_rhoq_t(ks,i,j,iq)
274  atmos_phy_cp_rhoq_t(ke+1:ka ,i,j,iq) = atmos_phy_cp_rhoq_t(ke,i,j,iq)
275  end do
276  enddo
277  enddo
278 
279  call comm_vars8( atmos_phy_cp_mflx_cloudbase(:,:) , 1 )
280  call comm_vars8( atmos_phy_cp_sflx_rain(:,:) , 2 )
281  call comm_vars8( atmos_phy_cp_cloudtop(:,:) , 3 )
282  call comm_vars8( atmos_phy_cp_cloudbase(:,:) , 4 )
283  call comm_vars8( atmos_phy_cp_cldfrac_dp(:,:,:), 5 )
284  call comm_vars8( atmos_phy_cp_cldfrac_sh(:,:,:), 6 )
285  call comm_vars8( atmos_phy_cp_kf_nca(:,:) , 7 )
286  call comm_vars8( atmos_phy_cp_kf_w0avg(:,:,:), 8 )
287 
288  ! tendency
289  call comm_vars8( atmos_phy_cp_dens_t(:,:,:), vmax+1 )
290  call comm_vars8( atmos_phy_cp_rhot_t(:,:,:), vmax+2 )
291 
292  do iq = 1, qa
293  call comm_vars8( atmos_phy_cp_rhoq_t(:,:,:,iq), vmax+2+iq )
294  enddo
295 
296  call comm_wait ( atmos_phy_cp_mflx_cloudbase(:,:) , 1 )
297  call comm_wait ( atmos_phy_cp_sflx_rain(:,:) , 2 )
298  call comm_wait ( atmos_phy_cp_cloudtop(:,:) , 3 )
299  call comm_wait ( atmos_phy_cp_cloudbase(:,:) , 4 )
300  call comm_wait ( atmos_phy_cp_cldfrac_dp(:,:,:), 5 )
301  call comm_wait ( atmos_phy_cp_cldfrac_sh(:,:,:), 6 )
302  call comm_wait ( atmos_phy_cp_kf_nca(:,:) , 7 )
303  call comm_wait ( atmos_phy_cp_kf_w0avg(:,:,:), 8 )
304 
305  call comm_wait ( atmos_phy_cp_dens_t(:,:,:), vmax+1 )
306  call comm_wait ( atmos_phy_cp_rhot_t(:,:,:), vmax+2 )
307 
308  do iq = 1, qa
309  call comm_wait ( atmos_phy_cp_rhoq_t(:,:,:,iq), vmax+2+iq )
310  enddo
311 
312  return
313  end subroutine atmos_phy_cp_vars_fillhalo
314 
315  !-----------------------------------------------------------------------------
318  use scale_fileio, only: &
319  fileio_read
320  use scale_rm_statistics, only: &
321  stat_total
322  implicit none
323 
324  real(RP) :: total
325  integer :: iq
326  !---------------------------------------------------------------------------
327 
328  if( io_l ) write(io_fid_log,*)
329  if( io_l ) write(io_fid_log,*) '*** Input restart file (ATMOS_PHY_CP) ***'
330 
331  if ( atmos_phy_cp_restart_in_basename /= '' ) then
332  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(atmos_phy_cp_restart_in_basename)
333 
334  call fileio_read( atmos_phy_cp_mflx_cloudbase(:,:), & ! [OUT]
335  atmos_phy_cp_restart_in_basename, var_name(1), 'XY', step=1 ) ! [IN]
336  call fileio_read( atmos_phy_cp_sflx_rain(:,:), & ! [OUT]
337  atmos_phy_cp_restart_in_basename, var_name(2), 'XY', step=1 ) ! [IN]
338  call fileio_read( atmos_phy_cp_cloudtop(:,:), & ! [OUT]
339  atmos_phy_cp_restart_in_basename, var_name(3), 'XY', step=1 ) ! [IN]
340  call fileio_read( atmos_phy_cp_cloudbase(:,:), & ! [OUT]
341  atmos_phy_cp_restart_in_basename, var_name(4), 'XY', step=1 ) ! [IN]
342  call fileio_read( atmos_phy_cp_cldfrac_dp(:,:,:), & ! [OUT]
343  atmos_phy_cp_restart_in_basename, var_name(5), 'ZXY', step=1 ) ! [IN]
344  call fileio_read( atmos_phy_cp_cldfrac_sh(:,:,:), & ! [OUT]
345  atmos_phy_cp_restart_in_basename, var_name(6), 'ZXY', step=1 ) ! [IN]
346  call fileio_read( atmos_phy_cp_kf_nca(:,:), & ! [OUT]
347  atmos_phy_cp_restart_in_basename, var_name(7), 'XY', step=1 ) ! [IN]
348  call fileio_read( atmos_phy_cp_kf_w0avg(:,:,:), & ! [OUT]
349  atmos_phy_cp_restart_in_basename, var_name(8), 'ZXY', step=1 ) ! [IN]
350  ! tendency
351  call fileio_read( atmos_phy_cp_dens_t(:,:,:), & ! [OUT]
352  atmos_phy_cp_restart_in_basename, var_t_name(1), 'ZXY', step=1 ) ! [IN]
353  call fileio_read( atmos_phy_cp_rhot_t(:,:,:), & ! [OUT]
354  atmos_phy_cp_restart_in_basename, var_t_name(2), 'ZXY', step=1 ) ! [IN]
355  do iq = 1, qa
356  call fileio_read( atmos_phy_cp_rhoq_t(:,:,:,iq), & ! [OUT]
357  atmos_phy_cp_restart_in_basename, var_t_name(2+iq), 'ZXY', step=1 ) ! [IN]
358  enddo
359 
361 
362  call stat_total( total, atmos_phy_cp_mflx_cloudbase(:,:) , var_name(1) )
363  call stat_total( total, atmos_phy_cp_sflx_rain(:,:) , var_name(2) )
364  call stat_total( total, atmos_phy_cp_cloudtop(:,:) , var_name(3) )
365  call stat_total( total, atmos_phy_cp_cloudbase(:,:) , var_name(4) )
366  call stat_total( total, atmos_phy_cp_cldfrac_dp(:,:,:), var_name(5) )
367  call stat_total( total, atmos_phy_cp_cldfrac_sh(:,:,:), var_name(6) )
368  call stat_total( total, atmos_phy_cp_kf_nca(:,:) , var_name(7) )
369  call stat_total( total, atmos_phy_cp_kf_w0avg(:,:,:), var_name(8) )
370 
371  ! tendency
372  call stat_total( total, atmos_phy_cp_dens_t(:,:,:), var_t_name(1) )
373  call stat_total( total, atmos_phy_cp_rhot_t(:,:,:), var_t_name(2) )
374 
375  do iq = 1, qa
376  call stat_total( total, atmos_phy_cp_rhoq_t(:,:,:,iq), var_t_name(2+iq) )
377  enddo
378  else
379  if( io_l ) write(io_fid_log,*) '*** restart file for ATMOS_PHY_CP is not specified.'
380  endif
381 
382  return
383  end subroutine atmos_phy_cp_vars_restart_read
384 
385  !-----------------------------------------------------------------------------
388  use scale_time, only: &
390  use scale_fileio, only: &
391  fileio_write
392  use scale_rm_statistics, only: &
393  stat_total
394  implicit none
395 
396  character(len=20) :: timelabel
397  character(len=H_LONG) :: basename
398 
399  real(RP) :: total
400  integer :: iq
401  !---------------------------------------------------------------------------
402 
403  if ( atmos_phy_cp_restart_out_basename /= '' ) then
404 
405  call time_gettimelabel( timelabel )
406  write(basename,'(A,A,A)') trim(atmos_phy_cp_restart_out_basename), '_', trim(timelabel)
407 
408  if( io_l ) write(io_fid_log,*)
409  if( io_l ) write(io_fid_log,*) '*** Output restart file (ATMOS_PHY_CP) ***'
410  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
411 
412  call fileio_write( atmos_phy_cp_mflx_cloudbase(:,:), basename, atmos_phy_cp_restart_out_title, & ! [IN]
413  var_name(1), var_desc(1), var_unit(1), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
414  call fileio_write( atmos_phy_cp_sflx_rain(:,:), basename, atmos_phy_cp_restart_out_title, & ! [IN]
415  var_name(2), var_desc(2), var_unit(2), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
416  call fileio_write( atmos_phy_cp_cloudtop(:,:), basename, atmos_phy_cp_restart_out_title, & ! [IN]
417  var_name(3), var_desc(3), var_unit(3), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
418  call fileio_write( atmos_phy_cp_cloudbase(:,:), basename, atmos_phy_cp_restart_out_title, & ! [IN]
419  var_name(4), var_desc(4), var_unit(4), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
420  call fileio_write( atmos_phy_cp_cldfrac_dp(:,:,:), basename, atmos_phy_cp_restart_out_title, & ! [IN]
421  var_name(5), var_desc(5), var_unit(5), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
422  call fileio_write( atmos_phy_cp_cldfrac_sh(:,:,:), basename, atmos_phy_cp_restart_out_title, & ! [IN]
423  var_name(6), var_desc(6), var_unit(6), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
424  call fileio_write( atmos_phy_cp_kf_nca(:,:), basename, atmos_phy_cp_restart_out_title, & ! [IN]
425  var_name(7), var_desc(7), var_unit(7), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
426  call fileio_write( atmos_phy_cp_kf_w0avg(:,:,:), basename, atmos_phy_cp_restart_out_title, & ! [IN]
427  var_name(8), var_desc(8), var_unit(8), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
428  ! tendency
429  call fileio_write( atmos_phy_cp_dens_t(:,:,:), basename, atmos_phy_cp_restart_out_title, & ! [IN]
430  var_t_name(1), var_t_desc(1), var_t_unit(1), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
431  call fileio_write( atmos_phy_cp_rhot_t(:,:,:), basename, atmos_phy_cp_restart_out_title, & ! [IN]
432  var_t_name(2), var_t_desc(2), var_t_unit(2), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
433  do iq = 1, qa
434  call fileio_write( atmos_phy_cp_rhoq_t(:,:,:,iq), basename, atmos_phy_cp_restart_out_title, & ! [IN]
435  var_t_name(2+iq), var_t_desc(2+iq), var_t_unit(2+iq), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
436  enddo
437  endif
438 
439  return
440  end subroutine atmos_phy_cp_vars_restart_write
441 
442  !-----------------------------------------------------------------------------
445  use scale_time, only: &
447  use scale_fileio, only: &
449  implicit none
450 
451  character(len=20) :: timelabel
452  character(len=H_LONG) :: basename
453 
454  !---------------------------------------------------------------------------
455 
456  if ( atmos_phy_cp_restart_out_basename /= '' ) then
457 
458  call time_gettimelabel( timelabel )
459  write(basename,'(A,A,A)') trim(atmos_phy_cp_restart_out_basename), '_', trim(timelabel)
460 
461  if( io_l ) write(io_fid_log,*)
462  if( io_l ) write(io_fid_log,*) '*** Output restart file (ATMOS_PHY_CP) ***'
463  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
464 
465  call fileio_create(restart_fid,basename, atmos_phy_cp_restart_out_title, & ! [IN]
467 
468  endif
469 
470  return
471  end subroutine atmos_phy_cp_vars_restart_create
472 
473  !-----------------------------------------------------------------------------
476  use scale_fileio, only: &
478  implicit none
479 
480  if ( restart_fid .NE. -1 ) then
481  call fileio_enddef( restart_fid ) ! [IN]
482  endif
483 
484  return
485  end subroutine atmos_phy_cp_vars_restart_enddef
486 
487  !-----------------------------------------------------------------------------
490  use scale_fileio, only: &
492  implicit none
493 
494  if ( restart_fid .NE. -1 ) then
495  call fileio_close( restart_fid ) ! [IN]
496  restart_fid = -1
497  endif
498 
499  return
500  end subroutine atmos_phy_cp_vars_restart_close
501 
502  !-----------------------------------------------------------------------------
505  use scale_fileio, only: &
507  implicit none
508 
509  integer :: iq
510  !---------------------------------------------------------------------------
511 
512  if ( restart_fid .NE. -1 ) then
513 
514  call fileio_def_var( restart_fid, var_id(1), var_name(1), var_desc(1), &
515  var_unit(1), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
516  call fileio_def_var( restart_fid, var_id(2), var_name(2), var_desc(2), &
517  var_unit(2), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
518  call fileio_def_var( restart_fid, var_id(3), var_name(3), var_desc(3), &
519  var_unit(3), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
520  call fileio_def_var( restart_fid, var_id(4), var_name(4), var_desc(4), &
521  var_unit(4), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
522  call fileio_def_var( restart_fid, var_id(5), var_name(5), var_desc(5), &
523  var_unit(5), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
524  call fileio_def_var( restart_fid, var_id(6), var_name(6), var_desc(6), &
525  var_unit(6), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
526  call fileio_def_var( restart_fid, var_id(7), var_name(7), var_desc(7), &
527  var_unit(7), 'XY', atmos_phy_cp_restart_out_dtype ) ! [IN]
528  call fileio_def_var( restart_fid, var_id(8), var_name(8), var_desc(8), &
529  var_unit(8), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
530 
531  call fileio_def_var( restart_fid, var_t_id(1), var_t_name(1), var_t_desc(1), &
532  var_t_unit(1), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
533  call fileio_def_var( restart_fid, var_t_id(2), var_t_name(2), var_t_desc(2), &
534  var_t_unit(2), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
535 
536  do iq = 1, qa
537  call fileio_def_var( restart_fid, var_t_id(2+iq), var_t_name(2+iq), var_t_desc(2+iq), &
538  var_t_unit(2+iq), 'ZXY', atmos_phy_cp_restart_out_dtype ) ! [IN]
539  enddo
540 
541  endif
542 
543  return
544  end subroutine atmos_phy_cp_vars_restart_def_var
545 
546  !-----------------------------------------------------------------------------
549  use scale_fileio, only: &
550  fileio_write_var
551  implicit none
552 
553  integer :: iq
554  !---------------------------------------------------------------------------
555 
556  if ( restart_fid .NE. -1 ) then
557 
558  call fileio_write_var( restart_fid, var_id(1), atmos_phy_cp_mflx_cloudbase(:,:), &
559  var_name(1), 'XY' ) ! [IN]
560  call fileio_write_var( restart_fid, var_id(2), atmos_phy_cp_sflx_rain(:,:), &
561  var_name(2), 'XY' ) ! [IN]
562  call fileio_write_var( restart_fid, var_id(3), atmos_phy_cp_cloudtop(:,:), &
563  var_name(3), 'XY' ) ! [IN]
564  call fileio_write_var( restart_fid, var_id(4), atmos_phy_cp_cloudbase(:,:), &
565  var_name(4), 'XY' ) ! [IN]
566  call fileio_write_var( restart_fid, var_id(5), atmos_phy_cp_cldfrac_dp(:,:,:), &
567  var_name(5), 'ZXY' ) ! [IN]
568  call fileio_write_var( restart_fid, var_id(6), atmos_phy_cp_cldfrac_sh(:,:,:), &
569  var_name(6), 'ZXY' ) ! [IN]
570  call fileio_write_var( restart_fid, var_id(7), atmos_phy_cp_kf_nca(:,:), &
571  var_name(7), 'XY' ) ! [IN]
572  call fileio_write_var( restart_fid, var_id(8), atmos_phy_cp_kf_w0avg(:,:,:), &
573  var_name(8), 'ZXY' ) ! [IN]
574  ! tendency
575  call fileio_write_var( restart_fid, var_t_id(1), atmos_phy_cp_dens_t(:,:,:), &
576  var_t_name(1), 'ZXY' ) ! [IN]
577  call fileio_write_var( restart_fid, var_t_id(2), atmos_phy_cp_rhot_t(:,:,:), &
578  var_t_name(2), 'ZXY' ) ! [IN]
579  do iq = 1, qa
580  call fileio_write_var( restart_fid, var_t_id(2+iq), atmos_phy_cp_rhoq_t(:,:,:,iq), &
581  var_t_name(2+iq), 'ZXY' ) ! [IN]
582  enddo
583 
584  endif
585 
586  return
588 
589 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.
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 restart file
subroutine, public atmos_phy_cp_vars_restart_enddef
Exit netCDF define mode.
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
subroutine, public atmos_phy_cp_vars_restart_write
Write restart.
logical, public atmos_phy_cp_restart_output
output restart file?
subroutine, public atmos_phy_cp_vars_restart_write_var
Write restart.
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
integer, public qa
subroutine, public atmos_phy_cp_vars_restart_create
Create restart file.
module FILE I/O (netcdf)
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
subroutine, public atmos_phy_cp_vars_setup
Setup.
module TRACER
subroutine, public fileio_def_var(fid, vid, varname, desc, unit, axistype, datatype, timeintv)
Define a variable to file.
integer, public ia
of x whole cells (local, with HALO)
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
integer, public ka
of z whole cells (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.
character(len=h_short), dimension(:), allocatable, public aq_name
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_lnml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:60
module PRECISION
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
character(len=h_mid), public atmos_phy_cp_restart_out_dtype
REAL4 or REAL8.
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_kf_nca
integer, public ja
of y whole cells (local, with HALO)