SCALE-RM
mod_atmos_phy_lt_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  !
32 
33  !-----------------------------------------------------------------------------
34  !
35  !++ Public parameters & variables
36  !
37  !-----------------------------------------------------------------------------
38  !
39  !++ Private procedure
40  !
41  !-----------------------------------------------------------------------------
42  !
43  !++ Private parameters & variables
44  !
45 
46  !--- For history output
47  integer, private, parameter :: w_nmax = 3
48  integer, private, parameter :: I_CRGD_LIQ = 1
49  integer, private, parameter :: I_CRGD_ICE = 2
50  integer, private, parameter :: I_CRGD_TOT = 3
51  integer, private :: HIST_id(w_nmax)
52  character(len=H_SHORT), private :: w_name(w_nmax)
53  character(len=H_MID), private :: w_longname(w_nmax)
54  character(len=H_SHORT), private :: w_unit(w_nmax)
55  data w_name / 'CRGD_LIQ', &
56  'CRGD_ICE', &
57  'CRGD_TOT' /
58  data w_longname / 'Charge density of liquid water', &
59  'Charge density of ice water', &
60  'Charge density of QHYD' /
61  data w_unit / 'nC/m3', &
62  'nC/m3', &
63  'nC/m3' /
64 
65 
66  !-----------------------------------------------------------------------------
67 contains
68  !-----------------------------------------------------------------------------
71  use mod_atmos_admin, only: &
75  use scale_tracer, only: &
77  use scale_atmos_phy_mp_suzuki10, only: &
81  use mod_atmos_phy_lt_vars, only: &
82  qa_lt, &
83  qs_lt, &
84  qe_lt
85  use scale_atmos_hydrometeor, only: &
86  qha, &
87  qhs
88  use scale_prc, only: &
89  prc_abort
90  implicit none
91 
92  character(len=H_SHORT), allocatable :: name(:)
93  character(len=H_MID ), allocatable :: desc(:)
94  character(len=H_SHORT), allocatable :: unit(:)
95  integer :: iq
96  !---------------------------------------------------------------------------
97 
98  log_newline
99  log_info("ATMOS_PHY_LT_driver_tracer_setup",*) 'Setup'
100 
101  if ( atmos_sw_phy_lt ) then
102 
103  select case ( atmos_phy_lt_type )
104  case ( 'OFF', 'NONE' )
105  log_info("ATMOS_PHY_LT_driver_tracer_setup",*) 'this component is never called.'
106  case ( 'SATO2019' )
107  select case ( atmos_phy_mp_type )
108  case ( 'TOMITA08', 'SN14' )
109  ! do nothing
110  case ( 'SUZUKI10' )
111 
112  if( atmos_phy_mp_suzuki10_nccn /= 0 ) then
113  log_error("ATMOS_PHY_LT_driver_tracer_setup",*) 'nccn in SUZUKI10 should be 0 for lithgning component(', atmos_phy_mp_suzuki10_nccn, '). CHECK!'
114  call prc_abort
115  endif
116  if ( atmos_phy_mp_suzuki10_nices == 0 ) then
117  log_error("ATMOS_PHY_LT_driver_tracer_setup",*) 'ICEFLG in SUZUKI10 should be 1 for lithgning component. CHECK!'
118  call prc_abort
119  endif
120  case ( 'KESSLER' )
121  log_error("ATMOS_PHY_LT_driver_tracer_setup",*) 'ATMOS_PHY_MP_TYPE should be TOMITA08, or SN14, or SUZUKI10 (', atmos_phy_mp_type, '). CHECK!'
122  call prc_abort
123  end select
124  case default
125  log_error("ATMOS_PHY_LT_driver_tracer_setup",*) 'invalid lithgning type(', atmos_phy_lt_type, '). CHECK!'
126  call prc_abort
127  end select
128 
129  qa_lt = qha
130 
131  allocate( name(qa_lt), desc(qa_lt), unit(qa_lt) )
132  do iq = 1, qa_lt
133  name(iq) = 'QCRG_'//trim(tracer_name(qhs+iq-1)(2:))
134  desc(iq) = 'Ratio of charge density of '//trim(tracer_name(qhs+iq-1))
135  unit(iq) = 'fC/kg'
136  end do
137  call tracer_regist( qs_lt, & ! [OUT]
138  qa_lt, & ! [IN]
139  name(:), & ! [IN]
140  desc(:), & ! [IN]
141  unit(:) ) ! [IN]
142  deallocate( name, desc, unit )
143 
144  qe_lt = qs_lt - 1 + qa_lt
145 
146  else
147  qa_lt = 0
148  qs_lt = -1
149  qe_lt = -2
150  endif
151 
152  return
153  end subroutine atmos_phy_lt_driver_tracer_setup
154 
155  !-----------------------------------------------------------------------------
157  subroutine atmos_phy_lt_driver_setup
159  real_lon => atmos_grid_cartesc_real_lon, &
160  real_lat => atmos_grid_cartesc_real_lat
161  use scale_atmos_grid_cartesc, only: &
162  cdx => atmos_grid_cartesc_cdx, &
164  use scale_atmos_phy_lt_sato2019, only: &
166  use mod_atmos_phy_lt_vars, only: &
167  flg_lt, &
169  use mod_atmos_admin, only: &
172  use scale_prc, only: &
173  prc_abort
174  use scale_atmos_hydrometeor, only: &
175  qha
176  use scale_file_history, only: &
178  implicit none
179 
180  logical :: lt_force_with_suzuki10 = .false. ! experimental use only
181 
182  namelist / param_atmos_phy_lt / &
183  lt_force_with_suzuki10
184 
185  integer :: ip
186  integer :: ierr
187  !---------------------------------------------------------------------------
188 
189  log_newline
190  log_info("ATMOS_PHY_LT_driver_setup",*) 'Setup'
191 
192  !--- read namelist
193  rewind(io_fid_conf)
194  read(io_fid_conf,nml=param_atmos_phy_lt,iostat=ierr)
195  if ( ierr < 0 ) then !--- missing
196  log_info("ATMOS_PHY_LT_driver_setup",*) 'Not found namelist. Default used.'
197  elseif ( ierr > 0 ) then !--- fatal error
198  log_error("ATMOS_PHY_LT_dirver_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_PHY_LT. Check!'
199  call prc_abort
200  end if
201  log_nml(param_atmos_phy_lt)
202 
203  select case( atmos_phy_lt_type )
204  case ( 'SATO2019' )
205 
206  if ( atmos_phy_mp_type == "SUZUKI10" ) then
207  log_warn("ATMOS_PHY_LT_driver_setup",*) 'At this moment, ATMOS_PHY_MP_TYPE of SUZUKI10 with SATO2019 scheme is for experimental use only.'
208  if ( .not. lt_force_with_suzuki10 ) then
209  log_error("ATMOS_PHY_LT_driver_setup",*) 'At this moment, ATMOS_PHY_MP_TYPE of SUZUKI10 with SATO2019 scheme is for experimental use only.'
210  call prc_abort
211  end if
212  end if
213 
214 
215  call atmos_phy_lt_sato2019_setup( ka, ks, ke, & ! [IN]
216  ia, is, ie, & ! [IN]
217  ja, js, je, & ! [IN]
218  imaxg, & ! [IN]
219  jmaxg, & ! [IN]
220  kmax, & ! [IN]
221  atmos_phy_mp_type, & ! [IN]
222  cdx, cdy ) ! [IN]
223  flg_lt = .true.
224  case default
225  flg_lt = .false.
226  end select
227 
228 
229  if ( flg_lt ) then
230 
231  allocate( atmos_phy_lt_sarea(ka,ia,ja,qha) )
232 
233  do ip = 1, w_nmax
234  call file_history_reg( w_name(ip), w_longname(ip), w_unit(ip), & ! [IN]
235  hist_id(ip) ) ! [OUT]
236  end do
237 
238  call history
239 
240  else
241  log_info("ATMOS_PHY_LT_driver_setup",*) 'This component is never called.'
242  endif
243 
244 
245  return
246  end subroutine atmos_phy_lt_driver_setup
247 
248  !-----------------------------------------------------------------------------
251  use scale_time, only: &
252  dt_lt => time_dtsec_atmos_phy_lt
253  use mod_atmos_vars, only: &
254  dens => dens_av, &
255  rhot => rhot_av, &
256  qtrc => qtrc_av, &
257  atmos_vars_get_diagnostic
258  use mod_atmos_phy_lt_vars, only: &
259  qa_lt, &
260  qs_lt, &
261  qe_lt, &
262  sarea => atmos_phy_lt_sarea, &
263  epot => atmos_phy_lt_epot
264  use scale_atmos_phy_lt_sato2019, only: &
266  implicit none
267 
268  real(rp) :: qhyd(ka,ia,ja)
269  !---------------------------------------------------------------------------
270 
271  call atmos_vars_get_diagnostic( "QHYD", qhyd(:,:,:) )
272 
274  ka, ks, ke, ia, is, ie, ja, js, je, kijmax, imax, jmax, qa_lt, & ! [IN]
275  dens(:,:,:), rhot(:,:,:), qhyd(:,:,:), sarea(:,:,:,:), & ! [IN]
276  dt_lt, & ! [IN]
277  qtrc(:,:,:,qs_lt:qe_lt), epot(:,:,:) ) ! [INOUT]
278 
279  call history
280 
281  return
282  end subroutine atmos_phy_lt_driver_adjustment
283 
284  ! private
285  subroutine history
287  qla
288  use mod_atmos_phy_lt_vars, only: &
289  qs_lt, &
290  qe_lt
291  use mod_atmos_vars, only: &
292  dens => dens_av, &
293  qtrc => qtrc_av
294  use scale_file_history, only: &
295  file_history_query, &
296  file_history_put
297  implicit none
298  real(RP) :: work(KA,IA,JA)
299  logical :: HIST_sw(w_nmax)
300  integer :: k, i, j, n, ip
301 
302  do ip = 1, w_nmax
303  call file_history_query( hist_id(ip), hist_sw(ip) )
304  end do
305 
306  if ( hist_sw(i_crgd_liq) ) then
307  !$omp parallel do
308  do j = js, je
309  do i = is, ie
310  do k = ks, ke
311  work(k,i,j) = 0.0_rp
312  do n = qs_lt, qs_lt + qla - 1
313  work(k,i,j) = work(k,i,j) + qtrc(k,i,j,n)
314  enddo
315  work(k,i,j) = work(k,i,j) * dens(k,i,j) * 1.e-6_rp ! [fC/kg] -> [nc/m3]
316  end do
317  end do
318  end do
319  call file_history_put( hist_id(i_crgd_liq), work(:,:,:) )
320  end if
321  if ( hist_sw(i_crgd_ice) ) then
322  !$omp parallel do
323  do j = js, je
324  do i = is, ie
325  do k = ks, ke
326  work(k,i,j) = 0.0_rp
327  do n = qs_lt + qla, qe_lt
328  work(k,i,j) = work(k,i,j) + qtrc(k,i,j,n)
329  enddo
330  work(k,i,j) = work(k,i,j) * dens(k,i,j) * 1.e-6_rp ! [fC/kg] -> [nc/m3]
331  end do
332  end do
333  end do
334  call file_history_put( hist_id(i_crgd_ice), work(:,:,:) )
335  end if
336  if ( hist_sw(i_crgd_tot) ) then
337  !$omp parallel do
338  do j = js, je
339  do i = is, ie
340  do k = ks, ke
341  work(k,i,j) = 0.0_rp
342  do n = qs_lt, qe_lt
343  work(k,i,j) = work(k,i,j) + qtrc(k,i,j,n)
344  enddo
345  work(k,i,j) = work(k,i,j) * dens(k,i,j) * 1.e-6_rp ! [fC/kg] -> [nc/m3]
346  end do
347  end do
348  end do
349  call file_history_put( hist_id(i_crgd_tot), work(:,:,:) )
350  end if
351 
352  return
353  end subroutine history
354 
355 end module mod_atmos_phy_lt_driver
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_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
scale_atmos_phy_lt_sato2019::atmos_phy_lt_sato2019_setup
subroutine, public atmos_phy_lt_sato2019_setup(KA, KS, KE, IA, IS, IE, JA, JS, JE, IMAXG, JMAXG, KMAX, MP_TYPE, CDX, CDY)
Setup.
Definition: scale_atmos_phy_lt_sato2019.F90:150
mod_atmos_vars::qtrc_av
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
Definition: mod_atmos_vars.F90:94
scale_atmos_hydrometeor::qhs
integer, public qhs
Definition: scale_atmos_hydrometeor.F90:115
scale_atmos_phy_lt_sato2019::atmos_phy_lt_sato2019_adjustment
subroutine, public atmos_phy_lt_sato2019_adjustment(KA, KS, KE, IA, IS, IE, JA, JS, JE, KIJMAX, IMAX, JMAX, QA_LT, DENS, RHOT, QHYD, Sarea, dt_LT, QTRC, Epot)
Update of charge density.
Definition: scale_atmos_phy_lt_sato2019.F90:304
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_phy_lt_vars
module Atmosphere / Physics Chemistry
Definition: mod_atmos_phy_lt_vars.F90:12
mod_atmos_vars::rhot_av
real(rp), dimension(:,:,:), pointer, public rhot_av
Definition: mod_atmos_vars.F90:93
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdy
y-length of control volume [m]
Definition: scale_atmos_grid_cartesC.F90:61
mod_atmos_phy_lt_driver::history
subroutine history
Definition: mod_atmos_phy_lt_driver.F90:286
scale_atmos_grid_cartesc_index::imaxg
integer, public imaxg
Definition: scale_atmos_grid_cartesC_index.F90:71
mod_atmos_phy_lt_vars::qe_lt
integer, public qe_lt
Definition: mod_atmos_phy_lt_vars.F90:60
mod_atmos_phy_lt_vars::atmos_phy_lt_sarea
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_lt_sarea
Definition: mod_atmos_phy_lt_vars.F90:56
mod_atmos_vars::rhot
real(rp), dimension(:,:,:), allocatable, target, public rhot
Definition: mod_atmos_vars.F90:79
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:80
scale_file_history
module file_history
Definition: scale_file_history.F90:15
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lon
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lon
longitude [rad,0-2pi]
Definition: scale_atmos_grid_cartesC_real.F90:48
scale_atmos_grid_cartesc_index::imax
integer, public imax
Definition: scale_atmos_grid_cartesC_index.F90:37
scale_atmos_grid_cartesc_index::jmaxg
integer, public jmaxg
Definition: scale_atmos_grid_cartesC_index.F90:72
scale_prc
module PROCESS
Definition: scale_prc.F90:11
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
mod_atmos_vars::dens
real(rp), dimension(:,:,:), allocatable, target, public dens
Definition: mod_atmos_vars.F90:75
mod_atmos_phy_lt_driver
module ATMOSPHERE / Physics Chemistry
Definition: mod_atmos_phy_lt_driver.F90:12
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
mod_atmos_admin::atmos_phy_lt_type
character(len=h_short), public atmos_phy_lt_type
Definition: mod_atmos_admin.F90:44
scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_nwaters
integer, public atmos_phy_mp_suzuki10_nwaters
Definition: scale_atmos_phy_mp_suzuki10.F90:56
mod_atmos_phy_lt_driver::atmos_phy_lt_driver_adjustment
subroutine, public atmos_phy_lt_driver_adjustment
Driver.
Definition: mod_atmos_phy_lt_driver.F90:251
scale_atmos_grid_cartesc_index::kmax
integer, public kmax
Definition: scale_atmos_grid_cartesC_index.F90:36
mod_atmos_admin::atmos_sw_phy_lt
logical, public atmos_sw_phy_lt
Definition: mod_atmos_admin.F90:60
scale_prof
module profiler
Definition: scale_prof.F90:11
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_mp_suzuki10
module Spectran Bin Microphysics
Definition: scale_atmos_phy_mp_suzuki10.F90:23
scale_atmos_hydrometeor::qha
integer, public qha
Definition: scale_atmos_hydrometeor.F90:114
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
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:65
scale_tracer
module TRACER
Definition: scale_tracer.F90:12
mod_atmos_phy_lt_vars::qa_lt
integer, public qa_lt
Definition: mod_atmos_phy_lt_vars.F90:58
mod_atmos_vars::dens_av
real(rp), dimension(:,:,:), pointer, public dens_av
Definition: mod_atmos_vars.F90:89
scale_atmos_grid_cartesc_index::ks
integer, public ks
start point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:51
mod_atmos_vars
module ATMOSPHERIC Variables
Definition: mod_atmos_vars.F90:12
scale_atmos_grid_cartesc_index::jmax
integer, public jmax
Definition: scale_atmos_grid_cartesC_index.F90:38
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_lt_vars::flg_lt
logical, public flg_lt
Definition: mod_atmos_phy_lt_vars.F90:64
scale_atmos_phy_lt_sato2019
module atmosphere / physics / lightninh / SATO2019
Definition: scale_atmos_phy_lt_sato2019.F90:12
mod_atmos_admin::atmos_phy_mp_type
character(len=h_short), public atmos_phy_mp_type
Definition: mod_atmos_admin.F90:36
scale_file_history::file_history_reg
subroutine, public file_history_reg(name, desc, unit, itemid, standard_name, ndims, dim_type, cell_measures, fill_halo)
Register/Append variable to history file.
Definition: scale_file_history.F90:650
mod_atmos_phy_lt_driver::atmos_phy_lt_driver_tracer_setup
subroutine, public atmos_phy_lt_driver_tracer_setup
Config.
Definition: mod_atmos_phy_lt_driver.F90:71
scale_time::time_dtsec_atmos_phy_lt
real(dp), public time_dtsec_atmos_phy_lt
time interval of physics(lightning ) [sec]
Definition: scale_time.F90:45
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdx
x-length of control volume [m]
Definition: scale_atmos_grid_cartesC.F90:60
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lat
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lat
latitude [rad,-pi,pi]
Definition: scale_atmos_grid_cartesC_real.F90:52
scale_atmos_grid_cartesc
module atmosphere / grid / cartesC
Definition: scale_atmos_grid_cartesC.F90:12
scale_atmos_hydrometeor::qla
integer, public qla
Definition: scale_atmos_hydrometeor.F90:118
scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_nices
integer, public atmos_phy_mp_suzuki10_nices
Definition: scale_atmos_phy_mp_suzuki10.F90:57
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:56
scale_atmos_grid_cartesc_index::kijmax
integer, public kijmax
Definition: scale_atmos_grid_cartesC_index.F90:58
scale_atmos_grid_cartesc_index::je
integer, public je
end point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:56
scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_nccn
integer, public atmos_phy_mp_suzuki10_nccn
Definition: scale_atmos_phy_mp_suzuki10.F90:58
mod_atmos_phy_lt_vars::atmos_phy_lt_epot
real(rp), dimension(:,:,:), allocatable, public atmos_phy_lt_epot
Definition: mod_atmos_phy_lt_vars.F90:55
mod_atmos_phy_lt_vars::qs_lt
integer, public qs_lt
Definition: mod_atmos_phy_lt_vars.F90:59
mod_atmos_phy_lt_driver::atmos_phy_lt_driver_setup
subroutine, public atmos_phy_lt_driver_setup
Setup.
Definition: mod_atmos_phy_lt_driver.F90:158