SCALE-RM
mod_atmos_phy_cp_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_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.
51  character(len=H_LONG), public :: atmos_phy_cp_restart_out_basename = ''
53  logical, public :: atmos_phy_cp_restart_out_postfix_timelabel = .true.
54  character(len=H_MID), public :: atmos_phy_cp_restart_out_title = 'ATMOS_PHY_CP restart'
55  character(len=H_SHORT), public :: atmos_phy_cp_restart_out_dtype = 'DEFAULT'
56 
57  ! restart variables
58  real(rp), public, allocatable :: atmos_phy_cp_dens_t (:,:,:) ! tendency DENS [kg/m3/s]
59  real(rp), public, allocatable :: atmos_phy_cp_momz_t (:,:,:) ! tendency MOMZ [kg/m2/s2]
60  real(rp), public, allocatable :: atmos_phy_cp_rhot_t (:,:,:) ! tendency RHOT [K*kg/m3/s]
61  real(rp), public, allocatable :: atmos_phy_cp_rhoqv_t (:,:,:) ! tendency rho*QV [kg/kg/s]
62  real(rp), public, allocatable :: atmos_phy_cp_rhohyd_t (:,:,:,:) ! tendency rho*QHYD [kg/kg/s]
63  real(rp), public, allocatable :: atmos_phy_cp_sflx_rain(:,:) ! convective rain [kg/m2/s]
64  real(rp), public, allocatable :: atmos_phy_cp_sflx_snow(:,:) ! convective snow [kg/m2/s]
65  real(rp), public, allocatable :: atmos_phy_cp_sflx_engi(:,:) ! internal energy [J/m2/s]
66 
67  ! only for K-F scheme
68  real(rp), public, allocatable :: atmos_phy_cp_w0mean (:,:,:) ! running mean vertical wind velocity [m/s]
69  real(rp), public, allocatable :: atmos_phy_cp_kf_nca (:,:) ! advection/cumulus convection timescale for KF[sec]
70 
71 
72  ! diagnostic variables
73  real(rp), public, allocatable :: atmos_phy_cp_mflx_cloudbase(:,:) ! cloud base mass flux [kg/m2/s]
74  real(rp), public, allocatable :: atmos_phy_cp_cloudtop (:,:) ! cloud top height [m]
75  real(rp), public, allocatable :: atmos_phy_cp_cloudbase (:,:) ! cloud base height [m]
76  real(rp), public, allocatable :: atmos_phy_cp_cldfrac_dp (:,:,:) ! cloud fraction (deep convection) (0-1)
77  real(rp), public, allocatable :: atmos_phy_cp_cldfrac_sh (:,:,:) ! cloud fraction (shallow convection) (0-1)
78 
79  !-----------------------------------------------------------------------------
80  !
81  !++ Private procedure
82  !
83  !-----------------------------------------------------------------------------
84  !
85  !++ Private parameters & variables
86  !
87  integer, private, parameter :: vmax = 2
88  integer, private, parameter :: i_w0mean = 1
89  integer, private, parameter :: i_kf_nca = 2
90 
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  character(len=H_SHORT), private :: var_dim (vmax)
96  integer, private :: var_id (vmax)
97  integer, private :: restart_fid = -1 ! file ID
98 
99  data var_name / 'w0mean', &
100  'kf_nca' /
101 
102  data var_desc / 'running mean vertical velocity', &
103  'advection/cumulus convection timescale for KF' /
104 
105  data var_unit / 'm/s', &
106  'sec' /
107 
108  data var_dim / 'ZXY', &
109  'XY' /
110 
111  ! surface flux and tendency names
112  integer, private :: vmax_t
113  integer, private :: i_cp_rain_sf = 1
114  integer, private :: i_cp_snow_sf = 2
115  integer, private :: i_cp_engi_sf = 3
116  integer, private :: i_cp_dens_t = 4
117  integer, private :: i_cp_rhot_t = 5
118  integer, private :: i_cp_qv_t = 6
119 
120  character(len=H_SHORT), private, allocatable :: var_t_name(:)
121  character(len=H_MID), private, allocatable :: var_t_desc(:)
122  character(len=H_SHORT), private, allocatable :: var_t_unit(:)
123  integer, private, allocatable :: var_t_id (:)
124 
125  !-----------------------------------------------------------------------------
126 contains
127  !-----------------------------------------------------------------------------
129  subroutine atmos_phy_cp_vars_setup
130  use scale_prc, only: &
131  prc_abort
132  use scale_const, only: &
133  undef => const_undef
134  use scale_atmos_hydrometeor, only: &
135  n_hyd, &
136  hyd_name
137  implicit none
138 
139  namelist / param_atmos_phy_cp_vars / &
149 
150  integer :: ierr
151  integer :: iv
152  integer :: iq
153  !---------------------------------------------------------------------------
154 
155  log_newline
156  log_info("ATMOS_PHY_CP_vars_setup",*) 'Setup'
157 
158  allocate( atmos_phy_cp_dens_t(ka,ia,ja) )
159  allocate( atmos_phy_cp_momz_t(ka,ia,ja) )
160  allocate( atmos_phy_cp_rhot_t(ka,ia,ja) )
161  allocate( atmos_phy_cp_rhoqv_t(ka,ia,ja) )
162  allocate( atmos_phy_cp_rhohyd_t(ka,ia,ja,n_hyd) )
163  atmos_phy_cp_dens_t(:,:,:) = 0.0_rp
164  atmos_phy_cp_momz_t(:,:,:) = undef
165  atmos_phy_cp_rhot_t(:,:,:) = 0.0_rp
166  atmos_phy_cp_rhoqv_t(:,:,:) = 0.0_rp
167  atmos_phy_cp_rhohyd_t(:,:,:,:) = 0.0_rp
168  !$acc enter data copyin(ATMOS_PHY_CP_DENS_t,ATMOS_PHY_CP_MOMZ_t,ATMOS_PHY_CP_RHOT_t,ATMOS_PHY_CP_RHOQV_t,ATMOS_PHY_CP_RHOHYD_t)
169 
170  allocate( atmos_phy_cp_w0mean(ka,ia,ja) )
171  allocate( atmos_phy_cp_kf_nca(ia,ja) )
172  atmos_phy_cp_w0mean(:,:,:) = 0.0_rp
173  atmos_phy_cp_kf_nca(:,:) = -100.0_rp
174  !$acc enter data copyin(ATMOS_PHY_CP_w0mean,ATMOS_PHY_CP_kf_nca)
175 
176  ! for surface flux and tendency restart
177  vmax_t = 6 + n_hyd
178  allocate( var_t_name(vmax_t) )
179  allocate( var_t_desc(vmax_t) )
180  allocate( var_t_unit(vmax_t) )
181  allocate( var_t_id(vmax_t) )
182 
183  var_t_name(i_cp_rain_sf) = 'SFLX_RAIN_CP'
184  var_t_desc(i_cp_rain_sf) = 'surface rain flux in CP'
185  var_t_unit(i_cp_rain_sf) = 'kg/m2/s'
186  var_t_name(i_cp_snow_sf) = 'SFLX_SNOW_CP'
187  var_t_desc(i_cp_snow_sf) = 'surface snow flux in CP'
188  var_t_unit(i_cp_snow_sf) = 'kg/m2/s'
189  var_t_name(i_cp_engi_sf) = 'SFLX_ENGI_CP'
190  var_t_desc(i_cp_engi_sf) = 'surface internal energy flux in CP'
191  var_t_unit(i_cp_engi_sf) = 'J/m2/s'
192 
193  var_t_name(i_cp_dens_t) = 'DENS_t_CP'
194  var_t_desc(i_cp_dens_t) = 'tendency DENS in CP'
195  var_t_unit(i_cp_dens_t) = 'kg/m3/s'
196  var_t_name(i_cp_rhot_t) = 'RHOT_t_CP'
197  var_t_desc(i_cp_rhot_t) = 'tendency RHOT in CP'
198  var_t_unit(i_cp_rhot_t) = 'K*kg/m3/s'
199 
200  var_t_name(i_cp_qv_t) = 'QV_t_CP'
201  var_t_desc(i_cp_qv_t) = 'tendency rho*QV in CP'
202  var_t_unit(i_cp_qv_t) = 'kg/m3/s'
203  do iq = 1, n_hyd
204  var_t_name(6+iq) = trim(hyd_name(iq))//'_t_CP'
205  var_t_desc(6+iq) = 'tendency rho*'//trim(hyd_name(iq))//' in CP'
206  var_t_unit(6+iq) = 'kg/m3/s'
207  enddo
208 
209 
210  allocate( atmos_phy_cp_mflx_cloudbase(ia,ja) )
211  allocate( atmos_phy_cp_sflx_rain(ia,ja) )
212  allocate( atmos_phy_cp_sflx_snow(ia,ja) )
213  allocate( atmos_phy_cp_sflx_engi(ia,ja) )
214  allocate( atmos_phy_cp_cloudtop(ia,ja) )
215  allocate( atmos_phy_cp_cloudbase(ia,ja) )
216  allocate( atmos_phy_cp_cldfrac_dp(ka,ia,ja) )
217  allocate( atmos_phy_cp_cldfrac_sh(ka,ia,ja) )
218  atmos_phy_cp_mflx_cloudbase(:,:) = 0.0_rp
219  atmos_phy_cp_sflx_rain(:,:) = 0.0_rp
220  atmos_phy_cp_sflx_snow(:,:) = 0.0_rp
221  atmos_phy_cp_sflx_engi(:,:) = 0.0_rp
222  atmos_phy_cp_cloudtop(:,:) = 0.0_rp
223  atmos_phy_cp_cloudbase(:,:) = 0.0_rp
224  atmos_phy_cp_cldfrac_dp(:,:,:) = 0.0_rp
225  atmos_phy_cp_cldfrac_sh(:,:,:) = 0.0_rp
226  !$acc enter data copyin(ATMOS_PHY_CP_MFLX_cloudbase,ATMOS_PHY_CP_SFLX_rain,ATMOS_PHY_CP_SFLX_snow,ATMOS_PHY_CP_SFLX_ENGI,ATMOS_PHY_CP_cloudtop,ATMOS_PHY_CP_cloudbase,ATMOS_PHY_CP_cldfrac_dp,ATMOS_PHY_CP_cldfrac_sh)
227 
228  !--- read namelist
229  rewind(io_fid_conf)
230  read(io_fid_conf,nml=param_atmos_phy_cp_vars,iostat=ierr)
231  if( ierr < 0 ) then !--- missing
232  log_info("ATMOS_PHY_CP_vars_setup",*) 'Not found namelist. Default used.'
233  elseif( ierr > 0 ) then !--- fatal error
234  log_error("ATMOS_PHY_CP_vars_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_PHY_CP_VARS. Check!'
235  call prc_abort
236  endif
237  log_nml(param_atmos_phy_cp_vars)
238 
239  log_newline
240  log_info("ATMOS_PHY_CP_vars_setup",*) '[ATMOS_PHY_CP] prognostic/diagnostic variables'
241  log_info_cont('(1x,A,A24,A,A48,A,A12,A)') &
242  ' |', 'VARNAME ','|', &
243  'DESCRIPTION ', '[', 'UNIT ', ']'
244  do iv = 1, vmax
245  log_info_cont('(1x,A,I3,A,A24,A,A48,A,A12,A)') &
246  'NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
247  enddo
248 
249  ! tendency
250  do iv = 1, vmax_t
251  log_info_cont('(1x,A,I3,A,A24,A,A48,A,A12,A)') &
252  'NO.',iv+vmax,'|',var_t_name(iv),'|',var_t_desc(iv),'[',var_t_unit(iv),']'
253  enddo
254 
255  log_newline
256  if ( atmos_phy_cp_restart_in_basename /= '' ) then
257  log_info("ATMOS_PHY_CP_vars_setup",*) 'Restart input? : YES, file = ', trim(atmos_phy_cp_restart_in_basename)
258  log_info("ATMOS_PHY_CP_vars_setup",*) 'Add timelabel? : ', atmos_phy_cp_restart_in_postfix_timelabel
259  else
260  log_info("ATMOS_PHY_CP_vars_setup",*) 'Restart input? : NO'
261  endif
263  .AND. atmos_phy_cp_restart_out_basename /= '' ) then
264  log_info("ATMOS_PHY_CP_vars_setup",*) 'Restart output? : YES, file = ', trim(atmos_phy_cp_restart_out_basename)
265  log_info("ATMOS_PHY_CP_vars_setup",*) 'Add timelabel? : ', atmos_phy_cp_restart_out_postfix_timelabel
266  else
267  log_info("ATMOS_PHY_CP_vars_setup",*) 'Restart output? : NO'
269  endif
270 
271  return
272  end subroutine atmos_phy_cp_vars_setup
273 
274  !-----------------------------------------------------------------------------
276  subroutine atmos_phy_cp_vars_finalize
277  implicit none
278  !---------------------------------------------------------------------------
279 
280  log_newline
281  log_info("ATMOS_PHY_CP_vars_finalize",*) 'Finalize'
282 
283  !$acc exit data delete(ATMOS_PHY_CP_DENS_t,ATMOS_PHY_CP_MOMZ_t,ATMOS_PHY_CP_RHOT_t,ATMOS_PHY_CP_RHOQV_t,ATMOS_PHY_CP_RHOHYD_t)
284  deallocate( atmos_phy_cp_dens_t )
285  deallocate( atmos_phy_cp_momz_t )
286  deallocate( atmos_phy_cp_rhot_t )
287  deallocate( atmos_phy_cp_rhoqv_t )
288  deallocate( atmos_phy_cp_rhohyd_t )
289 
290  !$acc exit data delete(ATMOS_PHY_CP_w0mean,ATMOS_PHY_CP_kf_nca)
291  deallocate( atmos_phy_cp_w0mean )
292  deallocate( atmos_phy_cp_kf_nca )
293 
294  ! for tendency restart
295  deallocate( var_t_name )
296  deallocate( var_t_desc )
297  deallocate( var_t_unit )
298  deallocate( var_t_id )
299 
300  !$acc exit data delete(ATMOS_PHY_CP_MFLX_cloudbase,ATMOS_PHY_CP_SFLX_rain,ATMOS_PHY_CP_SFLX_snow,ATMOS_PHY_CP_SFLX_ENGI,ATMOS_PHY_CP_cloudtop,ATMOS_PHY_CP_cloudbase,ATMOS_PHY_CP_cldfrac_dp,ATMOS_PHY_CP_cldfrac_sh)
301  deallocate( atmos_phy_cp_mflx_cloudbase )
302  deallocate( atmos_phy_cp_sflx_rain )
303  deallocate( atmos_phy_cp_sflx_snow )
304  deallocate( atmos_phy_cp_sflx_engi )
305  deallocate( atmos_phy_cp_cloudtop )
306  deallocate( atmos_phy_cp_cloudbase )
307  deallocate( atmos_phy_cp_cldfrac_dp )
308  deallocate( atmos_phy_cp_cldfrac_sh )
309 
310  return
311  end subroutine atmos_phy_cp_vars_finalize
312 
313  !-----------------------------------------------------------------------------
315  subroutine atmos_phy_cp_vars_fillhalo
316  use scale_comm_cartesc, only: &
317  comm_vars8, &
318  comm_wait
319  use scale_atmos_hydrometeor, only: &
320  n_hyd
321  implicit none
322 
323  integer :: i, j
324  integer :: iq
325  !---------------------------------------------------------------------------
326 
327  !$omp parallel do
328  !$acc parallel vector_length(32)
329  !$acc loop collapse(2) independent
330  do j = js, je
331  do i = is, ie
340  end do
341  end do
342  !$acc end parallel
343  !$omp parallel do collapse(2)
344  !$acc parallel vector_length(32)
345  !$acc loop collapse(3) independent
346  do iq = 1, n_hyd
347  do j = js, je
348  do i = is, ie
349  atmos_phy_cp_rhohyd_t( 1:ks-1,i,j,iq) = atmos_phy_cp_rhohyd_t(ks,i,j,iq)
350  atmos_phy_cp_rhohyd_t(ke+1:ka ,i,j,iq) = atmos_phy_cp_rhohyd_t(ke,i,j,iq)
351  enddo
352  enddo
353  end do
354  !$acc end parallel
355 
356  call comm_vars8( atmos_phy_cp_w0mean(:,:,:), 1 )
357  call comm_vars8( atmos_phy_cp_kf_nca(:,:), 2 )
358 
359  ! tendency
360  call comm_vars8( atmos_phy_cp_dens_t(:,:,:), vmax+1 )
361  call comm_vars8( atmos_phy_cp_rhot_t(:,:,:), vmax+2 )
362  call comm_vars8( atmos_phy_cp_rhoqv_t(:,:,:), vmax+3 )
363  do iq = 1, n_hyd
364  call comm_vars8( atmos_phy_cp_rhohyd_t(:,:,:,iq), vmax+3+iq )
365  enddo
366 
367  call comm_wait ( atmos_phy_cp_w0mean(:,:,:), 1 )
368  call comm_wait ( atmos_phy_cp_kf_nca(:,:), 2 )
369 
370  call comm_wait ( atmos_phy_cp_dens_t(:,:,:), vmax+1 )
371  call comm_wait ( atmos_phy_cp_rhot_t(:,:,:), vmax+2 )
372  call comm_wait ( atmos_phy_cp_rhoqv_t(:,:,:), vmax+3 )
373  do iq = 1, n_hyd
374  call comm_wait ( atmos_phy_cp_rhohyd_t(:,:,:,iq), vmax+3+iq )
375  enddo
376 
377  return
378  end subroutine atmos_phy_cp_vars_fillhalo
379 
380  !-----------------------------------------------------------------------------
383  use scale_time, only: &
385  use scale_file_cartesc, only: &
387  implicit none
388 
389  character(len=19) :: timelabel
390  character(len=H_LONG) :: basename
391  !---------------------------------------------------------------------------
392 
393  log_newline
394  log_info("ATMOS_PHY_CP_vars_restart_open",*) 'Open restart file (ATMOS_PHY_CP) '
395 
396  if ( atmos_phy_cp_restart_in_basename /= '' ) then
397 
399  call time_gettimelabel( timelabel )
400  basename = trim(atmos_phy_cp_restart_in_basename)//'_'//trim(timelabel)
401  else
402  basename = trim(atmos_phy_cp_restart_in_basename)
403  endif
404 
405  log_info("ATMOS_PHY_CP_vars_restart_open",*) 'basename: ', trim(basename)
406 
407  call file_cartesc_open( basename, restart_fid, aggregate=atmos_phy_cp_restart_in_aggregate )
408  else
409  log_info("ATMOS_PHY_CP_vars_restart_open",*) 'restart file for ATMOS_PHY_CP is not specified.'
410  endif
411 
412  return
413  end subroutine atmos_phy_cp_vars_restart_open
414 
415  !-----------------------------------------------------------------------------
418  use scale_file, only: &
420  use scale_file_cartesc, only: &
421  file_cartesc_read, &
423  use scale_atmos_hydrometeor, only: &
424  n_hyd
425  implicit none
426 
427  integer :: i, j, iq
428  !---------------------------------------------------------------------------
429 
430  if ( restart_fid /= -1 ) then
431  log_newline
432  log_info("ATMOS_PHY_CP_vars_restart_read",*) 'Read from restart file (ATMOS_PHY_CP) '
433 
434  call file_cartesc_read( restart_fid, var_name(1), 'ZXY', & ! [IN]
435  atmos_phy_cp_w0mean(:,:,:) ) ! [OUT]
436  call file_cartesc_read( restart_fid, var_name(2), 'XY', & ! [IN]
437  atmos_phy_cp_kf_nca(:,:) ) ! [OUT]
438 
439  ! surface flux
440  call file_cartesc_read( restart_fid, var_t_name(1), 'XY', & ! [IN]
441  atmos_phy_cp_sflx_rain(:,:) ) ! [OUT]
442  call file_cartesc_read( restart_fid, var_t_name(2), 'XY', & ! [IN]
443  atmos_phy_cp_sflx_snow(:,:) ) ! [OUT]
444  call file_cartesc_read( restart_fid, var_t_name(3), 'XY', & ! [IN]
445  atmos_phy_cp_sflx_engi(:,:) ) ! [OUT]
446 
447  ! tendency
448  call file_cartesc_read( restart_fid, var_t_name(4), 'ZXY', & ! [IN]
449  atmos_phy_cp_dens_t(:,:,:) ) ! [OUT]
450  call file_cartesc_read( restart_fid, var_t_name(5), 'ZXY', & ! [IN]
451  atmos_phy_cp_rhot_t(:,:,:) ) ! [OUT]
452  call file_cartesc_read( restart_fid, var_t_name(6), 'ZXY', & ! [IN]
453  atmos_phy_cp_rhoqv_t(:,:,:) ) ! [OUT]
454  do iq = 1, n_hyd
455  call file_cartesc_read( restart_fid, var_t_name(6+iq), 'ZXY', & ! [IN]
456  atmos_phy_cp_rhohyd_t(:,:,:,iq) ) ! [OUT]
457  enddo
458 
459  if ( file_get_aggregate(restart_fid) ) then
460  call file_cartesc_flush( restart_fid ) ! X/Y halos have been read from file
461  !$acc update device(ATMOS_PHY_CP_w0mean,ATMOS_PHY_CP_kf_nca,ATMOS_PHY_CP_SFLX_rain,ATMOS_PHY_CP_SFLX_snow,ATMOS_PHY_CP_SFLX_ENGI,ATMOS_PHY_CP_DENS_t,ATMOS_PHY_CP_RHOT_t,ATMOS_PHY_CP_RHOQV_t,ATMOS_PHY_CP_RHOHYD_t)
462 
463  ! fill K halos
464  !$omp parallel do
465  !$acc parallel vector_length(32)
466  !$acc loop collapse(2) independent
467  do j = 1, ja
468  do i = 1, ia
477  end do
478  end do
479  !$acc end parallel
480  !$omp parallel do collapse(2)
481  !$acc parallel vector_length(32)
482  !$acc loop collapse(3) independent
483  do iq = 1, n_hyd
484  do j = 1, ja
485  do i = 1, ia
486  atmos_phy_cp_rhohyd_t( 1:ks-1,i,j,iq) = atmos_phy_cp_rhohyd_t(ks,i,j,iq)
487  atmos_phy_cp_rhohyd_t(ke+1:ka, i,j,iq) = atmos_phy_cp_rhohyd_t(ke,i,j,iq)
488  enddo
489  enddo
490  enddo
491  !$acc end parallel
492  else
494  end if
495 
497 
498  else
499  log_info("ATMOS_PHY_CP_vars_restart_read",*) 'invalid restart file ID for ATMOS_PHY_CP.'
500  endif
501 
502  return
503  end subroutine atmos_phy_cp_vars_restart_read
504 
505  !-----------------------------------------------------------------------------
508  use scale_time, only: &
510  use scale_file_cartesc, only: &
512  implicit none
513 
514  character(len=19) :: timelabel
515  character(len=H_LONG) :: basename
516  !---------------------------------------------------------------------------
517 
518  if ( atmos_phy_cp_restart_out_basename /= '' ) then
519 
520  log_newline
521  log_info("ATMOS_PHY_CP_vars_restart_create",*) 'Create restart file (ATMOS_PHY_AE) '
522 
524  call time_gettimelabel( timelabel )
525  basename = trim(atmos_phy_cp_restart_out_basename)//'_'//trim(timelabel)
526  else
527  basename = trim(atmos_phy_cp_restart_out_basename)
528  endif
529 
530  log_info("ATMOS_PHY_CP_vars_restart_create",*) 'basename: ', trim(basename)
531 
532  call file_cartesc_create( &
534  restart_fid, & ! [OUT]
535  aggregate=atmos_phy_cp_restart_out_aggregate ) ! [IN]
536 
537  endif
538 
539  return
540  end subroutine atmos_phy_cp_vars_restart_create
541 
542  !-----------------------------------------------------------------------------
545  use scale_file_cartesc, only: &
547  implicit none
548 
549  if ( restart_fid /= -1 ) then
550  call file_cartesc_enddef( restart_fid ) ! [IN]
551  endif
552 
553  return
554  end subroutine atmos_phy_cp_vars_restart_enddef
555 
556  !-----------------------------------------------------------------------------
559  use scale_file_cartesc, only: &
561  implicit none
562  !---------------------------------------------------------------------------
563 
564  if ( restart_fid /= -1 ) then
565  log_newline
566  log_info("ATMOS_PHY_CP_vars_restart_close",*) 'Close restart file (ATMOS_PHY_CP) '
567 
568  call file_cartesc_close( restart_fid ) ! [IN]
569 
570  restart_fid = -1
571  endif
572 
573  return
574  end subroutine atmos_phy_cp_vars_restart_close
575 
576  !-----------------------------------------------------------------------------
579  use scale_file_cartesc, only: &
581  use scale_atmos_hydrometeor, only: &
582  n_hyd
583  implicit none
584 
585  integer :: i, iq
586  !---------------------------------------------------------------------------
587 
588  if ( restart_fid /= -1 ) then
589 
590  do i = 1, vmax
591  call file_cartesc_def_var( restart_fid, & ! [IN]
592  var_name(i), var_desc(i), var_unit(i), & ! [IN]
593  var_dim(i), atmos_phy_cp_restart_out_dtype, & ! [IN]
594  var_id(i) ) ! [OUT]
595  end do
596 
597  do i = 1, 3
598  call file_cartesc_def_var( restart_fid, & ! [IN]
599  var_t_name(i), var_t_desc(i), var_t_unit(i), & ! [IN]
600  'XY', atmos_phy_cp_restart_out_dtype, & ! [IN]
601  var_t_id(i) ) ! [OUT]
602  end do
603 
604  do i = 4, 6
605  call file_cartesc_def_var( restart_fid, & ! [IN]
606  var_t_name(i), var_t_desc(i), var_t_unit(i), & ! [IN]
607  'ZXY', atmos_phy_cp_restart_out_dtype, & ! [IN]
608  var_t_id(i) ) ! [OUT]
609  end do
610 
611  do iq = 1, n_hyd
612  call file_cartesc_def_var( restart_fid, & ! [IN]
613  var_t_name(6+iq), var_t_desc(6+iq), var_t_unit(6+iq), & ! [IN]
614  'ZXY', atmos_phy_cp_restart_out_dtype, & ! [IN]
615  var_t_id(6+iq) ) ! [OUT]
616  enddo
617 
618  endif
619 
620  return
621  end subroutine atmos_phy_cp_vars_restart_def_var
622 
623  !-----------------------------------------------------------------------------
626  use scale_file_cartesc, only: &
627  file_cartesc_write => file_cartesc_write_var
628  use scale_atmos_hydrometeor, only: &
629  n_hyd
630  implicit none
631 
632  integer :: iq
633  !---------------------------------------------------------------------------
634 
635  if ( restart_fid /= -1 ) then
636 
638 
640 
641  call file_cartesc_write( restart_fid, var_id(1), atmos_phy_cp_w0mean(:,:,:), & ! [IN]
642  var_name(1), 'ZXY' ) ! [IN]
643  call file_cartesc_write( restart_fid, var_id(2), atmos_phy_cp_kf_nca(:,:), & ! [IN]
644  var_name(2), 'XY' ) ! [IN]
645 
646  ! surface flux
647  call file_cartesc_write( restart_fid, var_t_id(1), atmos_phy_cp_sflx_rain(:,:), & ! [IN]
648  var_t_name(1), 'XY' ) ! [IN]
649  call file_cartesc_write( restart_fid, var_t_id(2), atmos_phy_cp_sflx_snow(:,:), & ! [IN]
650  var_t_name(2), 'XY' ) ! [IN]
651  call file_cartesc_write( restart_fid, var_t_id(3), atmos_phy_cp_sflx_engi(:,:), & ! [IN]
652  var_t_name(3), 'XY' ) ! [IN]
653 
654  ! tendency
655  call file_cartesc_write( restart_fid, var_t_id(4), atmos_phy_cp_dens_t(:,:,:), & ! [IN]
656  var_t_name(4), 'ZXY' ) ! [IN]
657  call file_cartesc_write( restart_fid, var_t_id(5), atmos_phy_cp_rhot_t(:,:,:), & ! [IN]
658  var_t_name(5), 'ZXY' ) ! [IN]
659  call file_cartesc_write( restart_fid, var_t_id(6), atmos_phy_cp_rhoqv_t(:,:,:), & ! [IN]
660  var_t_name(6), 'ZXY' ) ! [IN]
661  do iq = 1, n_hyd
662  call file_cartesc_write( restart_fid, var_t_id(6+iq), atmos_phy_cp_rhohyd_t(:,:,:,iq), & ! [IN]
663  var_t_name(6+iq), 'ZXY' ) ! [IN]
664  enddo
665 
666  endif
667 
668  return
669  end subroutine atmos_phy_cp_vars_restart_write
670 
671  subroutine atmos_phy_cp_vars_check
672  use scale_statistics, only: &
674  statistics_total
675  use scale_atmos_grid_cartesc_real, only: &
680  use scale_atmos_hydrometeor, only: &
681  n_hyd
682  implicit none
683  integer :: iq
684  !---------------------------------------------------------------------------
685 
686  call valcheck( ka, ks, ke, ia, is, ie, ja, js, je, &
687  atmos_phy_cp_w0mean(:,:,:), & ! (in)
688  -100.0_rp, 100.0_rp, var_name(1), & ! (in)
689  __file__, __line__ ) ! (in)
690  call valcheck( ia, is, ie, ja, js, je, &
691  atmos_phy_cp_kf_nca(:,:), & ! (in)
692  -100.0_rp, 1.0e5_rp, var_name(2), & ! (in)
693  __file__, __line__ ) ! (in)
694  ! surface flux
695  call valcheck( ia, is, ie, ja, js, je, &
696  atmos_phy_cp_sflx_rain(:,:), & ! (in)
697  0.0e0_rp, 1.0e0_rp, var_t_name(1), & ! (in)
698  __file__, __line__ ) ! (in)
699  call valcheck( ia, is, ie, ja, js, je, &
700  atmos_phy_cp_sflx_snow(:,:), & ! (in)
701  0.0e0_rp, 1.0e0_rp, var_t_name(2), & ! (in)
702  __file__, __line__ ) ! (in)
703  call valcheck( ia, is, ie, ja, js, je, &
704  atmos_phy_cp_sflx_engi(:,:), & ! (in)
705  0.0e0_rp, 5.0e3_rp, var_t_name(3), & ! (in)
706  __file__, __line__ ) ! (in)
707  ! tendency
708  call valcheck( ka, ks, ke, ia, is, ie, ja, js, je, &
709  atmos_phy_cp_dens_t(:,:,:), & ! (in)
710  -1.0e0_rp, 1.0e0_rp, var_t_name(4), & ! (in)
711  __file__, __line__ ) ! (in)
712  call valcheck( ka, ks, ke, ia, is, ie, ja, js, je, &
713  atmos_phy_cp_rhot_t(:,:,:), & ! (in)
714  -1.0e3_rp, 1.0e3_rp, var_t_name(5), & ! (in)
715  __file__, __line__ ) ! (in)
716  call valcheck( ka, ks, ke, ia, is, ie, ja, js, je, &
717  atmos_phy_cp_rhoqv_t(:,:,:), & ! (in)
718  -1.0e0_rp, 1.0e0_rp, var_t_name(6), & ! (in)
719  __file__, __line__ ) ! (in)
720  do iq = 1, n_hyd
721  call valcheck( ka, ks, ke, ia, is, ie, ja, js, je, &
722  atmos_phy_cp_rhohyd_t(:,:,:,iq), & ! (in)
723  -1.0e0_rp, 1.0e0_rp, var_t_name(6+iq), & ! (in)
724  __file__, __line__ ) ! (in)
725  end do
726 
727  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
728  atmos_phy_cp_w0mean(:,:,:), var_name(1), & ! (in)
729  atmos_grid_cartesc_real_vol(:,:,:), & ! (in)
731  call statistics_total( ia, is, ie, ja, js, je, &
732  atmos_phy_cp_kf_nca(:,:), var_name(2), & ! (in)
733  atmos_grid_cartesc_real_area(:,:), & ! (in)
735  ! surface flux
736  call statistics_total( ia, is, ie, ja, js, je, &
737  atmos_phy_cp_sflx_rain(:,:), var_t_name(1), & ! (in)
738  atmos_grid_cartesc_real_area(:,:), & ! (in)
740  call statistics_total( ia, is, ie, ja, js, je, &
741  atmos_phy_cp_sflx_snow(:,:), var_t_name(2), & ! (in)
742  atmos_grid_cartesc_real_area(:,:), & ! (in)
744  call statistics_total( ia, is, ie, ja, js, je, &
745  atmos_phy_cp_sflx_engi(:,:), var_t_name(3), & ! (in)
746  atmos_grid_cartesc_real_area(:,:), & ! (in)
748  ! tendency
749  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
750  atmos_phy_cp_dens_t(:,:,:), var_t_name(4), & ! (in)
751  atmos_grid_cartesc_real_vol(:,:,:), & ! (in)
753  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
754  atmos_phy_cp_rhot_t(:,:,:), var_t_name(5), & ! (in)
755  atmos_grid_cartesc_real_vol(:,:,:), & ! (in)
757  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
758  atmos_phy_cp_rhoqv_t(:,:,:), var_t_name(6), & ! (in)
759  atmos_grid_cartesc_real_vol(:,:,:), & ! (in)
761  do iq = 1, n_hyd
762  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
763  atmos_phy_cp_rhohyd_t(:,:,:,iq), var_t_name(6+iq), & ! (in)
764  atmos_grid_cartesc_real_vol(:,:,:), & ! (in)
766  enddo
767 
768  return
769  end subroutine atmos_phy_cp_vars_check
770 
771 end module mod_atmos_phy_cp_vars
mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_write
subroutine, public atmos_phy_cp_vars_restart_write
Write restart.
Definition: mod_atmos_phy_cp_vars.F90:626
mod_atmos_phy_cp_vars::atmos_phy_cp_mflx_cloudbase
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase
Definition: mod_atmos_phy_cp_vars.F90:73
scale_statistics
module Statistics
Definition: scale_statistics.F90:11
mod_atmos_phy_cp_vars::atmos_phy_cp_rhoqv_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhoqv_t
Definition: mod_atmos_phy_cp_vars.F90:61
mod_atmos_phy_cp_vars::atmos_phy_cp_cloudbase
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_cloudbase
Definition: mod_atmos_phy_cp_vars.F90:75
scale_atmos_grid_cartesc_index::ke
integer, public ke
end point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:52
mod_atmos_phy_cp_vars::atmos_phy_cp_rhohyd_t
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhohyd_t
Definition: mod_atmos_phy_cp_vars.F90:62
mod_atmos_phy_cp_vars::atmos_phy_cp_restart_in_postfix_timelabel
logical, public atmos_phy_cp_restart_in_postfix_timelabel
Add timelabel to the basename of input file?
Definition: mod_atmos_phy_cp_vars.F90:49
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
mod_atmos_phy_cp_vars::atmos_phy_cp_cldfrac_sh
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_cldfrac_sh
Definition: mod_atmos_phy_cp_vars.F90:77
scale_atmos_hydrometeor::hyd_name
character(len=h_short), dimension(n_hyd), parameter, public hyd_name
Definition: scale_atmos_hydrometeor.F90:104
mod_atmos_phy_cp_vars::atmos_phy_cp_rhot_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t
Definition: mod_atmos_phy_cp_vars.F90:60
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_cp_vars::atmos_phy_cp_sflx_engi
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_engi
Definition: mod_atmos_phy_cp_vars.F90:65
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_phy_cp_vars::atmos_phy_cp_restart_out_dtype
character(len=h_short), public atmos_phy_cp_restart_out_dtype
REAL4 or REAL8.
Definition: mod_atmos_phy_cp_vars.F90:55
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
mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_open
subroutine, public atmos_phy_cp_vars_restart_open
Open restart file for read.
Definition: mod_atmos_phy_cp_vars.F90:383
mod_atmos_phy_cp_vars::atmos_phy_cp_cldfrac_dp
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_cldfrac_dp
Definition: mod_atmos_phy_cp_vars.F90:76
mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_create
subroutine, public atmos_phy_cp_vars_restart_create
Create restart file.
Definition: mod_atmos_phy_cp_vars.F90:508
mod_atmos_phy_cp_vars::atmos_phy_cp_w0mean
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_w0mean
Definition: mod_atmos_phy_cp_vars.F90:68
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
mod_atmos_phy_cp_vars::atmos_phy_cp_restart_output
logical, public atmos_phy_cp_restart_output
output restart file?
Definition: mod_atmos_phy_cp_vars.F90:46
mod_atmos_phy_cp_vars::atmos_phy_cp_restart_out_title
character(len=h_mid), public atmos_phy_cp_restart_out_title
title of the output file
Definition: mod_atmos_phy_cp_vars.F90:54
mod_atmos_phy_cp_vars::atmos_phy_cp_restart_in_basename
character(len=h_long), public atmos_phy_cp_restart_in_basename
Basename of the input file.
Definition: mod_atmos_phy_cp_vars.F90:48
mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_enddef
subroutine, public atmos_phy_cp_vars_restart_enddef
Exit netCDF define mode.
Definition: mod_atmos_phy_cp_vars.F90:545
scale_atmos_grid_cartesc_real
module Atmosphere GRID CartesC Real(real space)
Definition: scale_atmos_grid_cartesC_real.F90:11
scale_file
module file
Definition: scale_file.F90:15
mod_atmos_phy_cp_vars::atmos_phy_cp_restart_out_basename
character(len=h_long), public atmos_phy_cp_restart_out_basename
Basename of the output file.
Definition: mod_atmos_phy_cp_vars.F90:51
scale_prc
module PROCESS
Definition: scale_prc.F90:11
mod_atmos_phy_cp_vars::atmos_phy_cp_sflx_rain
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
Definition: mod_atmos_phy_cp_vars.F90:63
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
scale_atmos_grid_cartesc_index::ie
integer, public ie
end point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:54
mod_atmos_phy_cp_vars::atmos_phy_cp_sflx_snow
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_snow
Definition: mod_atmos_phy_cp_vars.F90:64
scale_io
module STDIO
Definition: scale_io.F90:10
mod_atmos_phy_cp_vars::atmos_phy_cp_restart_out_postfix_timelabel
logical, public atmos_phy_cp_restart_out_postfix_timelabel
Add timelabel to the basename of output file?
Definition: mod_atmos_phy_cp_vars.F90:53
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_cp_vars::atmos_phy_cp_vars_restart_close
subroutine, public atmos_phy_cp_vars_restart_close
Close restart file.
Definition: mod_atmos_phy_cp_vars.F90:559
scale_file_cartesc::file_cartesc_close
subroutine, public file_cartesc_close(fid)
Close a netCDF file.
Definition: scale_file_cartesC.F90:1044
mod_atmos_phy_cp_vars::atmos_phy_cp_restart_in_aggregate
logical, public atmos_phy_cp_restart_in_aggregate
Switch to use aggregate file.
Definition: mod_atmos_phy_cp_vars.F90:50
mod_atmos_phy_cp_vars::atmos_phy_cp_restart_out_aggregate
logical, public atmos_phy_cp_restart_out_aggregate
Switch to use aggregate file.
Definition: mod_atmos_phy_cp_vars.F90:52
mod_atmos_phy_cp_vars::atmos_phy_cp_vars_setup
subroutine, public atmos_phy_cp_vars_setup
Setup.
Definition: mod_atmos_phy_cp_vars.F90:130
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_grid_cartesc_index::ja
integer, public ja
Definition: scale_atmos_grid_cartesC_index.F90:49
scale_time
module TIME
Definition: scale_time.F90:11
mod_atmos_phy_cp_vars::atmos_phy_cp_cloudtop
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_cloudtop
Definition: mod_atmos_phy_cp_vars.F90:74
mod_atmos_phy_cp_vars::atmos_phy_cp_momz_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momz_t
Definition: mod_atmos_phy_cp_vars.F90:59
scale_tracer
module TRACER
Definition: scale_tracer.F90:12
mod_atmos_phy_cp_vars::atmos_phy_cp_vars_check
subroutine atmos_phy_cp_vars_check
Definition: mod_atmos_phy_cp_vars.F90:672
mod_atmos_phy_cp_vars::atmos_phy_cp_vars_fillhalo
subroutine, public atmos_phy_cp_vars_fillhalo
HALO Communication.
Definition: mod_atmos_phy_cp_vars.F90:316
scale_atmos_grid_cartesc_index::ks
integer, public ks
start point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:51
scale_debug
module DEBUG
Definition: scale_debug.F90:11
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
scale_statistics::statistics_checktotal
logical, public statistics_checktotal
calc&report variable totals to logfile?
Definition: scale_statistics.F90:109
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
scale_atmos_grid_cartesc_index::js
integer, public js
start point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:55
mod_atmos_phy_cp_vars::atmos_phy_cp_dens_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_dens_t
Definition: mod_atmos_phy_cp_vars.F90:58
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_cp_vars::atmos_phy_cp_vars_finalize
subroutine, public atmos_phy_cp_vars_finalize
Setup.
Definition: mod_atmos_phy_cp_vars.F90:277
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_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:43
mod_atmos_phy_cp_vars
module Atmosphere / Physics Cumulus
Definition: mod_atmos_phy_cp_vars.F90:12
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:57
mod_atmos_phy_cp_vars::atmos_phy_cp_kf_nca
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_kf_nca
Definition: mod_atmos_phy_cp_vars.F90:69
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_cp_vars::atmos_phy_cp_vars_restart_def_var
subroutine, public atmos_phy_cp_vars_restart_def_var
Write restart.
Definition: mod_atmos_phy_cp_vars.F90:579
mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_read
subroutine, public atmos_phy_cp_vars_restart_read
Read restart.
Definition: mod_atmos_phy_cp_vars.F90:418