SCALE-RM
Functions/Subroutines | Variables
mod_atmos_phy_cp_vars Module Reference

module Atmosphere / Physics Cumulus More...

Functions/Subroutines

subroutine, public atmos_phy_cp_vars_setup
 Setup. More...
 
subroutine, public atmos_phy_cp_vars_fillhalo
 HALO Communication. More...
 
subroutine, public atmos_phy_cp_vars_restart_read
 Read restart. More...
 
subroutine, public atmos_phy_cp_vars_restart_write
 Write restart. More...
 
subroutine, public atmos_phy_cp_vars_restart_create
 Create restart file. More...
 
subroutine, public atmos_phy_cp_vars_restart_enddef
 Exit netCDF define mode. More...
 
subroutine, public atmos_phy_cp_vars_restart_close
 Close restart file. More...
 
subroutine, public atmos_phy_cp_vars_restart_def_var
 Write restart. More...
 
subroutine, public atmos_phy_cp_vars_restart_write_var
 Write restart. More...
 

Variables

logical, public atmos_phy_cp_restart_output = .false.
 output restart file? More...
 
character(len=h_long), public atmos_phy_cp_restart_in_basename = ''
 basename of the restart file More...
 
character(len=h_long), public atmos_phy_cp_restart_out_basename = ''
 basename of the output file More...
 
character(len=h_mid), public atmos_phy_cp_restart_out_title = 'ATMOS_PHY_CP restart'
 title of the output file More...
 
character(len=h_mid), public atmos_phy_cp_restart_out_dtype = 'DEFAULT'
 REAL4 or REAL8. More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_dens_t
 
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momz_t
 
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momx_t
 
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momy_t
 
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t
 
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhoq_t
 
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase
 
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
 
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_cloudtop
 
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_cloudbase
 
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_cldfrac_dp
 
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_cldfrac_sh
 
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_kf_nca
 
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_kf_w0avg
 

Detailed Description

module Atmosphere / Physics Cumulus

Description
Container for mod_atmos_phy_cp
Author
Team SCALE
History
  • 2014-05-04 (H.Yashiro) [new]
NAMELIST
  • PARAM_ATMOS_PHY_CP_VARS
    nametypedefault valuecomment
    ATMOS_PHY_CP_RESTART_IN_BASENAME character(len=H_LONG) '' basename of the restart file
    ATMOS_PHY_CP_RESTART_OUTPUT logical .false. output restart file?
    ATMOS_PHY_CP_RESTART_OUT_BASENAME character(len=H_LONG) '' basename of the output file
    ATMOS_PHY_CP_RESTART_OUT_TITLE character(len=H_MID) 'ATMOS_PHY_CP restart' title of the output file
    ATMOS_PHY_CP_RESTART_OUT_DTYPE character(len=H_MID) 'DEFAULT' REAL4 or REAL8

History Output
No history output

Function/Subroutine Documentation

◆ atmos_phy_cp_vars_setup()

subroutine, public mod_atmos_phy_cp_vars::atmos_phy_cp_vars_setup ( )

Setup.

Definition at line 134 of file mod_atmos_phy_cp_vars.f90.

References scale_tracer::aq_name, atmos_phy_cp_cldfrac_dp, atmos_phy_cp_cldfrac_sh, atmos_phy_cp_cloudbase, atmos_phy_cp_cloudtop, atmos_phy_cp_dens_t, atmos_phy_cp_kf_nca, atmos_phy_cp_kf_w0avg, atmos_phy_cp_mflx_cloudbase, atmos_phy_cp_momx_t, atmos_phy_cp_momy_t, atmos_phy_cp_momz_t, atmos_phy_cp_restart_in_basename, atmos_phy_cp_restart_out_basename, atmos_phy_cp_restart_out_dtype, atmos_phy_cp_restart_out_title, atmos_phy_cp_restart_output, atmos_phy_cp_rhoq_t, atmos_phy_cp_rhot_t, atmos_phy_cp_sflx_rain, scale_const::const_undef, scale_grid_index::ia, scale_stdio::io_fid_conf, scale_stdio::io_fid_log, scale_stdio::io_l, scale_stdio::io_lnml, scale_grid_index::ja, scale_grid_index::ka, scale_process::prc_mpistop(), and scale_tracer::qa.

Referenced by mod_atmos_vars::atmos_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 / &
141  atmos_phy_cp_restart_in_basename, &
142  atmos_phy_cp_restart_output, &
143  atmos_phy_cp_restart_out_basename, &
144  atmos_phy_cp_restart_out_title, &
145  atmos_phy_cp_restart_out_dtype
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
237  if ( atmos_phy_cp_restart_output &
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'
242  atmos_phy_cp_restart_output = .false.
243  endif
244 
245  return
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momy_t
subroutine, public prc_mpistop
Abort MPI.
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momx_t
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
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_mflx_cloudbase
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_cp_vars_fillhalo()

subroutine, public mod_atmos_phy_cp_vars::atmos_phy_cp_vars_fillhalo ( )

HALO Communication.

Definition at line 251 of file mod_atmos_phy_cp_vars.f90.

References atmos_phy_cp_cldfrac_dp, atmos_phy_cp_cldfrac_sh, atmos_phy_cp_cloudbase, atmos_phy_cp_cloudtop, atmos_phy_cp_dens_t, atmos_phy_cp_kf_nca, atmos_phy_cp_kf_w0avg, atmos_phy_cp_mflx_cloudbase, atmos_phy_cp_rhoq_t, atmos_phy_cp_rhot_t, atmos_phy_cp_sflx_rain, scale_grid_index::ie, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, scale_grid_index::ka, scale_grid_index::ke, scale_grid_index::ks, and scale_tracer::qa.

Referenced by atmos_phy_cp_vars_restart_read().

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
262  atmos_phy_cp_cldfrac_dp( 1:ks-1,i,j) = atmos_phy_cp_cldfrac_dp(ks,i,j)
263  atmos_phy_cp_cldfrac_dp(ke+1:ka, i,j) = atmos_phy_cp_cldfrac_dp(ke,i,j)
264  atmos_phy_cp_cldfrac_sh( 1:ks-1,i,j) = atmos_phy_cp_cldfrac_sh(ks,i,j)
265  atmos_phy_cp_cldfrac_sh(ke+1:ka, i,j) = atmos_phy_cp_cldfrac_sh(ke,i,j)
266  atmos_phy_cp_kf_w0avg( 1:ks-1,i,j) = atmos_phy_cp_kf_w0avg(ks,i,j)
267  atmos_phy_cp_kf_w0avg(ke+1:ka, i,j) = atmos_phy_cp_kf_w0avg(ke,i,j)
268  atmos_phy_cp_dens_t( 1:ks-1,i,j) = atmos_phy_cp_dens_t(ks,i,j)
269  atmos_phy_cp_dens_t(ke+1:ka ,i,j) = atmos_phy_cp_dens_t(ke,i,j)
270  atmos_phy_cp_rhot_t( 1:ks-1,i,j) = atmos_phy_cp_rhot_t(ks,i,j)
271  atmos_phy_cp_rhot_t(ke+1:ka ,i,j) = atmos_phy_cp_rhot_t(ke,i,j)
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
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_dens_t
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhoq_t
module COMMUNICATION
Definition: scale_comm.F90:23
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
Here is the caller graph for this function:

◆ atmos_phy_cp_vars_restart_read()

subroutine, public mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_read ( )

Read restart.

Definition at line 318 of file mod_atmos_phy_cp_vars.f90.

References atmos_phy_cp_cldfrac_dp, atmos_phy_cp_cldfrac_sh, atmos_phy_cp_cloudbase, atmos_phy_cp_cloudtop, atmos_phy_cp_dens_t, atmos_phy_cp_kf_nca, atmos_phy_cp_kf_w0avg, atmos_phy_cp_mflx_cloudbase, atmos_phy_cp_restart_in_basename, atmos_phy_cp_rhoq_t, atmos_phy_cp_rhot_t, atmos_phy_cp_sflx_rain, atmos_phy_cp_vars_fillhalo(), scale_stdio::io_fid_log, scale_stdio::io_l, and scale_tracer::qa.

Referenced by mod_atmos_vars::atmos_vars_restart_read().

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 
360  call atmos_phy_cp_vars_fillhalo
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
module FILE I/O (netcdf)
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_dens_t
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhoq_t
module Statistics
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_cp_vars_restart_write()

subroutine, public mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_write ( )

Write restart.

Definition at line 388 of file mod_atmos_phy_cp_vars.f90.

References atmos_phy_cp_cldfrac_dp, atmos_phy_cp_cldfrac_sh, atmos_phy_cp_cloudbase, atmos_phy_cp_cloudtop, atmos_phy_cp_dens_t, atmos_phy_cp_kf_nca, atmos_phy_cp_kf_w0avg, atmos_phy_cp_mflx_cloudbase, atmos_phy_cp_restart_out_basename, atmos_phy_cp_restart_out_dtype, atmos_phy_cp_restart_out_title, atmos_phy_cp_rhoq_t, atmos_phy_cp_rhot_t, atmos_phy_cp_sflx_rain, scale_stdio::io_fid_log, scale_stdio::io_l, scale_tracer::qa, and scale_time::time_gettimelabel().

Referenced by mod_atmos_vars::atmos_vars_restart_write().

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
module FILE I/O (netcdf)
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_dens_t
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhoq_t
module Statistics
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_cp_vars_restart_create()

subroutine, public mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_create ( )

Create restart file.

Definition at line 445 of file mod_atmos_phy_cp_vars.f90.

References atmos_phy_cp_restart_out_basename, atmos_phy_cp_restart_out_dtype, atmos_phy_cp_restart_out_title, scale_fileio::fileio_create(), scale_stdio::io_fid_log, scale_stdio::io_l, and scale_time::time_gettimelabel().

Referenced by mod_atmos_vars::atmos_vars_restart_create().

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]
466  atmos_phy_cp_restart_out_dtype ) ! [IN]
467 
468  endif
469 
470  return
module FILE I/O (netcdf)
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
subroutine, public fileio_create(fid, basename, title, datatype, date, subsec, append, nozcoord)
Create/open a netCDF file.
module TIME
Definition: scale_time.F90:15
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_cp_vars_restart_enddef()

