SCALE-RM
mod_atmos_phy_cp_driver.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
21  use scale_tracer
22  !-----------------------------------------------------------------------------
23  implicit none
24  private
25  !-----------------------------------------------------------------------------
26  !
27  !++ Public procedure
28  !
31 
32  !-----------------------------------------------------------------------------
33  !
34  !++ Public parameters & variables
35  !
36  !-----------------------------------------------------------------------------
37  !
38  !++ Private procedure
39  !
40  !-----------------------------------------------------------------------------
41  !
42  !++ Private parameters & variables
43  !
44  !-----------------------------------------------------------------------------
45 contains
46  !-----------------------------------------------------------------------------
48  subroutine atmos_phy_cp_driver_setup
49  use scale_prc, only: &
50  prc_abort
51  use scale_atmos_phy_cp_common, only: &
53  use scale_atmos_phy_cp_kf, only: &
55  use mod_atmos_admin, only: &
58  use scale_time , only :&
59  time_dtsec, &
64  use scale_atmos_hydrometeor, only: &
66  implicit none
67 
68  logical :: warmrain
69  !---------------------------------------------------------------------------
70 
71  log_newline
72  log_info("ATMOS_PHY_CP_driver_setup",*) 'Setup'
73 
74  if ( atmos_sw_phy_cp ) then
75 
76  ! setup library component
78  select case ( atmos_phy_cp_type )
79  case ( 'KF' )
80  warmrain = ( .not. atmos_hydrometeor_ice_phase )
81  call atmos_phy_cp_kf_setup( ka, ks, ke, ia, 1, ia, ja, 1, ja, &
84  warmrain )
85  case default
86  log_error("ATMOS_PHY_CP_driver_setup",*) 'ATMOS_PHY_CP_TYPE (', trim(atmos_phy_cp_type), ') is invalid. Check!'
87  call prc_abort
88  end select
89 
90  else
91  log_info("ATMOS_PHY_CP_driver_setup",*) 'this component is never called.'
92  endif
93 
94  return
95  end subroutine atmos_phy_cp_driver_setup
96 
97  !-----------------------------------------------------------------------------
99  subroutine atmos_phy_cp_driver_calc_tendency( update_flag )
100  use scale_statistics, only: &
102  statistics_total
103  use scale_atmos_grid_cartesc_real, only: &
112  use scale_file_history, only: &
113  file_history_in
114  use scale_time , only :&
115  time_dtsec, &
117  use scale_atmos_grid_cartesc_real, only: &
119  use scale_atmos_hydrometeor, only: &
120  hyd_name
121  use scale_atmos_phy_cp_kf, only: &
123  use scale_atmos_phy_cp_common, only: &
125  use mod_atmos_phy_mp_vars, only: &
126  qs_mp, &
127  qe_mp
128  use mod_atmos_phy_mp_driver, only: &
130  use mod_atmos_admin, only: &
132  use mod_atmos_vars, only: &
133  dens => dens_av, &
134  momz => momz_av, &
135  momx => momx_av, &
136  momy => momy_av, &
137  rhot => rhot_av, &
138  qtrc => qtrc_av, &
139  dens_t => dens_tp, &
140  momz_t => momz_tp, &
141  momx_t => momx_tp, &
142  momy_t => momy_tp, &
143  rhot_t => rhot_tp, &
144  rhoq_t => rhoq_tp, &
145  u, &
146  v, &
147  w, &
148  temp, &
149  pres, &
150  qdry, &
151  qv, &
152  rtot, &
153  cptot
154  use scale_atmos_hydrometeor, only: &
155  n_hyd
156  use mod_atmos_phy_cp_vars, only: &
157  dens_t_cp => atmos_phy_cp_dens_t, &
158  rhot_t_cp => atmos_phy_cp_rhot_t, &
159  rhoqv_t_cp => atmos_phy_cp_rhoqv_t, &
160  rhohyd_t_cp => atmos_phy_cp_rhohyd_t, &
161  mflx_cloudbase => atmos_phy_cp_mflx_cloudbase, &
162  sflx_rain => atmos_phy_cp_sflx_rain, & ! convective rain [kg/m2/s]
163  cloudtop => atmos_phy_cp_cloudtop, & ! cloud top height [m]
164  cloudbase => atmos_phy_cp_cloudbase, & ! cloud base height [m]
165  cldfrac_dp => atmos_phy_cp_cldfrac_dp, & ! cloud fraction (deep convection) (0-1)
166  cldfrac_sh => atmos_phy_cp_cldfrac_sh, & ! cloud fraction (shallow convection) (0-1)
167  w0mean => atmos_phy_cp_w0mean, & ! running mean vertical wind velocity [m/s]
168  kf_nca => atmos_phy_cp_kf_nca ! advection/cumulus convection timescale/dt for KF [step]
169  implicit none
170 
171  logical, intent(in) :: update_flag
172 
173  real(RP) :: RHOQ_t_CP(ka,ia,ja,qs_mp:qe_mp)
174 
175  integer :: k, i, j, iq
176  !---------------------------------------------------------------------------
177 
178  ! temporal running mean of vertical velocity
179  call atmos_phy_cp_common_wmean( ka, ks, ke, ia, 1, ia, ja, 1, ja, &
180  w(:,:,:), & ! [IN]
182  w0mean(:,:,:) ) ! [INOUT]
183  call file_history_in( w0mean(:,:,:), 'w0mean', 'running mean vertical wind velocity', 'kg/m2/s', fill_halo=.true. )
184 
185  if ( update_flag ) then ! update
186  select case ( atmos_phy_cp_type )
187  case ( 'KF' )
188  call atmos_phy_cp_kf_tendency( ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
189  dens(:,:,:), & ! [IN]
190  u(:,:,:), v(:,:,:), & ! [IN]
191  rhot(:,:,:), temp(:,:,:), pres(:,:,:), & ! [IN]
192  qdry(:,:,:), qv(:,:,:), & ! [IN]
193  rtot(:,:,:), cptot(:,:,:), & ! [IN]
194  w0mean(:,:,:), & ! [IN]
195  fz, & ! [IN]
196  time_dtsec_atmos_phy_cp, & ! [IN]
197  dens_t_cp(:,:,:), & ! [INOUT]
198  rhot_t_cp(:,:,:), & ! [INOUT]
199  rhoqv_t_cp(:,:,:), rhohyd_t_cp(:,:,:,:), & ! [INOUT]
200  sflx_rain(:,:), & ! [OUT]
201  cloudtop(:,:), cloudbase(:,:), & ! [OUT]
202  cldfrac_dp(:,:,:), cldfrac_sh(:,:,:), & ! [OUT]
203  kf_nca(:,:) ) ! [OUT]
204  end select
205 
206 !OCL XFILL
207  do j = jsb, jeb
208  do i = isb, ieb
209  mflx_cloudbase(i,j) = 0.0_rp
210  enddo
211  enddo
212 
213  ! diagnose tendency of number concentration
214 
215  call file_history_in( mflx_cloudbase(:,:), 'CBMFX', 'cloud base mass flux', 'kg/m2/s', fill_halo=.true. )
216  call file_history_in( sflx_rain(:,:), 'RAIN_CP', 'surface rain rate by CP', 'kg/m2/s', fill_halo=.true. )
217  call file_history_in( sflx_rain(:,:), 'PREC_CP', 'surface precipitation rate by CP', 'kg/m2/s', fill_halo=.true. )
218  call file_history_in( cloudtop(:,:), 'CUMHGT', 'CP cloud top height', 'm', fill_halo=.true. )
219  call file_history_in( cloudbase(:,:), 'CUBASE', 'CP cloud base height', 'm', fill_halo=.true. )
220  call file_history_in( cldfrac_dp(:,:,:), 'CUMFRC_DP', 'CP cloud fraction (deep)', '1', fill_halo=.true. )
221  call file_history_in( cldfrac_sh(:,:,:), 'CUMFRC_SH', 'CP cloud fraction (shallow)', '1', fill_halo=.true. )
222  call file_history_in( kf_nca(:,:), 'kf_nca', 'advection or cumulus convection timescale for KF', 's', fill_halo=.true. )
223 
224  call file_history_in( dens_t_cp(:,:,:), 'DENS_t_CP', 'tendency DENS in CP', 'kg/m3/s' , fill_halo=.true. )
225  call file_history_in( rhot_t_cp(:,:,:), 'RHOT_t_CP', 'tendency RHOT in CP', 'K*kg/m3/s', fill_halo=.true. )
226 
227  call file_history_in( rhoqv_t_cp(:,:,:), 'QV_t_CP', 'tendency rho*QV in CP', 'kg/m3/s', fill_halo=.true. )
228  do iq = 1, n_hyd
229  call file_history_in( rhohyd_t_cp(:,:,:,iq), trim(hyd_name(iq))//'_t_CP', &
230  'tendency rho*'//trim(hyd_name(iq))//' in CP', 'kg/m3/s', fill_halo=.true. )
231  enddo
232 
233  endif ! update
234 
235  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
236  do j = jsb, jeb
237  do i = isb, ieb
238  do k = ks, ke
239  dens_t(k,i,j) = dens_t(k,i,j) + dens_t_cp(k,i,j)
240  rhot_t(k,i,j) = rhot_t(k,i,j) + rhot_t_cp(k,i,j)
241  enddo
242  enddo
243  enddo
244 
246  rhoqv_t_cp(:,:,:), rhohyd_t_cp(:,:,:,:), & ! [IN]
247  rhoq_t_cp(:,:,:,qs_mp:qe_mp) ) ! [OUT]
248 
249  do iq = qs_mp, qe_mp
250  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(3)
251  do j = jsb, jeb
252  do i = isb, ieb
253  do k = ks, ke
254  rhoq_t(k,i,j,iq) = rhoq_t(k,i,j,iq) + rhoq_t_cp(k,i,j,iq)
255  enddo
256  enddo
257  enddo
258  enddo
259 
260  if ( statistics_checktotal ) then
261  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
262  dens_t_cp(:,:,:), 'DENS_t_CP', &
263  atmos_grid_cartesc_real_vol(:,:,:), &
264  atmos_grid_cartesc_real_totvol )
265  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
266  rhot_t_cp(:,:,:), 'RHOT_t_CP', &
267  atmos_grid_cartesc_real_vol(:,:,:), &
268  atmos_grid_cartesc_real_totvol )
269 
270  do iq = qs_mp, qe_mp
271  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
272  rhoq_t_cp(:,:,:,iq), trim(tracer_name(iq))//'_t_CP', &
273  atmos_grid_cartesc_real_vol(:,:,:), &
274  atmos_grid_cartesc_real_totvol )
275  enddo
276  endif
277 
278  return
279  end subroutine atmos_phy_cp_driver_calc_tendency
280 
281 end module mod_atmos_phy_cp_driver
module ATMOS admin
real(rp), dimension(:,:,:), allocatable, public dens_tp
logical, public atmos_sw_phy_cp
real(rp), dimension(:,:,:), allocatable, target, public momz
subroutine, public atmos_phy_cp_common_setup
Setup.
module Atmosphere / Physics Cumulus
character(len=h_short), dimension(n_hyd), parameter, public hyd_name
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_dens_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhoqv_t
real(rp), dimension(:,:,:), allocatable, target, public rhot
real(rp), dimension(:,:,:), allocatable, public momy_tp
real(rp), dimension(:,:,:), allocatable, target, public qdry
integer, public ia
of whole cells: x, local, with HALO
module Atmosphere / Physics Cloud Microphysics
module ATMOSPHERE / Physics Cumulus
module ATMOSPHERIC Variables
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
real(rp), dimension(:,:,:), allocatable, target, public momx
real(rp), public atmos_grid_cartesc_real_totvolzxv
total volume (zxv, local) [m3]
real(rp), dimension(:,:,:), allocatable, public rhot_tp
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_vol
control volume (zxy) [m3]
character(len=h_short), public atmos_phy_cp_type
real(rp), public atmos_grid_cartesc_real_totvol
total volume (zxy, local) [m3]
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fz
geopotential height [m] (wxy)
integer, public ja
of whole cells: y, local, with HALO
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volzxv
control volume (zxv) [m3]
real(rp), dimension(:,:,:), allocatable, target, public dens
character(len=h_short), dimension(qa_max), public tracer_name
logical, public statistics_checktotal
calc&report variable totals to logfile?
module atmosphere / physics / cumulus / Common
subroutine, public atmos_phy_cp_kf_setup(KA, KS, KE, IA, IS, IE, JA, JS, JE, CZ, AREA, TIME_DTSEC, KF_DTSEC, WARMRAIN_in)
Setup initial setup for Kain-Fritsch Cumulus Parameterization.
real(rp), public atmos_grid_cartesc_real_totvolzuy
total volume (zuy, local) [m3]
integer, public is
start point of inner domain: x, local
integer, public ie
end point of inner domain: x, local
real(rp), dimension(:,:,:), pointer, public momx_av
module TRACER
module atmosphere / hydrometeor
subroutine, public atmos_phy_mp_driver_qhyd2qtrc(KA, KS, KE, IA, IS, IE, JA, JS, JE, QV, QHYD, QTRC, QNUM)
subroutine, public atmos_phy_cp_driver_setup
Setup.
real(dp), public time_dtsec
time interval of model [sec]
Definition: scale_time.F90:38
module atmosphere / grid / cartesC index
integer, public ke
end point of inner domain: z, local
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volwxy
control volume (wxy) [m3]
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t
module PROCESS
Definition: scale_prc.F90:11
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
integer, public je
end point of inner domain: y, local
real(rp), dimension(:,:,:), allocatable, target, public temp
real(rp), dimension(:,:,:), allocatable, target, public w
module TIME
Definition: scale_time.F90:16
integer, public ks
start point of inner domain: z, local
real(rp), dimension(:,:,:), pointer, public dens_av
logical, public atmos_hydrometeor_ice_phase
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
real(rp), dimension(:,:,:), allocatable, pointer, target, public qv
integer, public js
start point of inner domain: y, local
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhohyd_t
module atmosphere / physics / cumulus / Kain-Fritsch
real(dp), public time_dtsec_atmos_phy_cp
time interval of physics(cumulus ) [sec]
Definition: scale_time.F90:42
real(rp), public atmos_grid_cartesc_real_totvolwxy
total volume (wxy, local) [m3]
real(rp), dimension(:,:,:), allocatable, public momx_tp
real(rp), dimension(:,:,:), allocatable, target, public momy
real(rp), dimension(:,:,:), allocatable, target, public v
real(rp), dimension(:,:,:), allocatable, target, public u
real(rp), dimension(:,:,:), allocatable, public momz_tp
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_cz
geopotential height [m] (zxy)
module profiler
Definition: scale_prof.F90:11
module Atmosphere GRID CartesC Real(real space)
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_area
horizontal area ( xy, normal z) [m2]
subroutine, public atmos_phy_cp_common_wmean(KA, KS, KE, IA, IS, IE, JA, JS, JE, W, TIME_DTSEC, CP_DTSEC, W0_mean)
ATMOS_PHY_CP_wmean running mean vertical wind velocity comment for W0 imported from WRF...
module PRECISION
integer, public ka
of whole cells: z, local, with HALO
real(rp), dimension(:,:,:), pointer, public momz_av
module Statistics
real(rp), dimension(:,:,:), pointer, public rhot_av
real(rp), dimension(:,:,:), allocatable, target, public cptot
subroutine, public atmos_phy_cp_kf_tendency(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS, U, V, RHOT, TEMP, PRES, QDRY, QV_in, Rtot, CPtot, w0avg, FZ, KF_DTSEC, DENS_t_CP, RHOT_t_CP, RHOQV_t_CP, RHOQ_t_CP, SFLX_convrain, cloudtop, cloudbase, cldfrac_dp, cldfrac_sh, nca)
ATMOS_PHY_CP_kf calculate Kain-Fritsch Cumulus Parameterization.
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase
module STDIO
Definition: scale_io.F90:10
integer, parameter, public n_hyd
real(rp), dimension(:,:,:), pointer, public momy_av
module atmosphere / physics / cloud microphysics
subroutine, public atmos_phy_cp_driver_calc_tendency(update_flag)
Driver.
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
real(rp), dimension(:,:,:), allocatable, target, public pres
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volzuy
control volume (zuy) [m3]
real(rp), dimension(:,:,:), allocatable, target, public rtot
module file_history
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc