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  !
32 
33  !-----------------------------------------------------------------------------
34  !
35  !++ Public parameters & variables
36  !
37  !-----------------------------------------------------------------------------
38  !
39  !++ Private procedure
40  !
41  !-----------------------------------------------------------------------------
42  !
43  !++ Private parameters & variables
44  !
45  !-----------------------------------------------------------------------------
46 contains
47  !-----------------------------------------------------------------------------
50  use mod_atmos_admin, only: &
53  use scale_tracer, only: &
55  use scale_atmos_phy_ae_kajino13, only: &
60  use scale_prc, only: &
61  prc_abort
62  use mod_atmos_phy_ae_vars, only: &
63  qa_ae, &
64  qs_ae, &
65  qe_ae
66  implicit none
67 
68  log_newline
69  log_info("ATMOS_PHY_AE_driver_tracer_setup",*) 'Setup'
70 
71  if ( atmos_sw_phy_ae ) then
72  select case ( atmos_phy_ae_type )
73  case ( 'OFF', 'NONE' )
74  log_info("ATMOS_PHY_AE_driver_tracer_setup",*) 'this component is never called.'
75  case ( 'KAJINO13' )
77 
78  call tracer_regist( qs_ae, & ! [OUT]
79  qa_ae, & ! [IN]
80  atmos_phy_ae_kajino13_name(:), & ! [IN]
81  atmos_phy_ae_kajino13_desc(:), & ! [IN]
82  atmos_phy_ae_kajino13_unit(:) ) ! [IN]
83  case default
84  log_error("ATMOS_PHY_AE_driver_tracer_setup",*) 'invalid aerosol type(', atmos_phy_ae_type, '). CHECK!'
85  call prc_abort
86  end select
87 
88  qe_ae = qs_ae + qa_ae - 1
89 
90  else
91  qa_ae = 0
92  qs_ae = -1
93  qe_ae = -2
94  end if
95 
96  return
98 
99  !-----------------------------------------------------------------------------
101  subroutine atmos_phy_ae_driver_setup
102  use mod_atmos_admin, only: &
105  use scale_atmos_phy_ae_kajino13, only: &
107  use scale_prc, only: &
108  prc_abort
109  implicit none
110  !---------------------------------------------------------------------------
111 
112  log_newline
113  log_info("ATMOS_PHY_AE_driver_setup",*) 'Setup'
114 
115  if ( atmos_sw_phy_ae ) then
116 
117  select case ( atmos_phy_ae_type )
118  case ( 'KAJINO13' )
120  case default
121  log_error("ATMOS_PHY_AE_driver_setup",*) 'invalid aerosol type(', atmos_phy_ae_type, '). CHECK!'
122  call prc_abort
123  end select
124 
125  endif
126 
127  return
128  end subroutine atmos_phy_ae_driver_setup
129 
130  !-----------------------------------------------------------------------------
133  use mod_atmos_vars, only: &
134  qtrc
135  use mod_atmos_phy_ae_vars, only: &
136  qa_ae, &
137  qs_ae, &
138  qe_ae
139  use mod_atmos_admin, only: &
142  use scale_atmos_phy_ae_kajino13, only: &
144  implicit none
145 
146  if ( atmos_sw_phy_ae ) then
147  select case ( atmos_phy_ae_type )
148  case ( 'KAJINO13' )
150  qtrc(:,:,:,qs_ae:qe_ae) ) ! [INOUT]
151 
152  end select
153 
154  end if
155 
156  return
157  end subroutine atmos_phy_ae_driver_adjustment
158 
159  !-----------------------------------------------------------------------------
161  subroutine atmos_phy_ae_driver_calc_tendency( update_flag )
162  use scale_tracer, only: &
164  use scale_prc, only: &
165  prc_abort
166  use scale_time, only: &
167  dt_ae => time_dtsec_atmos_phy_ae
168  use scale_statistics, only: &
170  statistics_total
171  use scale_atmos_grid_cartesc_real, only: &
174  use scale_file_history, only: &
175  file_history_in
176  use mod_atmos_vars, only: &
177  dens => dens_av, &
178  qtrc => qtrc_av, &
179  qdry, &
180  pres, &
181  temp, &
182  qv, &
183  rhoq_t => rhoq_tp
184  use mod_atmos_phy_ae_vars, only: &
185  qa_ae, &
186  qs_ae, &
187  qe_ae, &
188  rhoq_t_ae => atmos_phy_ae_rhoq_t, &
189  ccn => atmos_phy_ae_ccn, &
190  ccn_t => atmos_phy_ae_ccn_t, &
191  ae_emit => atmos_phy_ae_emit
192  use mod_atmos_phy_mp_vars, only: &
193  evaporate => atmos_phy_mp_evaporate
194  use mod_atmos_admin, only: &
196  use scale_atmos_phy_ae_kajino13, only: &
198  implicit none
199 
200  logical, intent(in) :: update_flag
201 
202  real(RP) :: CN(ka,ia,ja)
203  real(RP) :: NREG(ka,ia,ja)
204 
205  integer :: k, i, j, iq
206  !---------------------------------------------------------------------------
207 
208  if ( update_flag ) then
209 
210 !OCL XFILL
211  ccn(:,:,:) = 0.0_rp ! reset
212 !OCL XFILL
213  rhoq_t_ae(:,:,:,:) = 0.0_rp ! reset
214 
215  do j = js, je
216  do i = is, ie
217  do k = ks, ke
218  nreg(k,i,j) = evaporate(k,i,j) * dt_ae
219  enddo
220  enddo
221  enddo
222 
223  select case ( atmos_phy_ae_type )
224  case ( 'KAJINO13' )
226  temp(:,:,:), & ! [IN]
227  pres(:,:,:), & ! [IN]
228  qdry(:,:,:), & ! [IN]
229  nreg(:,:,:), & ! [IN]
230  dens(:,:,:), & ! [IN]
231  qv(:,:,:), & ! [IN]
232  qtrc(:,:,:,qs_ae:qe_ae), & ! [IN]
233  ae_emit(:,:,:,qs_ae:qe_ae), & ! [IN]
234  dt_ae, & ! [IN]
235  rhoq_t_ae(:,:,:,qs_ae:qe_ae), & ! [OUT]
236  cn(:,:,:), & ! [OUT]
237  ccn(:,:,:) ) ! [OUT]
238  end select
239 
240  ccn_t(:,:,:) = ccn(:,:,:) / dt_ae
241 
242  call file_history_in( cn(:,:,:)*1.e-6_rp, 'CN', 'condensation nucrei', 'num/cc' )
243  call file_history_in( ccn(:,:,:)*1.e-6_rp, 'CCN', 'cloud condensation nucrei', 'num/cc' )
244 
245  endif
246 
247  do iq = qs_ae, qe_ae
248  !$omp parallel do private(i,j,k) OMP_SCHEDULE_
249  do j = js, je
250  do i = is, ie
251  do k = ks, ke
252  rhoq_t(k,i,j,iq) = rhoq_t(k,i,j,iq) + rhoq_t_ae(k,i,j,iq)
253  enddo
254  enddo
255  enddo
256  enddo
257 
258  if ( statistics_checktotal ) then
259  do iq = qs_ae, qe_ae
260  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
261  rhoq_t_ae(:,:,:,iq), trim(tracer_name(iq))//'_t_AE', &
264  enddo
265  endif
266 
267  return
268  end subroutine atmos_phy_ae_driver_calc_tendency
269 
270 end module mod_atmos_phy_ae_driver
module ATMOS admin
subroutine, public atmos_phy_ae_driver_calc_tendency(update_flag)
Driver.
subroutine, public atmos_phy_ae_driver_setup
Setup.
real(rp), dimension(:,:,:), allocatable, target, public qdry
integer, public ia
of whole cells: x, local, with HALO
module Atmosphere / Physics Cloud Microphysics
character(len=h_short), dimension(:), allocatable, public atmos_phy_ae_kajino13_name
module ATMOSPHERIC Variables
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
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.
subroutine, public atmos_phy_ae_kajino13_tracer_setup(QA_AE)
Tracer setup.
character(len=h_mid), dimension(:), allocatable, public atmos_phy_ae_kajino13_desc
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_vol
control volume (zxy) [m3]
real(rp), public atmos_grid_cartesc_real_totvol
total volume (zxy, local) [m3]
logical, public atmos_sw_phy_ae
integer, public ja
of whole cells: y, local, with HALO
character(len=h_short), public atmos_phy_ae_type
real(rp), dimension(:,:,:), allocatable, target, public dens
module ATMOSPHERE / Physics Aerosol Microphysics
character(len=h_short), dimension(qa_max), public tracer_name
logical, public statistics_checktotal
calc&report variable totals to logfile?
character(len=h_short), dimension(:), allocatable, public atmos_phy_ae_kajino13_unit
integer, public is
start point of inner domain: x, local
integer, public ie
end point of inner domain: x, local
module TRACER
subroutine, public atmos_phy_ae_driver_adjustment
adjustment
module atmosphere / grid / cartesC index
integer, public ke
end point of inner domain: z, local
module PROCESS
Definition: scale_prc.F90:11
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_ae_emit
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
integer, public je
end point of inner domain: y, local
subroutine, public atmos_phy_ae_driver_tracer_setup
Setup.
real(rp), dimension(:,:,:), allocatable, target, public temp
subroutine, public atmos_phy_ae_kajino13_setup
Setup.
module TIME
Definition: scale_time.F90:16
integer, public ks
start point of inner domain: z, local
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_ae_rhoq_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_ae_ccn
real(rp), dimension(:,:,:), pointer, public dens_av
real(dp), public time_dtsec_atmos_phy_ae
time interval of physics(aerosol ) [sec]
Definition: scale_time.F90:49
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
real(rp), dimension(:,:,:), allocatable, pointer, target, public qv
subroutine, public atmos_phy_ae_kajino13_negative_fixer(KA, KS, KE, IA, IS, IE, JA, JS, JE, QA_AE, QTRC)
integer, public js
start point of inner domain: y, local
real(rp), dimension(:,:,:), allocatable, public atmos_phy_mp_evaporate
module profiler
Definition: scale_prof.F90:11
module Atmosphere GRID CartesC Real(real space)
module PRECISION
module atmosphere / physics / aerosol / Kajino13
integer, public ka
of whole cells: z, local, with HALO
module Statistics
subroutine, public tracer_regist(QS, NQ, NAME, DESC, UNIT, CV, CP, R, ADVC, MASS)
Regist tracer.
module STDIO
Definition: scale_io.F90:10
module ATMOSPHERE / Physics Aerosol Microphysics
real(rp), dimension(:,:,:), allocatable, target, public pres
module file_history
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
real(rp), dimension(:,:,:), allocatable, public atmos_phy_ae_ccn_t