SCALE-RM
mod_atmos_phy_ae_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  !-----------------------------------------------------------------------------
22  implicit none
23  private
24  !-----------------------------------------------------------------------------
25  !
26  !++ Public procedure
27  !
33 
34  !-----------------------------------------------------------------------------
35  !
36  !++ Public parameters & variables
37  !
38  !-----------------------------------------------------------------------------
39  !
40  !++ Private procedure
41  !
42  !-----------------------------------------------------------------------------
43  !
44  !++ Private parameters & variables
45  !
46  !-----------------------------------------------------------------------------
47 contains
48  !-----------------------------------------------------------------------------
51  use mod_atmos_admin, only: &
54  use scale_tracer, only: &
56  use scale_atmos_phy_ae_kajino13, only: &
61  use scale_prc, only: &
62  prc_abort
63  use mod_atmos_phy_ae_vars, only: &
64  qa_ae, &
65  qs_ae, &
66  qe_ae
67  implicit none
68 
69  log_newline
70  log_info("ATMOS_PHY_AE_driver_tracer_setup",*) 'Setup'
71 
72  if ( atmos_sw_phy_ae ) then
73  select case ( atmos_phy_ae_type )
74  case ( 'OFF', 'NONE' )
75  log_info("ATMOS_PHY_AE_driver_tracer_setup",*) 'this component is never called.'
76  case ( 'KAJINO13' )
78 
79  call tracer_regist( qs_ae, & ! [OUT]
80  qa_ae, & ! [IN]
81  atmos_phy_ae_kajino13_name(:), & ! [IN]
82  atmos_phy_ae_kajino13_desc(:), & ! [IN]
83  atmos_phy_ae_kajino13_unit(:) ) ! [IN]
84  case ( 'OFFLINE' )
85  log_info("ATMOS_PHY_AE_driver_tracer_setup",*) 'offline aerosol module has no tracers'
86  case default
87  log_error("ATMOS_PHY_AE_driver_tracer_setup",*) 'invalid aerosol type(', atmos_phy_ae_type, '). CHECK!'
88  call prc_abort
89  end select
90 
91  qe_ae = qs_ae + qa_ae - 1
92 
93  else
94  qa_ae = 0
95  qs_ae = -1
96  qe_ae = -2
97  end if
98 
99  return
100  end subroutine atmos_phy_ae_driver_tracer_setup
101 
102  !-----------------------------------------------------------------------------
104  subroutine atmos_phy_ae_driver_setup
105  use mod_atmos_admin, only: &
108  use scale_atmos_phy_ae_kajino13, only: &
110  use scale_atmos_phy_ae_offline, only: &
112  use scale_prc, only: &
113  prc_abort
114  implicit none
115  !---------------------------------------------------------------------------
116 
117  log_newline
118  log_info("ATMOS_PHY_AE_driver_setup",*) 'Setup'
119 
120  if ( atmos_sw_phy_ae ) then
121 
122  select case ( atmos_phy_ae_type )
123  case ( 'KAJINO13' )
125  case ( 'OFFLINE' )
127  case default
128  log_error("ATMOS_PHY_AE_driver_setup",*) 'invalid aerosol type(', atmos_phy_ae_type, '). CHECK!'
129  call prc_abort
130  end select
131 
132  endif
133 
134  return
135  end subroutine atmos_phy_ae_driver_setup
136 
137  !-----------------------------------------------------------------------------
142  use mod_atmos_admin, only: &
145  implicit none
146  !---------------------------------------------------------------------------
147 
148  log_newline
149  log_info("ATMOS_PHY_AE_driver_finalize",*) 'Finalize'
150 
151  if ( atmos_sw_phy_ae ) then
152  select case ( atmos_phy_ae_type )
153  case ( 'KAJINO13' )
155  case ( 'OFFLINE' )
156  end select
157  endif
158 
159  return
160  end subroutine atmos_phy_ae_driver_finalize
161 
162  !-----------------------------------------------------------------------------
165  use mod_atmos_vars, only: &
166  qtrc
167  use mod_atmos_phy_ae_vars, only: &
168  qa_ae, &
169  qs_ae, &
170  qe_ae
171  use mod_atmos_admin, only: &
174  use scale_atmos_phy_ae_kajino13, only: &
176  implicit none
177 
178  if ( atmos_sw_phy_ae ) then
179 
180  select case ( atmos_phy_ae_type )
181  case ( 'KAJINO13' )
183  qtrc(:,:,:,qs_ae:qe_ae) ) ! [INOUT]
184  end select
185 
186  end if
187 
188  return
189  end subroutine atmos_phy_ae_driver_adjustment
190 
191  !-----------------------------------------------------------------------------
193  subroutine atmos_phy_ae_driver_calc_tendency( update_flag )
194  use scale_tracer, only: &
196  use scale_prc, only: &
197  prc_abort
198  use scale_time, only: &
199  dt_ae => time_dtsec_atmos_phy_ae, &
201  use scale_statistics, only: &
203  statistics_total
204  use scale_atmos_grid_cartesc_real, only: &
207  use scale_file_history, only: &
208  file_history_in
209  use mod_atmos_vars, only: &
210  dens => dens_av, &
211  qtrc => qtrc_av, &
212  qdry, &
213  pres, &
214  temp, &
215  qv, &
216  rhoq_t => rhoq_tp
217  use mod_atmos_phy_ae_vars, only: &
218  qa_ae, &
219  qs_ae, &
220  qe_ae, &
221  rhoq_t_ae => atmos_phy_ae_rhoq_t, &
222  ccn => atmos_phy_ae_ccn, &
223  ccn_t => atmos_phy_ae_ccn_t, &
224  ae_emit => atmos_phy_ae_emit
225  use mod_atmos_phy_mp_vars, only: &
226  evaporate => atmos_phy_mp_evaporate
227  use mod_atmos_admin, only: &
229  use scale_atmos_phy_ae_kajino13, only: &
231  use scale_atmos_phy_ae_offline, only: &
233  implicit none
234 
235  logical, intent(in) :: update_flag
236 
237  real(rp) :: cn(ka,ia,ja)
238  real(rp) :: nreg(ka,ia,ja)
239 
240  integer :: k, i, j, iq
241  !---------------------------------------------------------------------------
242 
243  if ( update_flag ) then
244 
245 !OCL XFILL
246  ccn(:,:,:) = 0.0_rp ! reset
247 !OCL XFILL
248  rhoq_t_ae(:,:,:,:) = 0.0_rp ! reset
249 
250  do j = js, je
251  do i = is, ie
252  do k = ks, ke
253  nreg(k,i,j) = evaporate(k,i,j) * dt_ae
254  enddo
255  enddo
256  enddo
257 
258  select case ( atmos_phy_ae_type )
259  case ( 'KAJINO13' )
261  temp(:,:,:), & ! [IN]
262  pres(:,:,:), & ! [IN]
263  qdry(:,:,:), & ! [IN]
264  nreg(:,:,:), & ! [IN]
265  dens(:,:,:), & ! [IN]
266  qv(:,:,:), & ! [IN]
267  qtrc(:,:,:,qs_ae:qe_ae), & ! [IN]
268  ae_emit(:,:,:,qs_ae:qe_ae), & ! [IN]
269  dt_ae, & ! [IN]
270  rhoq_t_ae(:,:,:,qs_ae:qe_ae), & ! [OUT]
271  cn(:,:,:), & ! [OUT]
272  ccn(:,:,:) ) ! [OUT]
273  case ( 'OFFLINE' )
274  call atmos_phy_ae_offline_tendency ( ka, ks, ke, ia, is, ie, ja, js, je, &
275  time_nowdaysec, & ! [IN]
276  ccn(:,:,:) ) ! [OUT]
277  cn(:,:,:) = 0.0_rp ! not supported
278  end select
279 
280  ccn_t(:,:,:) = ccn(:,:,:) / dt_ae
281 
282  call file_history_in( cn(:,:,:)*1.e-6_rp, 'CN', 'condensation nucrei', 'num/cc' )
283  call file_history_in( ccn(:,:,:)*1.e-6_rp, 'CCN', 'cloud condensation nucrei', 'num/cc' )
284 
285  endif
286 
287  do iq = qs_ae, qe_ae
288  !$omp parallel do private(i,j,k) OMP_SCHEDULE_
289  do j = js, je
290  do i = is, ie
291  do k = ks, ke
292  rhoq_t(k,i,j,iq) = rhoq_t(k,i,j,iq) + rhoq_t_ae(k,i,j,iq)
293  enddo
294  enddo
295  enddo
296  enddo
297 
298  if ( statistics_checktotal ) then
299  do iq = qs_ae, qe_ae
300  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
301  rhoq_t_ae(:,:,:,iq), trim(tracer_name(iq))//'_t_AE', &
304  enddo
305  endif
306 
307  return
308  end subroutine atmos_phy_ae_driver_calc_tendency
309 
310 end module mod_atmos_phy_ae_driver
scale_atmos_phy_ae_kajino13
module atmosphere / physics / aerosol / Kajino13
Definition: scale_atmos_phy_ae_kajino13.F90:12
scale_statistics
module Statistics
Definition: scale_statistics.F90:11
mod_atmos_phy_mp_vars
module Atmosphere / Physics Cloud Microphysics
Definition: mod_atmos_phy_mp_vars.F90:12
scale_atmos_grid_cartesc_index::ke
integer, public ke
end point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:52
scale_time::time_nowdaysec
real(dp), public time_nowdaysec
second of current time [sec]
Definition: scale_time.F90:72
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
mod_atmos_vars::rhoq_tp
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
Definition: mod_atmos_vars.F90:121
mod_atmos_vars::qtrc_av
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
Definition: mod_atmos_vars.F90:95
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_admin
module ATMOS admin
Definition: mod_atmos_admin.F90:11
mod_atmos_vars::qdry
real(rp), dimension(:,:,:), allocatable, target, public qdry
Definition: mod_atmos_vars.F90:140
mod_atmos_phy_ae_driver::atmos_phy_ae_driver_setup
subroutine, public atmos_phy_ae_driver_setup
Setup.
Definition: mod_atmos_phy_ae_driver.F90:105
scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13_name
character(len=h_short), dimension(:), allocatable, public atmos_phy_ae_kajino13_name
Definition: scale_atmos_phy_ae_kajino13.F90:52
scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13_tracer_setup
subroutine, public atmos_phy_ae_kajino13_tracer_setup(QA_AE)
Tracer setup.
Definition: scale_atmos_phy_ae_kajino13.F90:184
mod_atmos_phy_ae_driver::atmos_phy_ae_driver_finalize
subroutine, public atmos_phy_ae_driver_finalize
finalize
Definition: mod_atmos_phy_ae_driver.F90:140
scale_atmos_grid_cartesc_real
module Atmosphere GRID CartesC Real(real space)
Definition: scale_atmos_grid_cartesC_real.F90:11
mod_atmos_vars::qtrc
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Definition: mod_atmos_vars.F90:81
scale_file_history
module file_history
Definition: scale_file_history.F90:15
scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13_tendency
subroutine, public atmos_phy_ae_kajino13_tendency(KA, KS, KE, IA, IS, IE, JA, JS, JE, QA_AE, TEMP, PRES, QDRY, NREG, DENS, QV, QTRC, EMIT, dt, RHOQ_t_AE, CN, CCN)
Aerosol Microphysics.
Definition: scale_atmos_phy_ae_kajino13.F90:670
mod_atmos_phy_ae_driver::atmos_phy_ae_driver_adjustment
subroutine, public atmos_phy_ae_driver_adjustment
adjustment
Definition: mod_atmos_phy_ae_driver.F90:165
scale_prc
module PROCESS
Definition: scale_prc.F90:11
mod_atmos_admin::atmos_sw_phy_ae
logical, public atmos_sw_phy_ae
Definition: mod_atmos_admin.F90:53
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
scale_io
module STDIO
Definition: scale_io.F90:10
scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13_setup
subroutine, public atmos_phy_ae_kajino13_setup
Setup.
Definition: scale_atmos_phy_ae_kajino13.F90:358
scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13_desc
character(len=h_mid), dimension(:), allocatable, public atmos_phy_ae_kajino13_desc
Definition: scale_atmos_phy_ae_kajino13.F90:53
mod_atmos_vars::dens
real(rp), dimension(:,:,:), allocatable, target, public dens
Definition: mod_atmos_vars.F90:76
scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13_finalize
subroutine, public atmos_phy_ae_kajino13_finalize
finalize
Definition: scale_atmos_phy_ae_kajino13.F90:604
scale_atmos_grid_cartesc_index
module atmosphere / grid / cartesC index
Definition: scale_atmos_grid_cartesC_index.F90:12
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_ae_vars::atmos_phy_ae_emit
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_ae_emit
Definition: mod_atmos_phy_ae_vars.F90:65
mod_atmos_phy_ae_vars::qa_ae
integer, public qa_ae
Definition: mod_atmos_phy_ae_vars.F90:67
scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13_unit
character(len=h_short), dimension(:), allocatable, public atmos_phy_ae_kajino13_unit
Definition: scale_atmos_phy_ae_kajino13.F90:54
scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13_negative_fixer
subroutine, public atmos_phy_ae_kajino13_negative_fixer(KA, KS, KE, IA, IS, IE, JA, JS, JE, QA_AE, QTRC)
Definition: scale_atmos_phy_ae_kajino13.F90:1194
scale_tracer::tracer_name
character(len=h_short), dimension(qa_max), public tracer_name
Definition: scale_tracer.F90:39
scale_prof
module profiler
Definition: scale_prof.F90:11
scale_atmos_phy_ae_offline::atmos_phy_ae_offline_setup
subroutine, public atmos_phy_ae_offline_setup
Setup.
Definition: scale_atmos_phy_ae_offline.F90:67
scale_atmos_phy_ae_offline::atmos_phy_ae_offline_tendency
subroutine, public atmos_phy_ae_offline_tendency(KA, KS, KE, IA, IS, IE, JA, JS, JE, time_now, CCN)
Aerosol Microphysics.
Definition: scale_atmos_phy_ae_offline.F90:194
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_phy_ae_offline
module atmosphere / physics / aerosol / offline
Definition: scale_atmos_phy_ae_offline.F90:12
mod_atmos_vars::temp
real(rp), dimension(:,:,:), allocatable, target, public temp
Definition: mod_atmos_vars.F90:134
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_vars::qv
real(rp), dimension(:,:,:), allocatable, pointer, target, public qv
Definition: mod_atmos_vars.F90:97
mod_atmos_admin::atmos_phy_ae_type
character(len=h_short), public atmos_phy_ae_type
Definition: mod_atmos_admin.F90:37
scale_time::time_dtsec_atmos_phy_ae
real(dp), public time_dtsec_atmos_phy_ae
time interval of physics(aerosol ) [sec]
Definition: scale_time.F90:44
scale_tracer::tracer_regist
subroutine, public tracer_regist(QS, NQ, NAME, DESC, UNIT, CV, CP, R, ENGI0, ADVC, MASS)
Regist tracer.
Definition: scale_tracer.F90:68
scale_tracer
module TRACER
Definition: scale_tracer.F90:12
mod_atmos_phy_mp_vars::atmos_phy_mp_evaporate
real(rp), dimension(:,:,:), allocatable, public atmos_phy_mp_evaporate
Definition: mod_atmos_phy_mp_vars.F90:73
mod_atmos_phy_ae_vars::atmos_phy_ae_ccn
real(rp), dimension(:,:,:), allocatable, public atmos_phy_ae_ccn
Definition: mod_atmos_phy_ae_vars.F90:63
mod_atmos_phy_ae_driver::atmos_phy_ae_driver_tracer_setup
subroutine, public atmos_phy_ae_driver_tracer_setup
Setup.
Definition: mod_atmos_phy_ae_driver.F90:51
mod_atmos_vars::pres
real(rp), dimension(:,:,:), allocatable, target, public pres
Definition: mod_atmos_vars.F90:135
mod_atmos_vars::dens_av
real(rp), dimension(:,:,:), pointer, public dens_av
Definition: mod_atmos_vars.F90:90
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_statistics::statistics_checktotal
logical, public statistics_checktotal
calc&report variable totals to logfile?
Definition: scale_statistics.F90:109
mod_atmos_phy_ae_vars::atmos_phy_ae_rhoq_t
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_ae_rhoq_t
Definition: mod_atmos_phy_ae_vars.F90:61
mod_atmos_vars
module ATMOSPHERIC Variables
Definition: mod_atmos_vars.F90:12
mod_atmos_phy_ae_driver
module ATMOSPHERE / Physics Aerosol Microphysics
Definition: mod_atmos_phy_ae_driver.F90:12
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_ae_vars::qs_ae
integer, public qs_ae
Definition: mod_atmos_phy_ae_vars.F90:68
mod_atmos_phy_ae_vars
module ATMOSPHERE / Physics Aerosol Microphysics
Definition: mod_atmos_phy_ae_vars.F90:12
mod_atmos_phy_ae_vars::atmos_phy_ae_ccn_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_ae_ccn_t
Definition: mod_atmos_phy_ae_vars.F90:64
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_atmos_grid_cartesc_index::je
integer, public je
end point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:56
mod_atmos_phy_ae_vars::qe_ae
integer, public qe_ae
Definition: mod_atmos_phy_ae_vars.F90:69
mod_atmos_phy_ae_driver::atmos_phy_ae_driver_calc_tendency
subroutine, public atmos_phy_ae_driver_calc_tendency(update_flag)
Driver.
Definition: mod_atmos_phy_ae_driver.F90:194