subroutine, public mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_enddef ( )

Exit netCDF define mode.

Definition at line 476 of file mod_atmos_phy_cp_vars.f90.

References scale_fileio::fileio_enddef().

Referenced by mod_atmos_vars::atmos_vars_restart_enddef().

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
module FILE I/O (netcdf)
subroutine, public fileio_enddef(fid)
Exit netCDF file define mode.
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_cp_vars_restart_close()

subroutine, public mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_close ( )

Close restart file.

Definition at line 490 of file mod_atmos_phy_cp_vars.f90.

References scale_fileio::fileio_close().

Referenced by mod_atmos_vars::atmos_vars_restart_close().

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
module FILE I/O (netcdf)
subroutine, public fileio_close(fid)
Close a netCDF file.
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_cp_vars_restart_def_var()

subroutine, public mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_def_var ( )

Write restart.

Definition at line 505 of file mod_atmos_phy_cp_vars.f90.

References atmos_phy_cp_restart_out_dtype, scale_fileio::fileio_def_var(), and scale_tracer::qa.

Referenced by mod_atmos_vars::atmos_vars_restart_def_var().

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
module FILE I/O (netcdf)
subroutine, public fileio_def_var(fid, vid, varname, desc, unit, axistype, datatype, timeintv)
Define a variable to file.
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_cp_vars_restart_write_var()

subroutine, public mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_write_var ( )

Write restart.

Definition at line 549 of file mod_atmos_phy_cp_vars.f90.

References atmos_phy_cp_cldfrac_dp, atmos_phy_cp_cldfrac_sh, atmos_phy_cp_cloudbase, atmos_phy_cp_cloudtop, atmos_phy_cp_dens_t, atmos_phy_cp_kf_nca, atmos_phy_cp_kf_w0avg, atmos_phy_cp_mflx_cloudbase, atmos_phy_cp_rhoq_t, atmos_phy_cp_rhot_t, atmos_phy_cp_sflx_rain, and scale_tracer::qa.

Referenced by mod_atmos_vars::atmos_vars_restart_write_var().

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
module FILE I/O (netcdf)
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_dens_t
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhoq_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
Here is the caller graph for this function:

Variable Documentation

◆ atmos_phy_cp_restart_output

logical, public mod_atmos_phy_cp_vars::atmos_phy_cp_restart_output = .false.

output restart file?

Definition at line 46 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), and atmos_phy_cp_vars_setup().

46  logical, public :: atmos_phy_cp_restart_output = .false.

◆ atmos_phy_cp_restart_in_basename

character(len=h_long), public mod_atmos_phy_cp_vars::atmos_phy_cp_restart_in_basename = ''

basename of the restart file

Definition at line 48 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), atmos_phy_cp_vars_restart_read(), and atmos_phy_cp_vars_setup().

