SCALE-RM
Functions/Subroutines | Variables
scale_tracer Module Reference

module TRACER More...

Functions/Subroutines

subroutine, public tracer_setup
 Setup. More...
 

Variables

integer, public qa
 
integer, public qa_mp
 
integer, public i_qv
 
integer, public i_qc
 
integer, public i_qr
 
integer, public i_qi
 
integer, public i_qs
 
integer, public i_qg
 
integer, public i_nc
 
integer, public i_nr
 
integer, public i_ni
 
integer, public i_ns
 
integer, public i_ng
 
integer, public qqa
 
integer, public qqs
 
integer, public qqe
 
integer, public qws
 
integer, public qwe
 
integer, public qis
 
integer, public qie
 
integer, public qa_ae
 
integer, public ae_ctg
 
integer, public gas_ctg
 
integer, public n_atr
 
integer, dimension(:), allocatable, public nkap
 
integer, dimension(:), allocatable, public nsiz
 
integer, public ic_mix
 
integer, public ic_sea
 
integer, public ic_dus
 
integer, public ig_h2so4
 
integer, public ig_cgas
 
integer, public qaes
 
integer, public qaee
 
character(len=h_short), dimension(:), allocatable, public aq_name
 
character(len=h_short), dimension(:), allocatable, public aq_mp_name
 
character(len=h_short), dimension(:), allocatable, public aq_ae_name
 
character(len=h_mid), dimension(:), allocatable, public aq_desc
 
character(len=h_mid), dimension(:), allocatable, public aq_mp_desc
 
character(len=h_mid), dimension(:), allocatable, public aq_ae_desc
 
character(len=h_short), dimension(:), allocatable, public aq_unit
 
character(len=h_short), dimension(:), allocatable, public aq_mp_unit
 
character(len=h_short), dimension(:), allocatable, public aq_ae_unit
 
integer, public mp_qa
 
integer, dimension(:), allocatable, public i_mp2all
 
integer, dimension(:), allocatable, public i_mp2rd
 
integer, public ae_qa
 
integer, public i_ae_dummy
 
integer, dimension(:), allocatable, public i_ae2all
 
integer, dimension(:), allocatable, public i_ae2rd
 
character(len=h_short), public tracer_type = 'DRY'
 
character(len=h_short), public aetracer_type = 'NONE'
 

Detailed Description

module TRACER

Description
Tracer module
Author
Team SCALE
History
  • 2013-12-04 (S.Nishizawa) [new]

Function/Subroutine Documentation

◆ tracer_setup()

subroutine, public scale_tracer::tracer_setup ( )

Setup.

Definition at line 127 of file scale_tracer.F90.

References ae_ctg, ae_qa, scale_aetracer_kajino13::aetracer_kajino13_setup(), scale_aetracer_none::aetracer_none_setup(), aetracer_type, aq_ae_desc, aq_ae_name, aq_ae_unit, aq_desc, aq_mp_desc, aq_mp_name, aq_mp_unit, aq_name, aq_unit, gas_ctg, i_ae2all, i_ae2rd, i_ae_dummy, i_mp2all, i_mp2rd, i_nc, i_ng, i_ni, i_nr, i_ns, i_qc, i_qg, i_qi, i_qr, i_qs, i_qv, ic_dus, ic_mix, ic_sea, ig_cgas, ig_h2so4, scale_stdio::io_fid_conf, scale_stdio::io_fid_log, scale_stdio::io_l, mp_qa, n_atr, nkap, nsiz, scale_process::prc_mpistop(), qa, qa_ae, qa_mp, qaee, qaes, qie, qis, qqa, qqe, qqs, qwe, qws, scale_tracer_dry::tracer_dry_setup(), scale_tracer_kessler::tracer_kessler_setup(), scale_tracer_sdm::tracer_sdm_setup(), scale_tracer_sn14::tracer_sn14_setup(), scale_tracer_suzuki10::tracer_suzuki10_setup(), scale_tracer_tomita08::tracer_tomita08_setup(), and tracer_type.

Referenced by mod_rm_driver::scalerm(), and mod_rm_prep::scalerm_prep().

