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  !
33  public :: atmos_phy_ae_driver
34 
35  !-----------------------------------------------------------------------------
36  !
37  !++ Public parameters & variables
38  !
39  !-----------------------------------------------------------------------------
40  !
41  !++ Private procedure
42  !
43  !-----------------------------------------------------------------------------
44  !
45  !++ Private parameters & variables
46  !
47  !-----------------------------------------------------------------------------
48 contains
49  !-----------------------------------------------------------------------------
51  subroutine atmos_phy_ae_driver_setup
52  use scale_atmos_phy_ae, only: &
54  use mod_atmos_admin, only: &
56 ! ATMOS_sw_phy_ae
57  implicit none
58  !---------------------------------------------------------------------------
59 
60  if( io_l ) write(io_fid_log,*)
61  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[ATMOS PHY_AE] / Origin[SCALE-RM]'
62 
63  ! note: tentatively, aerosol module should be called at all time. we need dummy subprogram.
64 ! if ( ATMOS_sw_phy_ae ) then
65 
66  ! setup library component
68 
69 ! else
70 ! if( IO_L ) write(IO_FID_LOG,*) '*** this component is never called.'
71 ! endif
72 
73  return
74  end subroutine atmos_phy_ae_driver_setup
75 
76  !-----------------------------------------------------------------------------
79 ! use mod_atmos_admin, only: &
80 ! ATMOS_sw_phy_ae
81  implicit none
82 
83  ! note: tentatively, aerosol module should be called at all time. we need dummy subprogram.
84 ! if ( ATMOS_sw_phy_ae ) then
85 
86  ! run once (only for the diagnostic value)
87  call prof_rapstart('ATM_Aerosol', 1)
88  call atmos_phy_ae_driver( update_flag = .true. )
89  call prof_rapend ('ATM_Aerosol', 1)
90 
91 ! endif
92 
93  return
94  end subroutine atmos_phy_ae_driver_resume
95 
96  !-----------------------------------------------------------------------------
98  subroutine atmos_phy_ae_driver( update_flag )
99  use scale_time, only: &
100  dt_ae => time_dtsec_atmos_phy_ae
101  use scale_rm_statistics, only: &
103  stat_total
104  use scale_history, only: &
105  hist_in
106  use scale_atmos_phy_ae, only: &
108  use mod_atmos_vars, only: &
109  dens, &
110  momz, &
111  momx, &
112  momy, &
113  rhot, &
114  qtrc, &
115  rhoq_t => rhoq_tp
116  use mod_atmos_phy_ae_vars, only: &
117  rhoq_t_ae => atmos_phy_ae_rhoq_t, &
118  ccn => atmos_phy_ae_ccn, &
119  ccn_t => atmos_phy_ae_ccn_t, &
120  ae_emit => atmos_phy_ae_emit
121  use mod_atmos_phy_mp_vars, only: &
122  evaporate => atmos_phy_mp_evaporate
123  implicit none
124 
125  logical, intent(in) :: update_flag
126 
127  real(RP) :: CN(ka,ia,ja)
128  real(RP) :: NREG(ka,ia,ja)
129 
130  real(RP) :: total ! dummy
131 
132  integer :: k, i, j, iq
133  !---------------------------------------------------------------------------
134 
135  if ( update_flag ) then
136 
137 !OCL XFILL
138  ccn(:,:,:) = 0.0_rp ! reset
139 !OCL XFILL
140  ccn_t(:,:,:) = 0.0_rp ! reset
141 !OCL XFILL
142  rhoq_t_ae(:,:,:,:) = 0.0_rp ! reset
143 
144  nreg(:,:,:) = evaporate(:,:,:) * dt_ae
145 
146  call atmos_phy_ae( dens, & ! [IN]
147  momz, & ! [IN]
148  momx, & ! [IN]
149  momy, & ! [IN]
150  rhot, & ! [IN]
151  ae_emit, & ! [IN]
152  nreg, & ! [IN]
153  qtrc, & ! [INOUT]
154  cn , & ! [OUT]
155  ccn, & ! [OUT]
156  rhoq_t_ae ) ! [INOUT]
157 
158  ccn_t(:,:,:) = ccn(:,:,:) / dt_ae
159 
160  call hist_in( cn(:,:,:)*1.e-6_rp, 'CN', 'condensation nucrei', 'num/cc' )
161  call hist_in( ccn(:,:,:)*1.e-6_rp, 'CCN', 'cloud condensation nucrei', 'num/cc' )
162 
163  endif
164 
165  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(3)
166  do iq = 1, qa
167  do j = js, je
168  do i = is, ie
169  do k = ks, ke
170  rhoq_t(k,i,j,iq) = rhoq_t(k,i,j,iq) + rhoq_t_ae(k,i,j,iq)
171  enddo
172  enddo
173  enddo
174  enddo
175 
176  if ( statistics_checktotal ) then
177  do iq = 1, qa
178  call stat_total( total, rhoq_t_ae(:,:,:,iq), trim(aq_name(iq))//'_t_AE' )
179  enddo
180  endif
181 
182  return
183  end subroutine atmos_phy_ae_driver
184 
185 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:59
procedure(ae), pointer, public atmos_phy_ae
module ATMOSPHERIC Variables
real(rp), dimension(:,:,:), allocatable, target, public momx
module STDIO
Definition: scale_stdio.F90:12
integer, public ke
end point of inner domain: z, local
integer, public qa
character(len=h_short), public atmos_phy_ae_type
real(rp), dimension(:,:,:), allocatable, target, public dens
module ATMOSPHERE / Physics Aerosol Microphysics
module Statistics
module grid index
module TRACER
integer, public ia
of x whole cells (local, with HALO)
integer, public ka
of z whole cells (local, with HALO)
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_ae_emit
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
character(len=h_short), dimension(:), allocatable, public aq_name
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
real(rp), dimension(:,:,:), allocatable, public atmos_phy_ae_ccn
subroutine, public atmos_phy_ae_setup(AE_TYPE)
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:132
module profiler
Definition: scale_prof.F90:10
integer, public ie
end point of inner domain: x, local
module PRECISION
module HISTORY
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:178
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 y whole cells (local, with HALO)