48  character(len=H_LONG), public :: atmos_phy_cp_restart_in_basename = ''

◆ atmos_phy_cp_restart_out_basename

character(len=h_long), public mod_atmos_phy_cp_vars::atmos_phy_cp_restart_out_basename = ''

basename of the output file

Definition at line 49 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), atmos_phy_cp_vars_restart_create(), atmos_phy_cp_vars_restart_write(), and atmos_phy_cp_vars_setup().

49  character(len=H_LONG), public :: atmos_phy_cp_restart_out_basename = ''

◆ atmos_phy_cp_restart_out_title

character(len=h_mid), public mod_atmos_phy_cp_vars::atmos_phy_cp_restart_out_title = 'ATMOS_PHY_CP restart'

title of the output file

Definition at line 50 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), atmos_phy_cp_vars_restart_create(), atmos_phy_cp_vars_restart_write(), and atmos_phy_cp_vars_setup().

50  character(len=H_MID), public :: atmos_phy_cp_restart_out_title = 'ATMOS_PHY_CP restart'

◆ atmos_phy_cp_restart_out_dtype

character(len=h_mid), public mod_atmos_phy_cp_vars::atmos_phy_cp_restart_out_dtype = 'DEFAULT'

REAL4 or REAL8.

Definition at line 51 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), atmos_phy_cp_vars_restart_create(), atmos_phy_cp_vars_restart_def_var(), atmos_phy_cp_vars_restart_write(), and atmos_phy_cp_vars_setup().

51  character(len=H_MID), public :: atmos_phy_cp_restart_out_dtype = 'DEFAULT'

◆ atmos_phy_cp_dens_t