127 #ifdef TRACER
128 #define EXTM2(name) scale_tracer_ ## name
129 #define _MODNAME(name) EXTM2(name)
130 #define EXTM3(name) tracer_ ## name ## _setup
131 #define _SETUP(name) EXTM3(name)
132  use _modname(tracer), only: &
133  _setup(tracer)
134 #else
135  use scale_process, only: &
137  use scale_tracer_dry, only: &
138  qa_mp_dry => qa_mp, &
139  i_qv_dry => i_qv, &
140  i_qc_dry => i_qc, &
141  i_qr_dry => i_qr, &
142  i_qi_dry => i_qi, &
143  i_qs_dry => i_qs, &
144  i_qg_dry => i_qg, &
145  i_nc_dry => i_nc, &
146  i_nr_dry => i_nr, &
147  i_ni_dry => i_ni, &
148  i_ns_dry => i_ns, &
149  i_ng_dry => i_ng, &
150  qqa_dry => qqa, &
151  qqs_dry => qqs, &
152  qqe_dry => qqe, &
153  qws_dry => qws, &
154  qwe_dry => qwe, &
155  qis_dry => qis, &
156  qie_dry => qie, &
157  mp_qa_dry => mp_qa, &
158  aq_mp_name_dry => aq_mp_name, &
159  aq_mp_desc_dry => aq_mp_desc, &
160  aq_mp_unit_dry => aq_mp_unit, &
161  i_mp2all_dry => i_mp2all, &
162  i_mp2rd_dry => i_mp2rd, &
164  use scale_tracer_kessler, only: &
165  qa_mp_kessler => qa_mp, &
166  i_qv_kessler => i_qv, &
167  i_qc_kessler => i_qc, &
168  i_qr_kessler => i_qr, &
169  i_qi_kessler => i_qi, &
170  i_qs_kessler => i_qs, &
171  i_qg_kessler => i_qg, &
172  i_nc_kessler => i_nc, &
173  i_nr_kessler => i_nr, &
174  i_ni_kessler => i_ni, &
175  i_ns_kessler => i_ns, &
176  i_ng_kessler => i_ng, &
177  qqa_kessler => qqa, &
178  qqs_kessler => qqs, &
179  qqe_kessler => qqe, &
180  qws_kessler => qws, &
181  qwe_kessler => qwe, &
182  qis_kessler => qis, &
183  qie_kessler => qie, &
184  mp_qa_kessler => mp_qa, &
185  aq_mp_name_kessler => aq_mp_name, &
186  aq_mp_desc_kessler => aq_mp_desc, &
187  aq_mp_unit_kessler => aq_mp_unit, &
188  i_mp2all_kessler => i_mp2all, &
189  i_mp2rd_kessler => i_mp2rd, &
191  use scale_tracer_tomita08, only: &
192  qa_mp_tomita08 => qa_mp, &
193  i_qv_tomita08 => i_qv, &
194  i_qc_tomita08 => i_qc, &
195  i_qr_tomita08 => i_qr, &
196  i_qi_tomita08 => i_qi, &
197  i_qs_tomita08 => i_qs, &
198  i_qg_tomita08 => i_qg, &
199  i_nc_tomita08 => i_nc, &
200  i_nr_tomita08 => i_nr, &
201  i_ni_tomita08 => i_ni, &
202  i_ns_tomita08 => i_ns, &
203  i_ng_tomita08 => i_ng, &
204  qqa_tomita08 => qqa, &
205  qqs_tomita08 => qqs, &
206  qqe_tomita08 => qqe, &
207  qws_tomita08 => qws, &
208  qwe_tomita08 => qwe, &
209  qis_tomita08 => qis, &
210  qie_tomita08 => qie, &
211  mp_qa_tomita08 => mp_qa, &
212  aq_mp_name_tomita08 => aq_mp_name, &
213  aq_mp_desc_tomita08 => aq_mp_desc, &
214  aq_mp_unit_tomita08 => aq_mp_unit, &
215  i_mp2all_tomita08 => i_mp2all, &
216  i_mp2rd_tomita08 => i_mp2rd, &
218  use scale_tracer_sn14, only: &
219  qa_mp_sn14 => qa_mp, &
220  i_qv_sn14 => i_qv, &
221  i_qc_sn14 => i_qc, &
222  i_qr_sn14 => i_qr, &
223  i_qi_sn14 => i_qi, &
224  i_qs_sn14 => i_qs, &
225  i_qg_sn14 => i_qg, &
226  i_nc_sn14 => i_nc, &
227  i_nr_sn14 => i_nr, &
228  i_ni_sn14 => i_ni, &
229  i_ns_sn14 => i_ns, &
230  i_ng_sn14 => i_ng, &
231  qqa_sn14 => qqa, &
232  qqs_sn14 => qqs, &
233  qqe_sn14 => qqe, &
234  qws_sn14 => qws, &
235  qwe_sn14 => qwe, &
236  qis_sn14 => qis, &
237  qie_sn14 => qie, &
238  mp_qa_sn14 => mp_qa, &
239  aq_mp_name_sn14 => aq_mp_name, &
240  aq_mp_desc_sn14 => aq_mp_desc, &
241  aq_mp_unit_sn14 => aq_mp_unit, &
242  i_mp2all_sn14 => i_mp2all, &
243  i_mp2rd_sn14 => i_mp2rd, &
245  use scale_tracer_suzuki10, only: &
246  qa_mp_suzuki10 => qa_mp, &
247  i_qv_suzuki10 => i_qv, &
248  i_qc_suzuki10 => i_qc, &
249  i_qr_suzuki10 => i_qr, &
250  i_qi_suzuki10 => i_qi, &
251  i_qs_suzuki10 => i_qs, &
252  i_qg_suzuki10 => i_qg, &
253  i_nc_suzuki10 => i_nc, &
254  i_nr_suzuki10 => i_nr, &
255  i_ni_suzuki10 => i_ni, &
256  i_ns_suzuki10 => i_ns, &
257  i_ng_suzuki10 => i_ng, &
258  qqa_suzuki10 => qqa, &
259  qqs_suzuki10 => qqs, &
260  qqe_suzuki10 => qqe, &
261  qws_suzuki10 => qws, &
262  qwe_suzuki10 => qwe, &
263  qis_suzuki10 => qis, &
264  qie_suzuki10 => qie, &
265  mp_qa_suzuki10 => mp_qa, &
266  aq_mp_name_suzuki10 => aq_mp_name, &
267  aq_mp_desc_suzuki10 => aq_mp_desc, &
268  aq_mp_unit_suzuki10 => aq_mp_unit, &
269  i_mp2all_suzuki10 => i_mp2all, &
270  i_mp2rd_suzuki10 => i_mp2rd, &
272  use scale_tracer_sdm, only: &
273  qa_mp_sdm => qa_mp, &
274  i_qv_sdm => i_qv, &
275  i_qc_sdm => i_qc, &
276  i_qr_sdm => i_qr, &
277  i_qi_sdm => i_qi, &
278  i_qs_sdm => i_qs, &
279  i_qg_sdm => i_qg, &
280  i_nc_sdm => i_nc, &
281  i_nr_sdm => i_nr, &
282  i_ni_sdm => i_ni, &
283  i_ns_sdm => i_ns, &
284  i_ng_sdm => i_ng, &
285  qqa_sdm => qqa, &
286  qqs_sdm => qqs, &
287  qqe_sdm => qqe, &
288  qws_sdm => qws, &
289  qwe_sdm => qwe, &
290  qis_sdm => qis, &
291  qie_sdm => qie, &
292  mp_qa_sdm => mp_qa, &
293  aq_mp_name_sdm => aq_mp_name, &
294  aq_mp_desc_sdm => aq_mp_desc, &
295  aq_mp_unit_sdm => aq_mp_unit, &
296  i_mp2all_sdm => i_mp2all, &
297  i_mp2rd_sdm => i_mp2rd, &
299  use scale_aetracer_none, only: &
300  qa_ae_none => qa_ae, &
301  ae_ctg_none => ae_ctg, &
302  n_atr_none => n_atr, &
303  gas_ctg_none => gas_ctg, &
304  nsiz_none => nsiz, &
305  nkap_none => nkap, &
306  ic_mix_none => ic_mix, &
307  ic_sea_none => ic_sea, &
308  ic_dus_none => ic_dus, &
309  ig_h2so4_none => ig_h2so4, &
310  ig_cgas_none => ig_cgas, &
311  ae_qa_none => ae_qa, &
312  i_ae_dummy_none => i_ae_dummy, &
313  aq_ae_name_none => aq_ae_name, &
314  aq_ae_desc_none => aq_ae_desc, &
315  aq_ae_unit_none => aq_ae_unit, &
316  i_ae2all_none => i_ae2all, &
317  i_ae2rd_none => i_ae2rd, &
319  use scale_aetracer_kajino13, only: &
320  qa_ae_kajino13 => qa_ae, &
321  ae_ctg_kajino13 => ae_ctg, &
322  n_atr_kajino13 => n_atr, &
323  gas_ctg_kajino13 => gas_ctg, &
324  nsiz_kajino13 => nsiz, &
325  nkap_kajino13 => nkap, &
326  ic_mix_kajino13 => ic_mix, &
327  ic_sea_kajino13 => ic_sea, &
328  ic_dus_kajino13 => ic_dus, &
329  ig_h2so4_kajino13 => ig_h2so4, &
330  ig_cgas_kajino13 => ig_cgas, &
331  ae_qa_kajino13 => ae_qa, &
332  i_ae_dummy_kajino13 => i_ae_dummy, &
333  aq_ae_name_kajino13 => aq_ae_name, &
334  aq_ae_desc_kajino13 => aq_ae_desc, &
335  aq_ae_unit_kajino13 => aq_ae_unit, &
336  i_ae2all_kajino13 => i_ae2all, &
337  i_ae2rd_kajino13 => i_ae2rd, &
339 #endif
340  implicit none
341 #ifndef TRACER
342  namelist / param_tracer / &
343  tracer_type, &
345 #endif
346 
347  integer :: ierr
348  !---------------------------------------------------------------------------
349 
350  if( io_l ) write(io_fid_log,*)
351  if( io_l ) write(io_fid_log,*) '+++ Module[TRACER]/Categ[COMMON]'
352 
353 #ifdef TRACER
354  call _setup(tracer)
355 #else
356  !--- read namelist
357  rewind(io_fid_conf)
358  read(io_fid_conf,nml=param_tracer,iostat=ierr)
359 
360  if( ierr < 0 ) then !--- missing
361  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
362  elseif( ierr > 0 ) then !--- fatal error
363  write(*,*) 'xxx Not appropriate names in namelist PARAM_TRACER. Check!'
364  call prc_mpistop
365  endif
366  if( io_l ) write(io_fid_log,nml=param_tracer)
367 
368  select case (tracer_type)
369  case ("DRY")
370  call tracer_dry_setup
371  qa_mp = qa_mp_dry
372  i_qv = i_qv_dry
373  i_qc = i_qc_dry
374  i_qr = i_qr_dry
375  i_qi = i_qi_dry
376  i_qs = i_qs_dry
377  i_qg = i_qg_dry
378  i_nc = i_nc_dry
379  i_nr = i_nr_dry
380  i_ni = i_ni_dry
381  i_ns = i_ns_dry
382  i_ng = i_ng_dry
383  qqa = qqa_dry
384  qqs = qqs_dry
385  qqe = qqe_dry
386  qws = qws_dry
387  qwe = qwe_dry
388  qis = qis_dry
389  qie = qie_dry
390  mp_qa = mp_qa_dry
391  allocate( aq_mp_name(qa_mp) )
392  allocate( aq_mp_desc(qa_mp) )
393  allocate( aq_mp_unit(qa_mp) )
394  allocate( i_mp2all(mp_qa) )
395  allocate( i_mp2rd(mp_qa) )
396  aq_mp_name = aq_mp_name_dry
397  aq_mp_desc = aq_mp_desc_dry
398  aq_mp_unit = aq_mp_unit_dry
399  i_mp2all = i_mp2all_dry
400  i_mp2rd = i_mp2rd_dry
401  case ("KESSLER")
403  qa_mp = qa_mp_kessler
404  i_qv = i_qv_kessler
405  i_qc = i_qc_kessler
406  i_qr = i_qr_kessler
407  i_qi = i_qi_kessler
408  i_qs = i_qs_kessler
409  i_qg = i_qg_kessler
410  i_nc = i_nc_kessler
411  i_nr = i_nr_kessler
412  i_ni = i_ni_kessler
413  i_ns = i_ns_kessler
414  i_ng = i_ng_kessler
415  qqa = qqa_kessler
416  qqs = qqs_kessler
417  qqe = qqe_kessler
418  qws = qws_kessler
419  qwe = qwe_kessler
420  qis = qis_kessler
421  qie = qie_kessler
422  mp_qa = mp_qa_kessler
423  allocate( aq_mp_name(qa_mp) )
424  allocate( aq_mp_desc(qa_mp) )
425  allocate( aq_mp_unit(qa_mp) )
426  allocate( i_mp2all(mp_qa) )
427  allocate( i_mp2rd(mp_qa) )
428  aq_mp_name = aq_mp_name_kessler
429  aq_mp_desc = aq_mp_desc_kessler
430  aq_mp_unit = aq_mp_unit_kessler
431  i_mp2all = i_mp2all_kessler
432  i_mp2rd = i_mp2rd_kessler
433  case ("TOMITA08")
435  qa_mp = qa_mp_tomita08
436  i_qv = i_qv_tomita08
437  i_qc = i_qc_tomita08
438  i_qr = i_qr_tomita08
439  i_qi = i_qi_tomita08
440  i_qs = i_qs_tomita08
441  i_qg = i_qg_tomita08
442  i_nc = i_nc_tomita08
443  i_nr = i_nr_tomita08
444  i_ni = i_ni_tomita08
445  i_ns = i_ns_tomita08
446  i_ng = i_ng_tomita08
447  qqa = qqa_tomita08
448  qqs = qqs_tomita08
449  qqe = qqe_tomita08
450  qws = qws_tomita08
451  qwe = qwe_tomita08
452  qis = qis_tomita08
453  qie = qie_tomita08
454  mp_qa = mp_qa_tomita08
455  allocate( aq_mp_name(qa_mp) )
456  allocate( aq_mp_desc(qa_mp) )
457  allocate( aq_mp_unit(qa_mp) )
458  allocate( i_mp2all(mp_qa) )
459  allocate( i_mp2rd(mp_qa) )
460  aq_mp_name = aq_mp_name_tomita08
461  aq_mp_desc = aq_mp_desc_tomita08
462  aq_mp_unit = aq_mp_unit_tomita08
463  i_mp2all = i_mp2all_tomita08
464  i_mp2rd = i_mp2rd_tomita08
465  case ("SN14")
466  call tracer_sn14_setup
467  qa_mp = qa_mp_sn14
468  i_qv = i_qv_sn14
469  i_qc = i_qc_sn14
470  i_qr = i_qr_sn14
471  i_qi = i_qi_sn14
472  i_qs = i_qs_sn14
473  i_qg = i_qg_sn14
474  i_nc = i_nc_sn14
475  i_nr = i_nr_sn14
476  i_ni = i_ni_sn14
477  i_ns = i_ns_sn14
478  i_ng = i_ng_sn14
479  qqa = qqa_sn14
480  qqs = qqs_sn14
481  qqe = qqe_sn14
482  qws = qws_sn14
483  qwe = qwe_sn14
484  qis = qis_sn14
485  qie = qie_sn14
486  mp_qa = mp_qa_sn14
487  allocate( aq_mp_name(qa_mp) )
488  allocate( aq_mp_desc(qa_mp) )
489  allocate( aq_mp_unit(qa_mp) )
490  allocate( i_mp2all(mp_qa) )
491  allocate( i_mp2rd(mp_qa) )
492  aq_mp_name = aq_mp_name_sn14
493  aq_mp_desc = aq_mp_desc_sn14
494  aq_mp_unit = aq_mp_unit_sn14
495  i_mp2all = i_mp2all_sn14
496  i_mp2rd = i_mp2rd_sn14
497  case ("SUZUKI10")
499  qa_mp = qa_mp_suzuki10
500  i_qv = i_qv_suzuki10
501  i_qc = i_qc_suzuki10
502  i_qr = i_qr_suzuki10
503  i_qi = i_qi_suzuki10
504  i_qs = i_qs_suzuki10
505  i_qg = i_qg_suzuki10
506  i_nc = i_nc_suzuki10
507  i_nr = i_nr_suzuki10
508  i_ni = i_ni_suzuki10
509  i_ns = i_ns_suzuki10
510  i_ng = i_ng_suzuki10
511  qqa = qqa_suzuki10
512  qqs = qqs_suzuki10
513  qqe = qqe_suzuki10
514  qws = qws_suzuki10
515  qwe = qwe_suzuki10
516  qis = qis_suzuki10
517  qie = qie_suzuki10
518  mp_qa = mp_qa_suzuki10
519  allocate( aq_mp_name(qa_mp) )
520  allocate( aq_mp_desc(qa_mp) )
521  allocate( aq_mp_unit(qa_mp) )
522  allocate( i_mp2all(mp_qa) )
523  allocate( i_mp2rd(mp_qa) )
524  aq_mp_name = aq_mp_name_suzuki10
525  aq_mp_desc = aq_mp_desc_suzuki10
526  aq_mp_unit = aq_mp_unit_suzuki10
527  i_mp2all = i_mp2all_suzuki10
528  i_mp2rd = i_mp2rd_suzuki10
529  case ("SDM")
530  call tracer_sdm_setup
531  qa_mp = qa_mp_sdm
532  i_qv = i_qv_sdm
533  i_qc = i_qc_sdm
534  i_qr = i_qr_sdm
535  i_qi = i_qi_sdm
536  i_qs = i_qs_sdm
537  i_qg = i_qg_sdm
538  i_nc = i_nc_sdm
539  i_nr = i_nr_sdm
540  i_ni = i_ni_sdm
541  i_ns = i_ns_sdm
542  i_ng = i_ng_sdm
543  qqa = qqa_sdm
544  qqs = qqs_sdm
545  qqe = qqe_sdm
546  qws = qws_sdm
547  qwe = qwe_sdm
548  qis = qis_sdm
549  qie = qie_sdm
550  mp_qa = mp_qa_sdm
551  allocate( aq_mp_name(qa_mp) )
552  allocate( aq_mp_desc(qa_mp) )
553  allocate( aq_mp_unit(qa_mp) )
554  allocate( i_mp2all(mp_qa) )
555  allocate( i_mp2rd(mp_qa) )
556  aq_mp_name = aq_mp_name_sdm
557  aq_mp_desc = aq_mp_desc_sdm
558  aq_mp_unit = aq_mp_unit_sdm
559  i_mp2all = i_mp2all_sdm
560  i_mp2rd = i_mp2rd_sdm
561  case default
562  write(*,*) 'xxx Unsupported TRACER_TYPE (', trim(tracer_type), '). Check!'
563  call prc_mpistop
564  end select
565  select case (aetracer_type)
566  case ("NONE")
568  qa_ae = qa_ae_none
569  ae_ctg = ae_ctg_none
570  n_atr = n_atr_none
571  gas_ctg = gas_ctg_none
572  allocate( nsiz(ae_ctg) )
573  allocate( nkap(ae_ctg) )
574  nsiz = nsiz_none
575  nkap = nkap_none
576  ic_mix = ic_mix_none
577  ic_sea = ic_sea_none
578  ic_dus = ic_dus_none
579  ig_h2so4 = ig_h2so4_none
580  ig_cgas = ig_cgas_none
581  ae_qa = ae_qa_none
582  i_ae_dummy = i_ae_dummy_none
583  allocate( aq_ae_name(qa_ae) )
584  allocate( aq_ae_desc(qa_ae) )
585  allocate( aq_ae_unit(qa_ae) )
586  allocate( i_ae2all(ae_qa) )
587  allocate( i_ae2rd(ae_qa) )
588  aq_ae_name = aq_ae_name_none
589  aq_ae_desc = aq_ae_desc_none
590  aq_ae_unit = aq_ae_unit_none
591  i_ae2all = i_ae2all_none
592  i_ae2rd = i_ae2rd_none
593  case ("KAJINO13")
595  qa_ae = qa_ae_kajino13
596  ae_ctg = ae_ctg_kajino13
597  n_atr = n_atr_kajino13
598  gas_ctg = gas_ctg_kajino13
599  allocate( nsiz(ae_ctg) )
600  allocate( nkap(ae_ctg) )
601  nsiz = nsiz_kajino13
602  nkap = nkap_kajino13
603  ic_mix = ic_mix_kajino13
604  ic_sea = ic_sea_kajino13
605  ic_dus = ic_dus_kajino13
606  ig_h2so4 = ig_h2so4_kajino13
607  ig_cgas = ig_cgas_kajino13
608  ae_qa = ae_qa_kajino13
609  i_ae_dummy = i_ae_dummy_kajino13
610  allocate( aq_ae_name(qa_ae) )
611  allocate( aq_ae_desc(qa_ae) )
612  allocate( aq_ae_unit(qa_ae) )
613  allocate( i_ae2all(ae_qa) )
614  allocate( i_ae2rd(ae_qa) )
615  aq_ae_name = aq_ae_name_kajino13
616  aq_ae_desc = aq_ae_desc_kajino13
617  aq_ae_unit = aq_ae_unit_kajino13
618  i_ae2all = i_ae2all_kajino13
619  i_ae2rd = i_ae2rd_kajino13
620  case default
621  write(*,*) 'xxx Unsupported AETRACER_TYPE (', trim(aetracer_type), '). Check!'
622  call prc_mpistop
623  end select
624  qaes = qa_mp+1
625  qaee = qa_mp+qa_ae
626  qa = qa_mp + qa_ae
627  allocate( aq_name(qa) )
628  allocate( aq_desc(qa) )
629  allocate( aq_unit(qa) )
630  aq_name(1:qa_mp) = aq_mp_name(1:qa_mp)
631  aq_desc(1:qa_mp) = aq_mp_desc(1:qa_mp)
632  aq_unit(1:qa_mp) = aq_mp_unit(1:qa_mp)
636 #endif
637 
integer, public qie
character(len=h_mid), dimension(:), allocatable, public aq_desc
character(len=h_short), dimension(:), allocatable, public aq_mp_name
integer, dimension(:), allocatable, public i_ae2rd
integer, public qa_ae
character(len=h_mid), dimension(:), allocatable, public aq_ae_desc
subroutine, public prc_mpistop
Abort MPI.
character(len=h_short), dimension(:), allocatable, public aq_mp_unit
module TRACER / sn14
character(len=h_short), public aetracer_type
integer, public qqe
integer, public i_ng
module TRACER / kajino13
integer, public qwe
module TRACER / dry
integer, public qaes
integer, public qa
integer, public i_ae_dummy
integer, public qws
integer, public qis
character(len=h_short), public tracer_type
module TRACER / suzuki10
character(len=h_short), dimension(:), allocatable, public aq_ae_unit
character(len=h_mid), dimension(:), allocatable, public aq_mp_desc
subroutine, public aetracer_none_setup
subroutine, public tracer_sdm_setup
integer, dimension(:), allocatable, public nkap
integer, public mp_qa
integer, public ae_ctg
integer, public i_ni
integer, public i_qv
module TRACER / kessler
integer, public ig_h2so4
integer, public qqa
integer, public gas_ctg
integer, public ae_qa
integer, dimension(:), allocatable, public i_mp2all
character(len=h_short), dimension(:), allocatable, public aq_name
module TRACER / none
integer, public i_nc
subroutine, public tracer_tomita08_setup
module PROCESS
subroutine, public tracer_kessler_setup
integer, dimension(:), allocatable, public nsiz
character(len=h_short), dimension(:), allocatable, public aq_unit
integer, public i_nr
integer, dimension(:), allocatable, public i_mp2rd
integer, public i_qs
integer, public i_qi
character(len=h_short), dimension(:), allocatable, public aq_ae_name
integer, public ic_mix
integer, public ic_sea
integer, public i_ns
integer, public qa_mp
integer, public qqs
subroutine, public aetracer_kajino13_setup
integer, public i_qg
integer, public ig_cgas
integer, public n_atr
subroutine, public tracer_dry_setup
subroutine, public tracer_suzuki10_setup
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
integer, public ic_dus
integer, dimension(:), allocatable, public i_ae2all
module TRACER / tomita08
integer, public qaee
subroutine, public tracer_sn14_setup
integer, public i_qr
integer, public i_qc
Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ qa

