SCALE-RM
mod_atmos_phy_ae_driver.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
12 !-------------------------------------------------------------------------------
13 #include "inc_openmp.h"
15  !-----------------------------------------------------------------------------
16  !
17  !++ used modules
18  !
19  use scale_precision
20  use scale_stdio
21  use scale_prof
23  use scale_tracer
24  !-----------------------------------------------------------------------------
25  implicit none
26  private
27  !-----------------------------------------------------------------------------
28  !
29  !++ Public procedure
30  !
34  public :: atmos_phy_ae_driver
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 scale_atmos_phy_ae, only: &
55  use mod_atmos_admin, only: &
57 ! ATMOS_sw_phy_ae
58  implicit none
59  !---------------------------------------------------------------------------
60 
61  if( io_l ) write(io_fid_log,*)
62  if( io_l ) write(io_fid_log,*) '++++++ Module[CONFIG] / Categ[ATMOS PHY_AE] / Origin[SCALE-RM]'
63 
64  ! note: tentatively, aerosol module should be called at all time. we need dummy subprogram.
65 ! if ( ATMOS_sw_phy_ae ) then
67 
68 ! else
69 ! if( IO_L ) write(IO_FID_LOG,*) '*** this component is never called.'
70 ! endif
71 
72  return
73  end subroutine atmos_phy_ae_driver_config
74 
75  !-----------------------------------------------------------------------------
77  subroutine atmos_phy_ae_driver_setup
78  use scale_atmos_phy_ae, only: &
80  use mod_atmos_admin, only: &
82 ! ATMOS_sw_phy_ae
83  implicit none
84  !---------------------------------------------------------------------------
85 
86  if( io_l ) write(io_fid_log,*)
87  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[ATMOS PHY_AE] / Origin[SCALE-RM]'
88 
89  ! note: tentatively, aerosol module should be called at all time. we need dummy subprogram.
90 ! if ( ATMOS_sw_phy_ae ) then
91 
92  ! setup library component
94 
95 ! else
96 ! if( IO_L ) write(IO_FID_LOG,*) '*** this component is never called.'
97 ! endif
98 
99  return
100  end subroutine atmos_phy_ae_driver_setup
101 
102  !-----------------------------------------------------------------------------
104  subroutine atmos_phy_ae_driver_resume
105 ! use mod_atmos_admin, only: &
106 ! ATMOS_sw_phy_ae
107  implicit none
108 
109  ! note: tentatively, aerosol module should be called at all time. we need dummy subprogram.
110 ! if ( ATMOS_sw_phy_ae ) then
111 
112  ! run once (only for the diagnostic value)
113  call prof_rapstart('ATM_Aerosol', 1)
114  call atmos_phy_ae_driver( update_flag = .true. )
115  call prof_rapend ('ATM_Aerosol', 1)
116 
117 ! endif
118 
119  return
120  end subroutine atmos_phy_ae_driver_resume
121 
122  !-----------------------------------------------------------------------------
124  subroutine atmos_phy_ae_driver( update_flag )
125  use scale_time, only: &
126  dt_ae => time_dtsec_atmos_phy_ae
127  use scale_rm_statistics, only: &
129  stat_total
130  use scale_history, only: &
131  hist_in
132  use scale_atmos_phy_ae, only: &
133  atmos_phy_ae, &
134  qa_ae, &
135  qs_ae, &
136  qe_ae
137  use mod_atmos_vars, only: &
138  dens => dens_av, &
139  momz => momz_av, &
140  momx => momx_av, &
141  momy => momy_av, &
142  rhot => rhot_av, &
143  qtrc => qtrc_av, &
144  rhoq_t => rhoq_tp
145  use mod_atmos_phy_ae_vars, only: &
146  rhoq_t_ae => atmos_phy_ae_rhoq_t, &
147  ccn => atmos_phy_ae_ccn, &
148  ccn_t => atmos_phy_ae_ccn_t, &
149  ae_emit => atmos_phy_ae_emit
150  use mod_atmos_phy_mp_vars, only: &
151  evaporate => atmos_phy_mp_evaporate
152  implicit none
153 
154  logical, intent(in) :: update_flag
155 
156  real(RP) :: cn(ka,ia,ja)
157  real(RP) :: nreg(ka,ia,ja)
158 
159  real(RP) :: total ! dummy
160 
161  integer :: k, i, j, iq
162  !---------------------------------------------------------------------------
163 
164  if ( update_flag ) then
165 
166 !OCL XFILL
167  ccn(:,:,:) = 0.0_rp ! reset
168 !OCL XFILL
169  ccn_t(:,:,:) = 0.0_rp ! reset
170 !OCL XFILL
171  rhoq_t_ae(:,:,:,:) = 0.0_rp ! reset
172 
173  do j = js, je
174  do i = is, ie
175  do k = ks, ke
176  nreg(k,i,j) = evaporate(k,i,j) * dt_ae
177  enddo
178  enddo
179  enddo
180 
181  call atmos_phy_ae( qa_ae, & ! [IN]
182  dens, & ! [IN]
183  momz, & ! [IN]
184  momx, & ! [IN]
185  momy, & ! [IN]
186  rhot, & ! [IN]
187  ae_emit, & ! [IN]
188  nreg, & ! [IN]
189  qtrc, & ! [INOUT]
190  cn , & ! [OUT]
191  ccn, & ! [OUT]
192  rhoq_t_ae ) ! [INOUT]
193 
194  ccn_t(:,:,:) = ccn(:,:,:) / dt_ae
195 
196  call hist_in( cn(:,:,:)*1.e-6_rp, 'CN', 'condensation nucrei', 'num/cc' )
197  call hist_in( ccn(:,:,:)*1.e-6_rp, 'CCN', 'cloud condensation nucrei', 'num/cc' )
198 
199  endif
200 
201  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(3)
202  do iq = qs_ae, qe_ae
203  do j = js, je
204  do i = is, ie
205  do k = ks, ke
206  rhoq_t(k,i,j,iq) = rhoq_t(k,i,j,iq) + rhoq_t_ae(k,i,j,iq)
207  enddo
208  enddo
209  enddo
210  enddo
211 
212  if ( statistics_checktotal ) then
213  do iq = qs_ae, qe_ae
214  call stat_total( total, rhoq_t_ae(:,:,:,iq), trim(tracer_name(iq))//'_t_AE' )
215  enddo
216  endif
217 
218  return
219  end subroutine atmos_phy_ae_driver
220 
221 end module mod_atmos_phy_ae_driver
module ATMOS admin
integer, public is
start point of inner domain: x, local
logical, public statistics_checktotal
calc&report variable totals to logfile?
real(rp), dimension(:,:,:), allocatable, target, public momz
integer, public je
end point of inner domain: y, local
subroutine, public atmos_phy_ae_driver_setup
Setup.
module ATMOSPHERE / Physics Aerosol Microphysics
subroutine, public atmos_phy_ae_driver(update_flag)
Driver.
real(rp), dimension(:,:,:), allocatable, target, public rhot
module Atmosphere / Physics Cloud Microphysics
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:61
procedure(ae), pointer, public atmos_phy_ae
module ATMOSPHERIC Variables
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
real(rp), dimension(:,:,:), allocatable, target, public momx
module STDIO
Definition: scale_stdio.F90:12
integer, public ke
end point of inner domain: z, local
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
module Statistics
module grid index
real(rp), dimension(:,:,:), pointer, public momx_av
module TRACER
integer, public ia
of whole cells: x, local, with HALO
integer, public ka
of whole cells: z, local, with HALO
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_ae_emit
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
integer, public js
start point of inner domain: y, local
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_ae_rhoq_t
subroutine, public atmos_phy_ae_config(AE_TYPE)
Setup.
real(rp), dimension(:,:,:), allocatable, public atmos_phy_ae_ccn
real(rp), dimension(:,:,:), pointer, public dens_av
procedure(su), pointer, public atmos_phy_ae_setup
real(dp), public time_dtsec_atmos_phy_ae
time interval of physics(aerosol ) [sec]
Definition: scale_time.F90:46
subroutine, public atmos_phy_ae_driver_resume
Resume.
integer, public ks
start point of inner domain: z, local
real(rp), dimension(:,:,:), allocatable, target, public momy
real(rp), dimension(:,:,:), allocatable, public atmos_phy_mp_evaporate
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:156
module profiler
Definition: scale_prof.F90:10
integer, public ie
end point of inner domain: x, local
module PRECISION
module HISTORY
real(rp), dimension(:,:,:), pointer, public momz_av
subroutine, public atmos_phy_ae_driver_config
Config.
real(rp), dimension(:,:,:), pointer, public rhot_av
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
real(rp), dimension(:,:,:), pointer, public momy_av
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:204
module ATMOSPHERE / Physics Aerosol Microphysics
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
real(rp), dimension(:,:,:), allocatable, public atmos_phy_ae_ccn_t
integer, public ja
of whole cells: y, local, with HALO