real(rp), dimension(:,:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_dens_t

Definition at line 53 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_atmos_phy_cp_driver::atmos_phy_cp_driver(), atmos_phy_cp_vars_fillhalo(), atmos_phy_cp_vars_restart_read(), atmos_phy_cp_vars_restart_write(), atmos_phy_cp_vars_restart_write_var(), and atmos_phy_cp_vars_setup().

53  real(RP), public, allocatable :: atmos_phy_cp_dens_t(:,:,:) ! tendency DENS [kg/m3/s]
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_dens_t

◆ atmos_phy_cp_momz_t

real(rp), dimension(:,:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_momz_t

Definition at line 54 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_atmos_phy_cp_driver::atmos_phy_cp_driver(), and atmos_phy_cp_vars_setup().

54  real(RP), public, allocatable :: atmos_phy_cp_momz_t(:,:,:) ! tendency MOMZ [kg/m2/s2]
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momz_t

◆ atmos_phy_cp_momx_t

real(rp), dimension(:,:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_momx_t

Definition at line 55 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_atmos_phy_cp_driver::atmos_phy_cp_driver(), and atmos_phy_cp_vars_setup().

55  real(RP), public, allocatable :: atmos_phy_cp_momx_t(:,:,:) ! tendency MOMX [kg/m2/s2]
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momx_t

◆ atmos_phy_cp_momy_t

real(rp), dimension(:,:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_momy_t

Definition at line 56 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_atmos_phy_cp_driver::atmos_phy_cp_driver(), and atmos_phy_cp_vars_setup().

56  real(RP), public, allocatable :: atmos_phy_cp_momy_t(:,:,:) ! tendency MOMY [kg/m2/s2]
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momy_t

◆ atmos_phy_cp_rhot_t

real(rp), dimension(:,:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_rhot_t

Definition at line 57 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_atmos_phy_cp_driver::atmos_phy_cp_driver(), atmos_phy_cp_vars_fillhalo(), atmos_phy_cp_vars_restart_read(), atmos_phy_cp_vars_restart_write(), atmos_phy_cp_vars_restart_write_var(), and atmos_phy_cp_vars_setup().

57  real(RP), public, allocatable :: atmos_phy_cp_rhot_t(:,:,:) ! tendency RHOT [K*kg/m3/s]
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t

◆ atmos_phy_cp_rhoq_t

real(rp), dimension(:,:,:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_rhoq_t

Definition at line 58 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_atmos_phy_cp_driver::atmos_phy_cp_driver(), atmos_phy_cp_vars_fillhalo(), atmos_phy_cp_vars_restart_read(), atmos_phy_cp_vars_restart_write(), atmos_phy_cp_vars_restart_write_var(), and atmos_phy_cp_vars_setup().

58  real(RP), public, allocatable :: atmos_phy_cp_rhoq_t(:,:,:,:) ! tendency rho*QTRC [kg/kg/s]
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhoq_t

◆ atmos_phy_cp_mflx_cloudbase

real(rp), dimension(:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_mflx_cloudbase

Definition at line 60 of file mod_atmos_phy_cp_vars.f90.

Referenced by mod_atmos_phy_cp_driver::atmos_phy_cp_driver(), atmos_phy_cp_vars_fillhalo(), atmos_phy_cp_vars_restart_read(), atmos_phy_cp_vars_restart_write(), atmos_phy_cp_vars_restart_write_var(), and atmos_phy_cp_vars_setup().

60  real(RP), public, allocatable :: atmos_phy_cp_mflx_cloudbase(:,:) ! cloud base mass flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase

◆ atmos_phy_cp_sflx_rain

real(rp), dimension (:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_sflx_rain

◆ atmos_phy_cp_cloudtop

real(rp), dimension (:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_cloudtop

Definition at line 62 of file mod_atmos_phy_cp_vars.f90.

Referenced by atmos_phy_cp_vars_fillhalo(), atmos_phy_cp_vars_restart_read(), atmos_phy_cp_vars_restart_write(), atmos_phy_cp_vars_restart_write_var(), and atmos_phy_cp_vars_setup().

62  real(RP), public, allocatable :: atmos_phy_cp_cloudtop (:,:) ! cloud top height [m]

◆ atmos_phy_cp_cloudbase

real(rp), dimension (:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_cloudbase

Definition at line 63 of file mod_atmos_phy_cp_vars.f90.

Referenced by atmos_phy_cp_vars_fillhalo(), atmos_phy_cp_vars_restart_read(), atmos_phy_cp_vars_restart_write(), atmos_phy_cp_vars_restart_write_var(), and atmos_phy_cp_vars_setup().

63  real(RP), public, allocatable :: atmos_phy_cp_cloudbase (:,:) ! cloud base height [m]

◆ atmos_phy_cp_cldfrac_dp

real(rp), dimension (:,:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_cldfrac_dp

Definition at line 64 of file mod_atmos_phy_cp_vars.f90.

Referenced by atmos_phy_cp_vars_fillhalo(), atmos_phy_cp_vars_restart_read(), atmos_phy_cp_vars_restart_write(), atmos_phy_cp_vars_restart_write_var(), and atmos_phy_cp_vars_setup().

64  real(RP), public, allocatable :: atmos_phy_cp_cldfrac_dp (:,:,:) ! cloud fraction (deep convection) [0-1]

◆ atmos_phy_cp_cldfrac_sh

real(rp), dimension (:,:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_cldfrac_sh

Definition at line 65 of file mod_atmos_phy_cp_vars.f90.

Referenced by atmos_phy_cp_vars_fillhalo(), atmos_phy_cp_vars_restart_read(), atmos_phy_cp_vars_restart_write(), atmos_phy_cp_vars_restart_write_var(), and atmos_phy_cp_vars_setup().

65  real(RP), public, allocatable :: atmos_phy_cp_cldfrac_sh (:,:,:) ! cloud fraction (shallow convection) [0-1]

◆ atmos_phy_cp_kf_nca

real(rp), dimension (:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_kf_nca

Definition at line 67 of file mod_atmos_phy_cp_vars.f90.

Referenced by atmos_phy_cp_vars_fillhalo(), atmos_phy_cp_vars_restart_read(), atmos_phy_cp_vars_restart_write(), atmos_phy_cp_vars_restart_write_var(), and atmos_phy_cp_vars_setup().

67  real(RP), public, allocatable :: atmos_phy_cp_kf_nca (:,:) ! advection/cumulus convection timescale/dt for KF[step]

◆ atmos_phy_cp_kf_w0avg

real(rp), dimension (:,:,:), allocatable, public mod_atmos_phy_cp_vars::atmos_phy_cp_kf_w0avg

Definition at line 68 of file mod_atmos_phy_cp_vars.f90.

Referenced by atmos_phy_cp_vars_fillhalo(), atmos_phy_cp_vars_restart_read(), atmos_phy_cp_vars_restart_write(), atmos_phy_cp_vars_restart_write_var(), and atmos_phy_cp_vars_setup().

68  real(RP), public, allocatable :: atmos_phy_cp_kf_w0avg (:,:,:) ! running mean vertical wind velocity for KF[m/s]