integer, public scale_tracer::qa

Definition at line 44 of file scale_tracer.F90.

Referenced by scale_atmos_boundary::atmos_boundary_setup(), scale_atmos_boundary::atmos_boundary_update(), scale_atmos_dyn::atmos_dyn(), scale_atmos_dyn::atmos_dyn_setup(), scale_atmos_dyn_tstep_large_fvm_heve::atmos_dyn_tstep_large_fvm_heve(), scale_atmos_dyn_tstep_large_fvm_heve::atmos_dyn_tstep_large_fvm_heve_setup(), mod_atmos_phy_ae_driver::atmos_phy_ae_driver(), scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_setup(), mod_atmos_phy_ch_driver::atmos_phy_ch_driver(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_setup(), mod_atmos_phy_cp_driver::atmos_phy_cp_driver(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_setup(), scale_atmos_phy_mp_convert::atmos_phy_mp_bulk2bin(), mod_atmos_phy_mp_driver::atmos_phy_mp_driver(), scale_atmos_phy_mp_dry::atmos_phy_mp_dry(), scale_atmos_phy_mp_dry::atmos_phy_mp_dry_cloudfraction(), scale_atmos_phy_mp_dry::atmos_phy_mp_dry_effectiveradius(), scale_atmos_phy_mp_dry::atmos_phy_mp_dry_mixingratio(), scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler(), scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_cloudfraction(), scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_effectiveradius(), scale_atmos_phy_mp_kessler::atmos_phy_mp_kessler_mixingratio(), scale_atmos_phy_mp_common::atmos_phy_mp_precipitation(), scale_atmos_phy_mp_sdm::atmos_phy_mp_sdm(), scale_atmos_phy_mp_sdm::atmos_phy_mp_sdm_cloudfraction(), scale_atmos_phy_mp_sdm::atmos_phy_mp_sdm_effectiveradius(), scale_atmos_phy_mp_sdm::atmos_phy_mp_sdm_mixingratio(), scale_atmos_phy_mp_sn14::atmos_phy_mp_sn14(), scale_atmos_phy_mp_sn14::atmos_phy_mp_sn14_cloudfraction(), scale_atmos_phy_mp_sn14::atmos_phy_mp_sn14_effectiveradius(), scale_atmos_phy_mp_sn14::atmos_phy_mp_sn14_mixingratio(), scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10(), scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_cloudfraction(), scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_effectiveradius(), scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_mixingratio(), scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_setup(), scale_atmos_phy_mp_tomita08::atmos_phy_mp_tomita08(), scale_atmos_phy_mp_tomita08::atmos_phy_mp_tomita08_cloudfraction(), scale_atmos_phy_mp_tomita08::atmos_phy_mp_tomita08_effectiveradius(), scale_atmos_phy_mp_tomita08::atmos_phy_mp_tomita08_mixingratio(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_setup(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_setup(), scale_atmos_phy_tb_d1980::atmos_phy_tb_d1980(), scale_atmos_phy_tb_dns::atmos_phy_tb_dns(), mod_atmos_phy_tb_driver::atmos_phy_tb_driver(), scale_atmos_phy_tb_hybrid::atmos_phy_tb_hybrid(), scale_atmos_phy_tb_mynn::atmos_phy_tb_mynn(), scale_atmos_phy_tb_smg::atmos_phy_tb_smg(), mod_atmos_phy_tb_vars::atmos_phy_tb_vars_setup(), mod_atmos_vars::atmos_vars_fillhalo(), mod_atmos_vars::atmos_vars_history(), mod_atmos_vars::atmos_vars_monitor(), mod_atmos_vars::atmos_vars_restart_check(), mod_atmos_vars::atmos_vars_restart_read(), mod_atmos_vars::atmos_vars_restart_write(), mod_atmos_vars::atmos_vars_setup(), mod_atmos_vars::atmos_vars_total(), scale_comm::comm_setup(), mod_cpl_vars::cpl_getsfc_atm(), mod_mkinit::diag_ds(), mod_mkinit::mkinit(), scale_atmos_phy_mp_sn14::mp_negativefilter(), scale_grid_nest::nest_setup(), mod_realinput_scale::parentatominputscale(), mod_realinput_wrfarw::parentatominputwrfarw(), mod_realinput::parentatomsetup(), mod_mkinit::read_sounding(), mod_realinput::realinput_atmos(), tracer_setup(), and scale_urban_phy_slc::urban_phy_slc().

44  integer, public :: qa
integer, public qa

◆ qa_mp

integer, public scale_tracer::qa_mp

Definition at line 46 of file scale_tracer.F90.

Referenced by tracer_setup(), and scale_tracer_suzuki10::tracer_suzuki10_setup().

46  integer, public :: qa_mp
integer, public qa_mp

◆ i_qv

integer, public scale_tracer::i_qv

Definition at line 47 of file scale_tracer.F90.

Referenced by scale_atmos_adiabat::atmos_adiabat_cape(), scale_atmos_adiabat::atmos_adiabat_liftparcel(), scale_atmos_boundary::atmos_boundary_setup(), scale_atmos_dyn_common::atmos_dyn_numfilter_coef_q(), scale_atmos_dyn_tstep_large_fvm_heve::atmos_dyn_tstep_large_fvm_heve(), scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13(), scale_atmos_phy_mp_convert::atmos_phy_mp_bulk2bin(), scale_atmos_phy_mp_common::atmos_phy_mp_negative_fixer(), scale_atmos_phy_mp_common::atmos_phy_mp_precipitation(), scale_atmos_phy_mp_common::atmos_phy_mp_saturation_adjustment(), mod_atmos_phy_rd_driver::atmos_phy_rd_driver(), scale_atmos_phy_rd_mstrnx::atmos_phy_rd_mstrnx(), scale_atmos_phy_sf_bulk::atmos_phy_sf_bulk(), scale_atmos_phy_sf_const::atmos_phy_sf_const(), mod_atmos_phy_sf_driver::atmos_phy_sf_driver(), mod_atmos_phy_tb_driver::atmos_phy_tb_driver(), scale_atmos_phy_tb_mynn::atmos_phy_tb_mynn(), scale_atmos_refstate::atmos_refstate_update(), scale_atmos_thermodyn::atmos_thermodyn_qd_0d(), scale_atmos_thermodyn::atmos_thermodyn_setup(), scale_atmos_thermodyn::atmos_thermodyn_tempre(), scale_atmos_thermodyn::atmos_thermodyn_tempre2(), mod_atmos_vars::atmos_vars_history(), mod_atmos_vars::atmos_vars_monitor(), mod_atmos_vars::atmos_vars_total(), mod_cpl_vars::cpl_getsfc_atm(), mod_cpl_vars::cpl_putatm(), mod_mkinit::interporation_fact(), scale_grid_nest::nest_setup(), mod_realinput_nicam::parentatominputnicam(), mod_realinput_wrfarw::parentatominputwrfarw(), mod_realinput::parentatomsetup(), mod_mkinit::read_sounding(), mod_mkinit::rect_setup(), tracer_setup(), and scale_tracer_suzuki10::tracer_suzuki10_setup().

47  integer, public :: i_qv
integer, public i_qv

◆ i_qc

integer, public scale_tracer::i_qc

◆ i_qr

integer, public scale_tracer::i_qr

◆ i_qi

integer, public scale_tracer::i_qi

◆ i_qs

integer, public scale_tracer::i_qs

◆ i_qg

integer, public scale_tracer::i_qg

◆ i_nc

integer, public scale_tracer::i_nc

◆ i_nr

integer, public scale_tracer::i_nr

Definition at line 54 of file scale_tracer.F90.

Referenced by mod_realinput_wrfarw::parentatominputwrfarw(), mod_realinput::replace_misval_map(), and tracer_setup().

54  integer, public :: i_nr
integer, public i_nr

◆ i_ni

integer, public scale_tracer::i_ni

Definition at line 55 of file scale_tracer.F90.

Referenced by mod_realinput_wrfarw::parentatominputwrfarw(), mod_realinput::replace_misval_map(), and tracer_setup().

55  integer, public :: i_ni
integer, public i_ni

◆ i_ns

integer, public scale_tracer::i_ns

Definition at line 56 of file scale_tracer.F90.

Referenced by mod_realinput_wrfarw::parentatominputwrfarw(), mod_realinput::replace_misval_map(), and tracer_setup().

56  integer, public :: i_ns
integer, public i_ns

◆ i_ng

integer, public scale_tracer::i_ng

Definition at line 57 of file scale_tracer.F90.

Referenced by mod_realinput_wrfarw::parentatominputwrfarw(), mod_realinput::replace_misval_map(), and tracer_setup().

57  integer, public :: i_ng
integer, public i_ng

◆ qqa

integer, public scale_tracer::qqa

◆ qqs

integer, public scale_tracer::qqs

◆ qqe

integer, public scale_tracer::qqe

◆ qws

integer, public scale_tracer::qws

◆ qwe

integer, public scale_tracer::qwe

◆ qis

integer, public scale_tracer::qis

◆ qie

integer, public scale_tracer::qie

◆ qa_ae

integer, public scale_tracer::qa_ae

Definition at line 68 of file scale_tracer.F90.

Referenced by scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_setup(), and tracer_setup().

68  integer, public :: qa_ae ! number of tracer for aerosol
integer, public qa_ae

◆ ae_ctg

integer, public scale_tracer::ae_ctg

Definition at line 69 of file scale_tracer.F90.

Referenced by scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13_setup(), mod_mkinit::rect_setup(), and tracer_setup().

69  integer, public :: ae_ctg ! category number of aerosol
integer, public ae_ctg

◆ gas_ctg

integer, public scale_tracer::gas_ctg

Definition at line 70 of file scale_tracer.F90.

Referenced by scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13(), mod_mkinit::rect_setup(), and tracer_setup().

70  integer, public :: gas_ctg ! category number of gas
integer, public gas_ctg

◆ n_atr

integer, public scale_tracer::n_atr

◆ nkap

integer, dimension(:), allocatable, public scale_tracer::nkap

Definition at line 72 of file scale_tracer.F90.

Referenced by mod_mkinit::rect_setup(), and tracer_setup().

72  integer, public, allocatable :: nkap(:)
integer, dimension(:), allocatable, public nkap

◆ nsiz

integer, dimension(:), allocatable, public scale_tracer::nsiz

Definition at line 73 of file scale_tracer.F90.

Referenced by scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13_setup(), mod_mkinit::rect_setup(), and tracer_setup().

73  integer, public, allocatable :: nsiz(:)
integer, dimension(:), allocatable, public nsiz

◆ ic_mix

integer, public scale_tracer::ic_mix

◆ ic_sea

integer, public scale_tracer::ic_sea

Definition at line 75 of file scale_tracer.F90.

Referenced by tracer_setup().

75  integer, public :: ic_sea
integer, public ic_sea

◆ ic_dus

integer, public scale_tracer::ic_dus

Definition at line 76 of file scale_tracer.F90.

Referenced by tracer_setup().

76  integer, public :: ic_dus
integer, public ic_dus

◆ ig_h2so4

integer, public scale_tracer::ig_h2so4

◆ ig_cgas

integer, public scale_tracer::ig_cgas

◆ qaes

integer, public scale_tracer::qaes

Definition at line 79 of file scale_tracer.F90.

Referenced by scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13(), mod_mkinit::rect_setup(), and tracer_setup().

79  integer, public :: qaes ! start index for aerosol tracer
integer, public qaes

◆ qaee

integer, public scale_tracer::qaee

Definition at line 80 of file scale_tracer.F90.

Referenced by scale_atmos_phy_ae_kajino13::atmos_phy_ae_kajino13(), mod_mkinit::rect_setup(), and tracer_setup().

80  integer, public :: qaee ! end index for aerosol tracer
integer, public qaee

◆ aq_name

character(len=h_short), dimension(:), allocatable, public scale_tracer::aq_name

◆ aq_mp_name

character(len=h_short), dimension(:), allocatable, public scale_tracer::aq_mp_name

Definition at line 83 of file scale_tracer.F90.

Referenced by tracer_setup(), and scale_tracer_suzuki10::tracer_suzuki10_setup().

83  character(len=H_SHORT), public, allocatable :: aq_mp_name(:)
character(len=h_short), dimension(:), allocatable, public aq_mp_name

◆ aq_ae_name

character(len=h_short), dimension(:), allocatable, public scale_tracer::aq_ae_name

Definition at line 84 of file scale_tracer.F90.

Referenced by tracer_setup().

84  character(len=H_SHORT), public, allocatable :: aq_ae_name(:)
character(len=h_short), dimension(:), allocatable, public aq_ae_name

◆ aq_desc

character(len=h_mid), dimension(:), allocatable, public scale_tracer::aq_desc

Definition at line 85 of file scale_tracer.F90.

Referenced by mod_atmos_vars::atmos_vars_history(), mod_atmos_vars::atmos_vars_monitor(), mod_atmos_vars::atmos_vars_restart_write(), mod_atmos_vars::atmos_vars_setup(), and tracer_setup().

85  character(len=H_MID) , public, allocatable :: aq_desc(:)
character(len=h_mid), dimension(:), allocatable, public aq_desc

◆ aq_mp_desc

character(len=h_mid), dimension(:), allocatable, public scale_tracer::aq_mp_desc

Definition at line 86 of file scale_tracer.F90.

Referenced by tracer_setup(), and scale_tracer_suzuki10::tracer_suzuki10_setup().

86  character(len=H_MID) , public, allocatable :: aq_mp_desc(:)
character(len=h_mid), dimension(:), allocatable, public aq_mp_desc

◆ aq_ae_desc

character(len=h_mid), dimension(:), allocatable, public scale_tracer::aq_ae_desc

Definition at line 87 of file scale_tracer.F90.

Referenced by tracer_setup().

87  character(len=H_MID) , public, allocatable :: aq_ae_desc(:)
character(len=h_mid), dimension(:), allocatable, public aq_ae_desc

◆ aq_unit

character(len=h_short), dimension(:), allocatable, public scale_tracer::aq_unit

◆ aq_mp_unit

character(len=h_short), dimension(:), allocatable, public scale_tracer::aq_mp_unit

Definition at line 89 of file scale_tracer.F90.

Referenced by tracer_setup(), and scale_tracer_suzuki10::tracer_suzuki10_setup().

89  character(len=H_SHORT), public, allocatable :: aq_mp_unit(:)
character(len=h_short), dimension(:), allocatable, public aq_mp_unit

◆ aq_ae_unit

character(len=h_short), dimension(:), allocatable, public scale_tracer::aq_ae_unit

Definition at line 90 of file scale_tracer.F90.

Referenced by tracer_setup().

90  character(len=H_SHORT), public, allocatable :: aq_ae_unit(:)
character(len=h_short), dimension(:), allocatable, public aq_ae_unit

◆ mp_qa

integer, public scale_tracer::mp_qa

◆ i_mp2all

integer, dimension(:), allocatable, public scale_tracer::i_mp2all

Definition at line 99 of file scale_tracer.F90.

Referenced by scale_atmos_phy_rd_mstrnx::atmos_phy_rd_mstrnx(), and tracer_setup().

99  integer, public, allocatable :: i_mp2all(:)
integer, dimension(:), allocatable, public i_mp2all

◆ i_mp2rd

integer, dimension(:), allocatable, public scale_tracer::i_mp2rd

Definition at line 101 of file scale_tracer.F90.

Referenced by scale_atmos_phy_rd_mstrnx::atmos_phy_rd_mstrnx_setup(), and tracer_setup().

101  integer, public, allocatable :: i_mp2rd(:)
integer, dimension(:), allocatable, public i_mp2rd

◆ ae_qa

integer, public scale_tracer::ae_qa

◆ i_ae_dummy

integer, public scale_tracer::i_ae_dummy

Definition at line 104 of file scale_tracer.F90.

Referenced by tracer_setup().

104  integer, public :: i_ae_dummy
integer, public i_ae_dummy

◆ i_ae2all

integer, dimension(:), allocatable, public scale_tracer::i_ae2all

Definition at line 105 of file scale_tracer.F90.

Referenced by scale_atmos_phy_rd_mstrnx::atmos_phy_rd_mstrnx(), and tracer_setup().

105  integer, public, allocatable :: i_ae2all(:)
integer, dimension(:), allocatable, public i_ae2all

◆ i_ae2rd

integer, dimension(:), allocatable, public scale_tracer::i_ae2rd

Definition at line 107 of file scale_tracer.F90.

Referenced by scale_atmos_phy_rd_mstrnx::atmos_phy_rd_mstrnx_setup(), and tracer_setup().

107  integer, public, allocatable :: i_ae2rd(:)
integer, dimension(:), allocatable, public i_ae2rd

◆ tracer_type

character(len=h_short), public scale_tracer::tracer_type = 'DRY'

◆ aetracer_type

character(len=h_short), public scale_tracer::aetracer_type = 'NONE'

Definition at line 110 of file scale_tracer.F90.

Referenced by mod_mkinit::interporation_fact(), mod_mkinit::read_sounding(), and tracer_setup().

110  character(len=H_SHORT), public :: aetracer_type = 'NONE'
character(len=h_short), public aetracer_type