SCALE-RM
mod_atmos_phy_ch_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  !
35 
36  !-----------------------------------------------------------------------------
37  !
38  !++ Public parameters & variables
39  !
40  !-----------------------------------------------------------------------------
41  !
42  !++ Private procedure
43  !
44  !-----------------------------------------------------------------------------
45  !
46  !++ Private parameters & variables
47  !
48  !-----------------------------------------------------------------------------
49 contains
50  !-----------------------------------------------------------------------------
53  use mod_atmos_admin, only: &
56  use scale_tracer, only: &
58  use scale_atmos_phy_ch_rn222, only: &
63  use mod_atmos_phy_ch_vars, only: &
64  qa_ch, &
65  qs_ch, &
66  qe_ch
67  use scale_prc, only: &
68  prc_abort
69  implicit none
70  !---------------------------------------------------------------------------
71 
72  log_newline
73  log_info("ATMOS_PHY_CH_driver_tracer_setup",*) 'Setup'
74 
75  if ( atmos_sw_phy_ch ) then
76 
77  select case ( atmos_phy_ch_type )
78  case ( 'OFF', 'NONE' )
79  log_info("ATMOS_PHY_CH_driver_tracer_setup",*) 'this component is never called.'
80  case ( 'RN222' )
81 
82  call tracer_regist( qs_ch, & ! [OUT]
84  atmos_phy_ch_rn222_name(:), & ! [IN]
85  atmos_phy_ch_rn222_desc(:), & ! [IN]
86  atmos_phy_ch_rn222_unit(:) ) ! [IN]
88 
89  case default
90  log_error("ATMOS_PHY_CH_driver_tracer_setup",*) 'invalid chemistry type(', atmos_phy_ch_type, '). CHECK!'
91  call prc_abort
92  end select
93 
94  qe_ch = qs_ch + qa_ch - 1
95 
96  else
97  qa_ch = 0
98  qs_ch = -1
99  qe_ch = -2
100  endif
101 
102  return
103  end subroutine atmos_phy_ch_driver_tracer_setup
104 
105  !-----------------------------------------------------------------------------
107  subroutine atmos_phy_ch_driver_setup
109  real_lon => atmos_grid_cartesc_real_lon, &
110  real_lat => atmos_grid_cartesc_real_lat
111  use scale_atmos_phy_ch_rn222, only: &
113  use scale_atmos_sfc_ch_rn222, only: &
115  use mod_atmos_admin, only: &
118  implicit none
119  !---------------------------------------------------------------------------
120 
121  log_newline
122  log_info("ATMOS_PHY_CH_driver_setup",*) 'Setup'
123 
124  if ( atmos_sw_phy_ch ) then
125 
127  call atmos_sfc_ch_rn222_setup( ia, ja, & ! [IN]
128  real_lon, real_lat ) ! [IN]
129 
130  else
131  log_info("ATMOS_PHY_CH_driver_setup",*) 'this component is never called.'
132  endif
133 
134  return
135  end subroutine atmos_phy_ch_driver_setup
136 
137  !-----------------------------------------------------------------------------
139  subroutine atmos_phy_ch_driver_calc_tendency( update_flag )
140  use scale_tracer, only: &
142  use scale_time, only: &
143  dt_ch => time_dtsec_atmos_phy_ch
144  use scale_statistics, only: &
146  statistics_total
147  use scale_atmos_grid_cartesc_real, only: &
150  use scale_file_history, only: &
151  file_history_in
152  use mod_atmos_vars, only: &
153  dens => dens_av, &
154  qtrc => qtrc_av, &
155  rhoq_t => rhoq_tp
156  use mod_atmos_phy_sf_vars, only: &
157  sflx_qtrc => atmos_phy_sf_sflx_qtrc
158  use mod_atmos_phy_ch_vars, only: &
159  rhoq_t_ch => atmos_phy_ch_rhoq_t, &
160  qa_ch, &
161  qs_ch, &
162  qe_ch
163 ! O3 => ATMOS_PHY_CH_O3
164  use mod_atmos_admin, only: &
166  use scale_atmos_phy_ch_rn222, only: &
168  implicit none
169 
170  logical, intent(in) :: update_flag
171 
172  integer :: k, i, j, iq
173  !---------------------------------------------------------------------------
174 
175  if ( update_flag ) then
176 
177 !OCL XFILL
178  rhoq_t_ch(:,:,:,:) = 0.0_rp
179 
180  select case( atmos_phy_ch_type )
181  case( 'RN222' )
182  call atmos_phy_ch_rn222_tendency( ka, ks, ke, & ! [IN]
183  ia, is, ie, & ! [IN]
184  ja, js, je, & ! [IN]
185  qa_ch, & ! [IN]
186  dens(:,:,:), & ! [IN]
187  qtrc(:,:,:,qs_ch:qe_ch), & ! [IN]
188  rhoq_t_ch(:,:,:,qs_ch:qe_ch) ) ! [INOUT]
189  end select
190 
191  do iq = qs_ch, qe_ch
192  call file_history_in( rhoq_t_ch(:,:,:,iq), trim(tracer_name(iq))//'_t_CH', &
193  'tendency rho*'//trim(tracer_name(iq))//' in CH', &
194  'kg/m3/s', fill_halo=.true. )
195  enddo
196  endif
197 
198  do iq = qs_ch, qe_ch
199  !$omp parallel do private(i,j,k) OMP_SCHEDULE_
200  do j = js, je
201  do i = is, ie
202  do k = ks, ke
203  rhoq_t(k,i,j,iq) = rhoq_t(k,i,j,iq) + rhoq_t_ch(k,i,j,iq)
204  enddo
205  enddo
206  enddo
207  enddo
208 
209  if ( statistics_checktotal ) then
210  do iq = qs_ch, qe_ch
211  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
212  rhoq_t_ch(:,:,:,iq), trim(tracer_name(iq))//'_t_CH', &
215  enddo
216  endif
217 
218  return
219  end subroutine atmos_phy_ch_driver_calc_tendency
220 
221  !-----------------------------------------------------------------------------
223  subroutine atmos_phy_ch_driver_ocean_flux( &
224  SFLX_QTRC )
226  use scale_atmos_sfc_ch_rn222, only: &
228  use mod_atmos_admin, only: &
230  use mod_atmos_phy_ch_vars, only: &
231  qa_ch, &
232  qs_ch, &
233  qe_ch
234  implicit none
235 
236  real(RP), intent(inout) :: SFLX_QTRC(oia,oja,qa)
237 
238  !---------------------------------------------------------------------------
239 
240  select case( atmos_phy_ch_type )
241  case( 'RN222' )
242  call atmos_sfc_ch_rn222_ocean_flux( oia, ois, oie, & ! [IN]
243  oja, ojs, oje, & ! [IN]
244  qa_ch, & ! [IN]
245  sflx_qtrc(:,:,qs_ch:qe_ch) ) ! [INOUT]
246  end select
247 
248  return
249  end subroutine atmos_phy_ch_driver_ocean_flux
250 
251  !-----------------------------------------------------------------------------
253  subroutine atmos_phy_ch_driver_land_flux( &
254  SFLX_QTRC )
256  use scale_time, only: &
258  use scale_atmos_sfc_ch_rn222, only: &
260  use mod_atmos_admin, only: &
262  use mod_atmos_phy_ch_vars, only: &
263  qa_ch, &
264  qs_ch, &
265  qe_ch
266  implicit none
267 
268  real(RP), intent(inout) :: SFLX_QTRC(lia,lja,qa)
269 
270  !---------------------------------------------------------------------------
271 
272  select case( atmos_phy_ch_type )
273  case( 'RN222' )
274  call atmos_sfc_ch_rn222_land_flux( lia, lis, lie, & ! [IN]
275  lja, ljs, lje, & ! [IN]
276  qa_ch, & ! [IN]
277  time_nowdate(:), & ! [IN]
278  sflx_qtrc(:,:,qs_ch:qe_ch) ) ! [INOUT]
279  end select
280 
281  return
282  end subroutine atmos_phy_ch_driver_land_flux
283 
284  !-----------------------------------------------------------------------------
286  subroutine atmos_phy_ch_driver_urban_flux( &
287  SFLX_QTRC )
289  use scale_time, only: &
291  use scale_atmos_sfc_ch_rn222, only: &
293  use mod_atmos_admin, only: &
295  use mod_atmos_phy_ch_vars, only: &
296  qa_ch, &
297  qs_ch, &
298  qe_ch
299  implicit none
300 
301  real(RP), intent(inout) :: SFLX_QTRC(uia,uja,qa)
302 
303  !---------------------------------------------------------------------------
304 
305  select case( atmos_phy_ch_type )
306  case( 'RN222' )
307  call atmos_sfc_ch_rn222_land_flux( uia, uis, uie, & ! [IN]
308  uja, ujs, uje, & ! [IN]
309  qa_ch, & ! [IN]
310  time_nowdate(:), & ! [IN]
311  sflx_qtrc(:,:,qs_ch:qe_ch) ) ! [INOUT]
312  end select
313 
314  return
315  end subroutine atmos_phy_ch_driver_urban_flux
316 
317 end module mod_atmos_phy_ch_driver
module ATMOS admin
module atmosphere / surface / chemistry / RN222
subroutine, public atmos_phy_ch_driver_urban_flux(SFLX_QTRC)
Driver.
integer, public ia
of whole cells: x, local, with HALO
real(dp), public time_dtsec_atmos_phy_ch
time interval of physics(chemistry ) [sec]
Definition: scale_time.F90:48
subroutine, public atmos_sfc_ch_rn222_setup(IA, JA, real_lon, real_lat)
Setup.
module land / grid / cartesianC / index
module ATMOSPHERIC Variables
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lat
latitude [rad,-pi,pi]
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
integer, public qa
subroutine, public atmos_phy_ch_rn222_tendency(KA, KS, KE, IA, IS, IE, JA, JS, JE, QA_CH, DENS, QTRC, RHOQ_t)
Chemistry Microphysics.
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_vol
control volume (zxy) [m3]
module ATMOSPHERE / Physics Chemistry
subroutine, public atmos_phy_ch_driver_calc_tendency(update_flag)
Driver.
real(rp), public atmos_grid_cartesc_real_totvol
total volume (zxy, local) [m3]
integer, public ja
of whole cells: y, local, with HALO
real(rp), dimension(:,:,:), allocatable, target, public dens
subroutine, public atmos_sfc_ch_rn222_ocean_flux(IA, IS, IE, JA, JS, JE, QA_CH, SFLX_QTRC)
Emission from the ocean surface.
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lon
longitude [rad,0-2pi]
character(len=h_short), dimension(qa_max), public tracer_name
subroutine, public atmos_phy_ch_driver_ocean_flux(SFLX_QTRC)
Driver.
logical, public statistics_checktotal
calc&report variable totals to logfile?
module urban / grid / icosahedralA / index
character(len=h_short), public atmos_phy_ch_type
integer, public is
start point of inner domain: x, local
subroutine, public atmos_phy_ch_driver_tracer_setup
Config.
module ATMOSPHERIC Surface Variables
subroutine, public atmos_sfc_ch_rn222_land_flux(IA, IS, IE, JA, JS, JE, QA_CH, NOWDATE, SFLX_QTRC)
Emission from the land surface.
integer, public ie
end point of inner domain: x, local
module TRACER
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 rhoq_tp
integer, public je
end point of inner domain: y, local
character(len=h_mid), dimension(qa_ch), public atmos_phy_ch_rn222_desc
module TIME
Definition: scale_time.F90:16
real(rp), dimension(:,:,:), allocatable, target, public atmos_phy_sf_sflx_qtrc
integer, public ks
start point of inner domain: z, local
subroutine, public atmos_phy_ch_rn222_setup
Setup.
logical, public atmos_sw_phy_ch
real(rp), dimension(:,:,:), pointer, public dens_av
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
module atmosphere / physics / chemistry / RN222
integer, public js
start point of inner domain: y, local
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_ch_rhoq_t
module Atmosphere / Physics Chemistry
subroutine, public atmos_phy_ch_driver_land_flux(SFLX_QTRC)
Driver.
module ocean / grid / cartesianC / index
module profiler
Definition: scale_prof.F90:11
module Atmosphere GRID CartesC Real(real space)
subroutine, public atmos_phy_ch_driver_setup
Setup.
module PRECISION
integer, public ka
of whole cells: z, local, with HALO
module Statistics
integer, dimension(6), public time_nowdate
current time [YYYY MM DD HH MM SS]
Definition: scale_time.F90:69
character(len=h_short), dimension(qa_ch), public atmos_phy_ch_rn222_unit
subroutine, public tracer_regist(QS, NQ, NAME, DESC, UNIT, CV, CP, R, ADVC, MASS)
Regist tracer.
module STDIO
Definition: scale_io.F90:10
character(len=h_short), dimension(qa_ch), public atmos_phy_ch_rn222_name
module file_history
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc