SCALE-RM
scale_atmos_phy_mp_kessler.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
12 !-------------------------------------------------------------------------------
13 #include "scalelib.h"
15  !-----------------------------------------------------------------------------
16  !
17  !++ used modules
18  !
19  use scale_precision
20  use scale_io
21  use scale_prof
22 
23  !-----------------------------------------------------------------------------
24  implicit none
25  private
26  !-----------------------------------------------------------------------------
27  !
28  !++ Public procedure
29  !
37 
38  !-----------------------------------------------------------------------------
39  !
40  !++ Public parameters & variables
41  !
42  integer, private, parameter :: QA_MP = 3
43 
44  integer, parameter, public :: atmos_phy_mp_kessler_ntracers = qa_mp
45  integer, parameter, public :: atmos_phy_mp_kessler_nwaters = 2
46  integer, parameter, public :: atmos_phy_mp_kessler_nices = 0
47  character(len=H_SHORT), parameter, public :: atmos_phy_mp_kessler_tracer_names(qa_mp) = (/ &
48  'QV', &
49  'QC', &
50  'QR' /)
51  character(len=H_MID) , parameter, public :: atmos_phy_mp_kessler_tracer_descriptions(qa_mp) = (/ &
52  'Ratio of Water Vapor mass to total mass (Specific humidity)', &
53  'Ratio of Cloud Water mass to total mass ', &
54  'Ratio of Rain Water mass to total mass '/)
55  character(len=H_SHORT), parameter, public :: atmos_phy_mp_kessler_tracer_units(qa_mp) = (/ &
56  'kg/kg', &
57  'kg/kg', &
58  'kg/kg' /)
59 
60 
61  !-----------------------------------------------------------------------------
62  !
63  !++ Private procedure
64  !
65  private :: mp_kessler
66 
67  !-----------------------------------------------------------------------------
68  !
69  !++ Private parameters & variables
70  !
71  integer, private, parameter :: i_qv = 1
72  integer, private, parameter :: i_qc = 2
73  integer, private, parameter :: i_qr = 3
74 
75  integer, private, parameter :: i_hyd_qc = 1
76  integer, private, parameter :: i_hyd_qr = 2
77 
78  logical, private :: flag_liquid = .true. ! warm rain
79  logical, private :: couple_aerosol = .false. ! Consider CCN effect ?
80 
81  real(rp), private, parameter :: re_qc = 8.e-6_rp ! effective radius for cloud water
82 
83  !-----------------------------------------------------------------------------
84 contains
85  !-----------------------------------------------------------------------------
90  use scale_prc, only: &
91  prc_abort
92  implicit none
93 
94  !---------------------------------------------------------------------------
95 
96  log_newline
97  log_info("ATMOS_PHY_MP_kessler_setup",*) 'Setup'
98  log_info("ATMOS_PHY_MP_kessler_setup",*) 'KESSLER-type 1-moment bulk 3 category'
99 
100  if( couple_aerosol ) then
101  log_error("ATMOS_PHY_MP_kessler_setup",*) 'MP_aerosol_couple should be .false. for KESSLER type MP!'
102  call prc_abort
103  endif
104 
105  return
106  end subroutine atmos_phy_mp_kessler_setup
107 
108  !-----------------------------------------------------------------------------
112  subroutine atmos_phy_mp_kessler_adjustment( &
113  KA, KS, KE, IA, IS, IE, JA, JS, JE, &
114  DENS, PRES, &
115  dt, &
116  TEMP, QTRC, CPtot, CVtot, &
117  RHOE_t, EVAPORATE )
118  use scale_const, only: &
119  dwatr => const_dwatr, &
120  pi => const_pi
121  use scale_file_history, only: &
122  file_history_in
123  use scale_atmos_phy_mp_common, only: &
124  mp_saturation_adjustment => atmos_phy_mp_saturation_adjustment
125  implicit none
126 
127  integer, intent(in) :: ka, ks, ke
128  integer, intent(in) :: ia, is, ie
129  integer, intent(in) :: ja, js, je
130  real(rp), intent(in) :: dens (ka,ia,ja) ! density [kg/m3]
131  real(rp), intent(in) :: pres (ka,ia,ja) ! pressure [Pa]
132  real(dp), intent(in) :: dt ! time interval of microphysics [s]
133  real(rp), intent(inout) :: temp (ka,ia,ja) ! temperature [K]
134  real(rp), intent(inout) :: qtrc (ka,ia,ja,qa_mp) ! tracer mass concentration [kg/kg]
135  real(rp), intent(inout) :: cptot (ka,ia,ja) ! total specific heat capacity at constant pressure [J/kg/K]
136  real(rp), intent(inout) :: cvtot (ka,ia,ja) ! total specific heat capacity at constant volume [J/kg/K]
137  real(rp), intent(out) :: rhoe_t (ka,ia,ja) ! tendency of rhoe [J/m3/s]
138  real(rp), intent(out) :: evaporate(ka,ia,ja) ! number of evaporated cloud [#/m3/s]
139 
140  real(rp) :: qtrc_dummy(ka,ia,ja)
141  real(rp) :: rhoe_d_sat(ka,ia,ja)
142  real(rp) :: qc_t_sat (ka,ia,ja)
143 
144  integer :: k, i, j
145  !---------------------------------------------------------------------------
146 
147  log_progress(*) 'atmosphere / physics / microphysics / Kessler'
148 
149  !##### MP Main #####
150  call mp_kessler( &
151  ka, ks, ke, ia, is, ie, ja, js, je, &
152  dens(:,:,:), pres(:,:,:), & ! [IN]
153  dt, & ! [IN]
154  temp(:,:,:), qtrc(:,:,:,:), & ! [INOUT]
155  cptot(:,:,:), cvtot(:,:,:), & ! [INOUT]
156  rhoe_t(:,:,:) ) ! [OUT]
157 
158  ! save value before saturation adjustment
159  do j = js, je
160  do i = is, ie
161  do k = ks, ke
162  qc_t_sat(k,i,j) = qtrc(k,i,j,i_qc)
163  enddo
164  enddo
165  enddo
166 
167 !OCL XFILL
168  qtrc_dummy(:,:,:) = -1.0_rp
169 
170  call mp_saturation_adjustment( &
171  ka, ks, ke, ia, is, ie, ja, js, je, &
172  dens(:,:,:), & ! [IN]
173  flag_liquid, & ! [IN]
174  temp(:,:,:), & ! [INOUT]
175  qtrc(:,:,:,i_qv), & ! [INOUT]
176  qtrc(:,:,:,i_qc), qtrc_dummy(:,:,:), & ! [INOUT]
177  cptot(:,:,:), cvtot(:,:,:), & ! [INOUT]
178  rhoe_d_sat(:,:,:) ) ! [OUT]
179 
180  do j = js, je
181  do i = is, ie
182  do k = ks, ke
183  rhoe_t(k,i,j) = rhoe_t(k,i,j) + rhoe_d_sat(k,i,j) / dt
184  enddo
185  enddo
186  enddo
187  do j = js, je
188  do i = is, ie
189  do k = ks, ke
190  qc_t_sat(k,i,j) = ( qtrc(k,i,j,i_qc) - qc_t_sat(k,i,j) ) / dt
191  enddo
192  enddo
193  enddo
194 
195  call file_history_in( qc_t_sat(:,:,:), 'Pcsat', 'QC production term by satadjust', 'kg/kg/s' )
196 
197  do j = js, je
198  do i = is, ie
199  do k = ks, ke
200  evaporate(k,i,j) = max( -qc_t_sat(k,i,j), 0.0_rp ) & ! if negative, condensation
201  * dens(k,i,j) / (4.0_rp/3.0_rp*pi*dwatr*re_qc**3) ! mass -> number (assuming constant particle radius as re_qc)
202  enddo
203  enddo
204  enddo
205 
206  !##### END MP Main #####
207 
208  return
209  end subroutine atmos_phy_mp_kessler_adjustment
210 
211  !-----------------------------------------------------------------------------
213  subroutine mp_kessler( &
214  KA, KS, KE, IA, IS, IE, JA, JS, JE, &
215  DENS0, PRES0, &
216  dt, &
217  TEMP0, QTRC0, &
218  CPtot0, CVtot0, &
219  RHOE_t )
220  use scale_const, only: &
221  eps => const_eps
222  use scale_atmos_hydrometeor, only: &
223  lhv, &
224  cp_vapor, &
225  cp_water, &
226  cv_vapor, &
227  cv_water
228  use scale_atmos_saturation, only: &
229  saturation_dens2qsat_liq => atmos_saturation_dens2qsat_liq
230  implicit none
231  integer, intent(in) :: ka, ks, ke
232  integer, intent(in) :: ia, is, ie
233  integer, intent(in) :: ja, js, je
234 
235  real(rp), intent(in) :: dens0(ka,ia,ja) ! density [kg/m3]
236  real(rp), intent(in) :: pres0(ka,ia,ja) ! pressure [Pa]
237  real(dp), intent(in) :: dt ! time interval of microphysics [s]
238 
239  real(rp), intent(inout) :: temp0 (ka,ia,ja) ! temperature [K]
240  real(rp), intent(inout) :: qtrc0 (ka,ia,ja,qa_mp) ! tracer mass concentration [kg/kg]
241  real(rp), intent(inout) :: cptot0(ka,ia,ja) ! total specific heat capacity at constant pressure [J/kg/K]
242  real(rp), intent(inout) :: cvtot0(ka,ia,ja) ! total specific heat capacity at constant volume [J/kg/K]
243 
244  real(rp), intent(out) :: rhoe_t(ka,ia,ja) ! tendency of rhoe [J/m3/s]
245 
246  real(rp) :: dens
247  real(rp) :: temp
248  real(rp) :: pres
249  real(rp) :: cptot, cvtot
250  real(rp) :: qv, qc, qr
251  real(rp) :: qv_t, qc_t, qr_t
252  real(rp) :: e_t, cp_t, cv_t
253  real(rp) :: qsatl ! saturated water vapor for liquid water [kg/kg]
254  real(rp) :: sliq ! saturated ratio S for liquid water (0-1)
255 
256  ! tendency
257  real(rp) :: dq_evap ! tendency q (evaporation)
258  real(rp) :: dq_auto ! tendency q (autoconversion)
259  real(rp) :: dq_accr ! tendency q (accretion)
260 
261  real(rp) :: vent_factor
262  real(rp) :: rdt
263 
264  integer :: k, i, j
265  !---------------------------------------------------------------------------
266 
267  call prof_rapstart('MP_kessler', 3)
268 
269  rdt = 1.0_rp / dt
270 
271  !$omp parallel do default(none) &
272  !$omp shared(KS,KE,IS,IE,JS,JE, &
273  !$omp DENS0,TEMP0,PRES0,QTRC0,CPtot0,CVtot0,dt, &
274  !$omp RHOE_t, &
275  !$omp EPS,LHV,CP_VAPOR,CP_WATER,CV_VAPOR,CV_WATER,rdt) &
276  !$omp private(k,i,j,dens,temp,pres,cptot,cvtot,qv,qc,qr,qv_t,qc_t,qr_t,e_t,cp_t,cv_t, &
277  !$omp QSATL,Sliq, &
278  !$omp dq_evap,dq_auto,dq_accr,vent_factor) &
279  !$omp OMP_SCHEDULE_ collapse(2)
280  do j = js, je
281  do i = is, ie
282  do k = ks, ke
283 
284  ! store to work
285  dens = dens0(k,i,j)
286  temp = temp0(k,i,j)
287  pres = pres0(k,i,j)
288  qv = qtrc0(k,i,j,i_qv)
289  qc = qtrc0(k,i,j,i_qc)
290  qr = qtrc0(k,i,j,i_qr)
291 
292  call saturation_dens2qsat_liq( &
293  temp, dens, & ! [IN]
294  qsatl ) ! [OUT]
295 
296  sliq = qv / max( qsatl, eps)
297 
298  ! Auto-conversion (QC->QR)
299  dq_auto = 1.e-3_rp * max( qc-1.e-3_rp, 0.0_rp )
300 
301  ! Accretion (QC->QR)
302  dq_accr = 2.2_rp * qc * qr**0.875_rp
303 
304  ! Evaporation (QR->QV)
305  vent_factor = 1.6_rp + 124.9_rp * ( dens*qr )**0.2046_rp
306  dq_evap = ( 1.0_rp-min(sliq,1.0_rp) ) / dens * vent_factor &
307  * ( dens*qr )**0.525_rp / ( 5.4e5_rp + 2.55e8_rp / ( pres*qsatl ) )
308 
309  ! limiter
310  qc_t = (-dq_auto-dq_accr )
311  qc_t = max( qc_t, -qc*rdt )
312 
313  qr_t = ( dq_auto+dq_accr-dq_evap )
314  qr_t = max( qr_t, -qr*rdt )
315 
316  qv_t = - ( qc_t + qr_t )
317  qv_t = max( qv_t, -qv*rdt)
318 
319  ! mass & energy update
320  qtrc0(k,i,j,i_qv) = qtrc0(k,i,j,i_qv) + qv_t * dt
321  qtrc0(k,i,j,i_qc) = qtrc0(k,i,j,i_qc) + qc_t * dt
322  qtrc0(k,i,j,i_qr) = qtrc0(k,i,j,i_qr) + qr_t * dt
323 
324  e_t = -lhv * qv_t ! internal energy change
325  cp_t = cp_vapor * qv_t &
326  + cp_water * ( qc_t + qr_t )
327  cptot = cptot0(k,i,j) + cp_t * dt
328 
329  cv_t = cv_vapor * qv_t &
330  + cv_water * ( qc_t + qr_t )
331  cvtot = cvtot0(k,i,j) + cv_t * dt
332 
333  rhoe_t(k,i,j) = dens * e_t
334 
335  temp0(k,i,j) = ( temp * cvtot0(k,i,j) + e_t * dt ) / cvtot
336  cptot0(k,i,j) = cptot
337  cvtot0(k,i,j) = cvtot
338 
339  enddo
340  enddo
341  enddo
342 
343  call prof_rapend ('MP_kessler', 3)
344 
345  return
346  end subroutine mp_kessler
347 
348  !-----------------------------------------------------------------------------
350 !OCL SERIAL
352  KA, KS, KE, &
353  DENS0, RHOQ0, &
354  REFSTATE_dens_profile, &
355  vterm )
356  implicit none
357 
358  integer, intent(in) :: ka, ks, ke
359  real(rp), intent(in) :: dens0 (ka) ! density [kg/m3]
360  real(rp), intent(in) :: rhoq0 (ka,qa_mp-1) ! density of each hydrometeor [kg/m3]
361  real(rp), intent(in) :: refstate_dens_profile(ka) ! reference state density profile [kg/m3]
362  real(rp), intent(out) :: vterm (ka,qa_mp-1) ! terminal velocity of each hydrometeor [m/s]
363 
364  real(rp) :: qr
365  real(rp) :: zerosw
366 
367  integer :: k
368  !---------------------------------------------------------------------------
369 
370  do k = ks, ke
371  vterm(k,i_hyd_qc) = 0.0_rp
372  enddo
373 
374  do k = ks, ke
375  qr = rhoq0(k,i_hyd_qr) / dens0(k)
376  zerosw = 0.5_rp - sign(0.5_rp, qr - 1.e-12_rp )
377 
378  vterm(k,i_hyd_qr) = - 36.34_rp * ( dens0(k) * ( qr + zerosw ) )**0.1364_rp &
379  * refstate_dens_profile(ks) / refstate_dens_profile(k) * ( 1.0_rp - zerosw )
380  enddo
381 
382  return
384 
385  !-----------------------------------------------------------------------------
388  KA, KS, KE, IA, IS, IE, JA, JS, JE, &
389  QTRC, &
390  mask_criterion, &
391  cldfrac )
392  implicit none
393  integer, intent(in) :: ka, ks, ke
394  integer, intent(in) :: ia, is, ie
395  integer, intent(in) :: ja, js, je
396 
397  real(rp), intent(in) :: qtrc(ka,ia,ja,qa_mp-1) ! hydrometeor mass concentration [kg/kg]
398  real(rp), intent(in) :: mask_criterion ! criterion of hydrometeor [kg/kg]
399 
400  real(rp), intent(out) :: cldfrac(ka,ia,ja) ! cloud fraction (0 or 1)
401 
402  real(rp) :: qhydro
403  integer :: k, i, j
404  !---------------------------------------------------------------------------
405 
406  do j = js, je
407  do i = is, ie
408  do k = ks, ke
409  qhydro = qtrc(k,i,j,i_hyd_qc) + qtrc(k,i,j,i_hyd_qr)
410  cldfrac(k,i,j) = 0.5_rp + sign(0.5_rp,qhydro-mask_criterion)
411  enddo
412  enddo
413  enddo
414 
415  return
417 
418  !-----------------------------------------------------------------------------
421  KA, KS, KE, IA, IS, IE, JA, JS, JE, &
422  DENS0, TEMP0, QTRC0, &
423  Re )
425  n_hyd, &
426  i_hc, &
427  i_hr
428  implicit none
429  integer, intent(in) :: ka, ks, ke
430  integer, intent(in) :: ia, is, ie
431  integer, intent(in) :: ja, js, je
432 
433  real(rp), intent(in) :: dens0(ka,ia,ja) ! density [kg/m3]
434  real(rp), intent(in) :: temp0(ka,ia,ja) ! temperature [K]
435  real(rp), intent(in) :: qtrc0(ka,ia,ja,qa_mp-1) ! hydrometeor mass concentration [kg/kg]
436 
437  real(rp), intent(out) :: re (ka,ia,ja,n_hyd) ! effective radius [cm]
438 
439  real(rp), parameter :: um2cm = 100.0_rp
440  !---------------------------------------------------------------------------
441 
442 !OCL XFILL
443  re(:,:,:,i_hc) = 8.e-6_rp * um2cm
444 !OCL XFILL
445  re(:,:,:,i_hr) = 100.e-6_rp * um2cm
446 !OCL XFILL
447  re(:,:,:,i_hr+1:) = 0.0_rp
448 
449  return
451 
452  !-----------------------------------------------------------------------------
454  subroutine atmos_phy_mp_kessler_qtrc2qhyd( &
455  KA, KS, KE, IA, IS, IE, JA, JS, JE, &
456  QTRC, &
457  Qe )
459  n_hyd, &
460  i_hc, &
461  i_hr
462  implicit none
463  integer, intent(in) :: ka, ks, ke
464  integer, intent(in) :: ia, is, ie
465  integer, intent(in) :: ja, js, je
466 
467  real(rp), intent(in) :: qtrc(ka,ia,ja,qa_mp-1) ! hydrometeor mass concentration [kg/kg]
468 
469  real(rp), intent(out) :: qe(ka,ia,ja,n_hyd) ! mass ratio of each hydrometeor [kg/kg]
470  !---------------------------------------------------------------------------
471 
472 !OCL XFILL
473  qe(:,:,:,i_hc) = qtrc(:,:,:,i_hyd_qc)
474 !OCL XFILL
475  qe(:,:,:,i_hr) = qtrc(:,:,:,i_hyd_qr)
476 !OCL XFILL
477  qe(:,:,:,i_hr+1:) = 0.0_rp
478 
479  return
480  end subroutine atmos_phy_mp_kessler_qtrc2qhyd
481 
482  !-----------------------------------------------------------------------------
484  subroutine atmos_phy_mp_kessler_qhyd2qtrc( &
485  KA, KS, KE, IA, IS, IE, JA, JS, JE, &
486  Qe, &
487  QTRC )
489  n_hyd, &
490  i_hc, &
491  i_hr
492  implicit none
493  integer, intent(in) :: ka, ks, ke
494  integer, intent(in) :: ia, is, ie
495  integer, intent(in) :: ja, js, je
496 
497  real(rp), intent(in) :: qe(ka,ia,ja,n_hyd) ! mass ratio of each hydrometeor [kg/kg]
498 
499  real(rp), intent(out) :: qtrc(ka,ia,ja,qa_mp-1) ! hydrometeor mass concentration [kg/kg]
500 
501  !---------------------------------------------------------------------------
502 
503 !OCL XFILL
504  qtrc(:,:,:,i_hyd_qc) = qe(:,:,:,i_hc)
505 !OCL XFILL
506  qtrc(:,:,:,i_hyd_qr) = qe(:,:,:,i_hr)
507 
508  ! ignore ice water
509 
510  return
511  end subroutine atmos_phy_mp_kessler_qhyd2qtrc
512 
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_cloud_fraction
subroutine, public atmos_phy_mp_kessler_cloud_fraction(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC, mask_criterion, cldfrac)
Calculate Cloud Fraction.
Definition: scale_atmos_phy_mp_kessler.F90:392
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_terminal_velocity
subroutine, public atmos_phy_mp_kessler_terminal_velocity(KA, KS, KE, DENS0, RHOQ0, REFSTATE_dens_profile, vterm)
Kessler-type warm rain microphysics (terminal velocity)
Definition: scale_atmos_phy_mp_kessler.F90:356
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
scale_atmos_hydrometeor::i_hr
integer, parameter, public i_hr
liquid water rain
Definition: scale_atmos_hydrometeor.F90:82
scale_atmos_hydrometeor::cp_water
real(rp), public cp_water
CP for water [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:133
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_adjustment
subroutine, public atmos_phy_mp_kessler_adjustment(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS, PRES, dt, TEMP, QTRC, CPtot, CVtot, RHOE_t, EVAPORATE)
ATMOS_PHY_MP_kessler_adjustment calculate state after saturation process.
Definition: scale_atmos_phy_mp_kessler.F90:118
scale_precision
module PRECISION
Definition: scale_precision.F90:14
scale_const::const_eps
real(rp), public const_eps
small number
Definition: scale_const.F90:33
scale_prof::prof_rapstart
subroutine, public prof_rapstart(rapname_base, level, disable_barrier)
Start raptime.
Definition: scale_prof.F90:159
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_tracer_names
character(len=h_short), dimension(qa_mp), parameter, public atmos_phy_mp_kessler_tracer_names
Definition: scale_atmos_phy_mp_kessler.F90:47
scale_file_history
module file_history
Definition: scale_file_history.F90:15
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_const::const_pi
real(rp), public const_pi
pi
Definition: scale_const.F90:31
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
scale_atmos_hydrometeor::cv_vapor
real(rp), public cv_vapor
CV for vapor [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:130
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_nwaters
integer, parameter, public atmos_phy_mp_kessler_nwaters
Definition: scale_atmos_phy_mp_kessler.F90:45
scale_io
module STDIO
Definition: scale_io.F90:10
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_ntracers
integer, parameter, public atmos_phy_mp_kessler_ntracers
Definition: scale_atmos_phy_mp_kessler.F90:44
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_effective_radius
subroutine, public atmos_phy_mp_kessler_effective_radius(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS0, TEMP0, QTRC0, Re)
Calculate Effective Radius.
Definition: scale_atmos_phy_mp_kessler.F90:424
scale_atmos_hydrometeor::lhv
real(rp), public lhv
latent heat of vaporization for use [J/kg]
Definition: scale_atmos_hydrometeor.F90:126
scale_atmos_phy_mp_common
module ATMOSPHERE / Physics Cloud Microphysics - Common
Definition: scale_atmos_phy_mp_common.F90:13
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_qtrc2qhyd
subroutine, public atmos_phy_mp_kessler_qtrc2qhyd(KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC, Qe)
Calculate mass ratio of each category.
Definition: scale_atmos_phy_mp_kessler.F90:458
scale_prof
module profiler
Definition: scale_prof.F90:11
scale_precision::dp
integer, parameter, public dp
Definition: scale_precision.F90:32
scale_atmos_phy_mp_kessler
module atmosphere / physics / microphysics / Kessler
Definition: scale_atmos_phy_mp_kessler.F90:14
scale_atmos_hydrometeor::i_hc
integer, parameter, public i_hc
liquid water cloud
Definition: scale_atmos_hydrometeor.F90:81
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_tracer_descriptions
character(len=h_mid), dimension(qa_mp), parameter, public atmos_phy_mp_kessler_tracer_descriptions
Definition: scale_atmos_phy_mp_kessler.F90:51
scale_const::const_dwatr
real(rp), parameter, public const_dwatr
density of water [kg/m3]
Definition: scale_const.F90:82
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_qhyd2qtrc
subroutine, public atmos_phy_mp_kessler_qhyd2qtrc(KA, KS, KE, IA, IS, IE, JA, JS, JE, Qe, QTRC)
Calculate mass ratio of each category.
Definition: scale_atmos_phy_mp_kessler.F90:488
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_nices
integer, parameter, public atmos_phy_mp_kessler_nices
Definition: scale_atmos_phy_mp_kessler.F90:46
scale_prof::prof_rapend
subroutine, public prof_rapend(rapname_base, level, disable_barrier)
Save raptime.
Definition: scale_prof.F90:217
scale_atmos_saturation
module atmosphere / saturation
Definition: scale_atmos_saturation.F90:12
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_setup
subroutine, public atmos_phy_mp_kessler_setup
ATMOS_PHY_MP_kessler_setup Setup.
Definition: scale_atmos_phy_mp_kessler.F90:90
scale_atmos_hydrometeor::n_hyd
integer, parameter, public n_hyd
Definition: scale_atmos_hydrometeor.F90:79
scale_atmos_hydrometeor::cp_vapor
real(rp), public cp_vapor
CP for vapor [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:131
scale_atmos_hydrometeor::cv_water
real(rp), public cv_water
CV for water [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:132
scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_tracer_units
character(len=h_short), dimension(qa_mp), parameter, public atmos_phy_mp_kessler_tracer_units
Definition: scale_atmos_phy_mp_kessler.F90:55