SCALE-RM
Functions/Subroutines
scale_atmos_phy_ae_offline Module Reference

module atmosphere / physics / aerosol / offline More...

Functions/Subroutines

subroutine, public atmos_phy_ae_offline_setup
 Setup. More...
 
subroutine, public atmos_phy_ae_offline_tendency (KA, KS, KE, IA, IS, IE, JA, JS, JE, time_now, CCN)
 Aerosol Microphysics. More...
 
subroutine, public atmos_phy_ae_offline_effective_radius (KA, IA, JA, RH, Re)
 Calculate Effective Radius. More...
 
subroutine, public atmos_phy_ae_offline_qtrc2qaero (KA, IA, JA, time_now, Qe)
 Calculate Effective Radius. More...
 
subroutine, public atmos_phy_ae_offline_mkinit (KA, KS, KE, IA, IS, IE, JA, JS, JE, ccn_init, CCN)
 

Detailed Description

module atmosphere / physics / aerosol / offline

Description
offline aerosol microphysics scheme
Author
Team SCALE
NAMELIST
  • PARAM_ATMOS_PHY_AE_OFFLINE
    nametypedefault valuecomment
    ATMOS_PHY_AE_OFFLINE_BASENAME character(len=H_LONG) ''
    ATMOS_PHY_AE_OFFLINE_BASENAME_ADD_NUM logical .false.
    ATMOS_PHY_AE_OFFLINE_NUMBER_OF_FILES integer 1
    ATMOS_PHY_AE_OFFLINE_AXISTYPE character(len=H_SHORT) 'XYZ'
    ATMOS_PHY_AE_OFFLINE_ENABLE_PERIODIC_YEAR logical .false.
    ATMOS_PHY_AE_OFFLINE_ENABLE_PERIODIC_MONTH logical .false.
    ATMOS_PHY_AE_OFFLINE_ENABLE_PERIODIC_DAY logical .false.
    ATMOS_PHY_AE_OFFLINE_STEP_FIXED integer 0
    ATMOS_PHY_AE_OFFLINE_OFFSET real(RP) 0.0_RP
    ATMOS_PHY_AE_OFFLINE_DEFVAL real(RP) = UNDEF
    ATMOS_PHY_AE_OFFLINE_CHECK_COORDINATES logical .true.
    ATMOS_PHY_AE_OFFLINE_STEP_LIMIT integer 0
    ATMOS_PHY_AE_OFFLINE_CONST_OUTQLD01 real(RP)
    ATMOS_PHY_AE_OFFLINE_CONST_OUTQLD02 real(RP)
    ATMOS_PHY_AE_OFFLINE_CONST_OUTQLD03 real(RP)
    ATMOS_PHY_AE_OFFLINE_CONST_OUTQLD04 real(RP)
    ATMOS_PHY_AE_OFFLINE_CONST_OUTQLD05 real(RP)
    ATMOS_PHY_AE_OFFLINE_CONST_OUTQLD06 real(RP)
    ATMOS_PHY_AE_OFFLINE_CONST_OUTQLD07 real(RP)
    ATMOS_PHY_AE_OFFLINE_CONST_UNCCN real(RP)

History Output
No history output

Function/Subroutine Documentation

◆ atmos_phy_ae_offline_setup()

subroutine, public scale_atmos_phy_ae_offline::atmos_phy_ae_offline_setup

Setup.

Definition at line 67 of file scale_atmos_phy_ae_offline.F90.

67  use scale_prc, only: &
68  prc_abort
69  use scale_file_external_input, only: &
71  use scale_const, only: &
72  undef => const_undef
73  implicit none
74 
75  character(len=H_LONG) :: ATMOS_PHY_AE_offline_basename = ''
76  logical :: ATMOS_PHY_AE_offline_basename_add_num = .false.
77  integer :: ATMOS_PHY_AE_offline_number_of_files = 1
78  character(len=H_SHORT) :: ATMOS_PHY_AE_offline_axistype = 'XYZ'
79  logical :: ATMOS_PHY_AE_offline_enable_periodic_year = .false.
80  logical :: ATMOS_PHY_AE_offline_enable_periodic_month = .false.
81  logical :: ATMOS_PHY_AE_offline_enable_periodic_day = .false.
82  integer :: ATMOS_PHY_AE_offline_step_fixed = 0
83  real(RP) :: ATMOS_PHY_AE_offline_offset = 0.0_rp
84  real(RP) :: ATMOS_PHY_AE_offline_defval ! = UNDEF
85  logical :: ATMOS_PHY_AE_offline_check_coordinates = .true.
86  integer :: ATMOS_PHY_AE_offline_step_limit = 0
87 
88  real(RP) :: ATMOS_PHY_AE_offline_const_outqld01
89  real(RP) :: ATMOS_PHY_AE_offline_const_outqld02
90  real(RP) :: ATMOS_PHY_AE_offline_const_outqld03
91  real(RP) :: ATMOS_PHY_AE_offline_const_outqld04
92  real(RP) :: ATMOS_PHY_AE_offline_const_outqld05
93  real(RP) :: ATMOS_PHY_AE_offline_const_outqld06
94  real(RP) :: ATMOS_PHY_AE_offline_const_outqld07
95  real(RP) :: ATMOS_PHY_AE_offline_const_unccn
96 
97  namelist / param_atmos_phy_ae_offline / &
98  atmos_phy_ae_offline_basename, &
99  atmos_phy_ae_offline_basename_add_num, &
100  atmos_phy_ae_offline_number_of_files, &
101  atmos_phy_ae_offline_axistype, &
102  atmos_phy_ae_offline_enable_periodic_year, &
103  atmos_phy_ae_offline_enable_periodic_month, &
104  atmos_phy_ae_offline_enable_periodic_day, &
105  atmos_phy_ae_offline_step_fixed, &
106  atmos_phy_ae_offline_offset, &
107  atmos_phy_ae_offline_defval, &
108  atmos_phy_ae_offline_check_coordinates, &
109  atmos_phy_ae_offline_step_limit, &
110  atmos_phy_ae_offline_const_outqld01, &
111  atmos_phy_ae_offline_const_outqld02, &
112  atmos_phy_ae_offline_const_outqld03, &
113  atmos_phy_ae_offline_const_outqld04, &
114  atmos_phy_ae_offline_const_outqld05, &
115  atmos_phy_ae_offline_const_outqld06, &
116  atmos_phy_ae_offline_const_outqld07, &
117  atmos_phy_ae_offline_const_unccn
118 
119  integer :: n, ierr
120  !---------------------------------------------------------------------------
121 
122  log_newline
123  log_info("ATMOS_PHY_AE_offline_setup",*) 'Setup'
124  log_info("ATMOS_PHY_AE_offline_setup",*) 'Kajino(2013) scheme'
125 
126  atmos_phy_ae_offline_defval = undef
127 
128  atmos_phy_ae_offline_const_outqld01 = undef
129  atmos_phy_ae_offline_const_outqld02 = undef
130  atmos_phy_ae_offline_const_outqld03 = undef
131  atmos_phy_ae_offline_const_outqld04 = undef
132  atmos_phy_ae_offline_const_outqld05 = undef
133  atmos_phy_ae_offline_const_outqld06 = undef
134  atmos_phy_ae_offline_const_outqld07 = undef
135  atmos_phy_ae_offline_const_unccn = undef
136 
137  !--- read namelist
138  rewind(io_fid_conf)
139  read(io_fid_conf,nml=param_atmos_phy_ae_offline,iostat=ierr)
140  if( ierr < 0 ) then !--- missing
141  log_info("ATMOS_PHY_AE_offline_setup",*) 'Not found namelist. Default used.'
142  elseif( ierr > 0 ) then !--- fatal error
143  log_error("ATMOS_PHY_AE_offline_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_PHY_AE_offline. Check!'
144  call prc_abort
145  endif
146  log_nml(param_atmos_phy_ae_offline)
147 
148  const_value(1) = atmos_phy_ae_offline_const_outqld01
149  const_value(2) = atmos_phy_ae_offline_const_outqld02
150  const_value(3) = atmos_phy_ae_offline_const_outqld03
151  const_value(4) = atmos_phy_ae_offline_const_outqld04
152  const_value(5) = atmos_phy_ae_offline_const_outqld05
153  const_value(6) = atmos_phy_ae_offline_const_outqld06
154  const_value(7) = atmos_phy_ae_offline_const_outqld07
155  const_value(8) = atmos_phy_ae_offline_const_unccn
156 
157  do n = 1, num_vars_3d
158 
159  if ( const_value(n) < undef*0.1 ) then ! read from external file
160 
161  if ( atmos_phy_ae_offline_basename /= '' ) then
162  call file_external_input_regist( atmos_phy_ae_offline_basename, & ! [IN]
163  atmos_phy_ae_offline_basename_add_num, & ! [IN]
164  atmos_phy_ae_offline_number_of_files, & ! [IN]
165  vars_3d(n), & ! [IN]
166  atmos_phy_ae_offline_axistype, & ! [IN]
167  atmos_phy_ae_offline_enable_periodic_year, & ! [IN]
168  atmos_phy_ae_offline_enable_periodic_month, & ! [IN]
169  atmos_phy_ae_offline_enable_periodic_day, & ! [IN]
170  atmos_phy_ae_offline_step_fixed, & ! [IN]
171  atmos_phy_ae_offline_offset, & ! [IN]
172  atmos_phy_ae_offline_defval, & ! [IN]
173  check_coordinates = atmos_phy_ae_offline_check_coordinates, & ! [IN]
174  step_limit = atmos_phy_ae_offline_step_limit ) ! [IN]
175  endif
176 
177  else ! set constant value
178 
179  log_info("ATMOS_PHY_AE_offline_setup",*) &
180  'Constant value is set for ', trim(vars_3d(n)), ', value = ', const_value(n)
181 
182  endif
183 
184  enddo
185 
186  return

References scale_const::const_undef, scale_file_external_input::file_external_input_regist(), scale_io::io_fid_conf, and scale_prc::prc_abort().

Referenced by mod_atmos_phy_ae_driver::atmos_phy_ae_driver_setup(), and atmos_phy_ae_offline_mkinit().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_ae_offline_tendency()

subroutine, public scale_atmos_phy_ae_offline::atmos_phy_ae_offline_tendency ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
real(dp), intent(in)  time_now,
real(rp), dimension(ka,ia,ja), intent(out)  CCN 
)

Aerosol Microphysics.

Definition at line 197 of file scale_atmos_phy_ae_offline.F90.

197  use scale_prc, only: &
198  prc_abort
199  use scale_file_external_input, only: &
200  file_external_input_update
201  use scale_const, only: &
202  undef => const_undef
203  implicit none
204 
205  integer, intent(in) :: KA, KS, KE
206  integer, intent(in) :: IA, IS, IE
207  integer, intent(in) :: JA, JS, JE
208  real(DP), intent(in) :: time_now
209  real(RP), intent(out) :: CCN(KA,IA,JA)
210 
211  logical :: error
212  integer :: n
213  !---------------------------------------------------------------------------
214 
215  log_progress(*) 'atmosphere / physics / aerosol / offline'
216 
217  n = 8 ! UNCCN
218 
219  if ( const_value(n) < undef*0.1 ) then ! read from external file
220 
221  call file_external_input_update( vars_3d(n), time_now, ccn(:,:,:), error )
222  if ( error ) then
223  log_error("ATMOS_PHY_AE_offline_flux",*) 'Requested data is not found! ', trim(vars_3d(n))
224  call prc_abort
225  endif
226 
227  else ! set constant value
228 
229  ccn(:,:,:) = const_value(n)
230 
231  endif
232 
233  return

References scale_const::const_undef, and scale_prc::prc_abort().

Referenced by mod_atmos_phy_ae_driver::atmos_phy_ae_driver_calc_tendency().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_ae_offline_effective_radius()

subroutine, public scale_atmos_phy_ae_offline::atmos_phy_ae_offline_effective_radius ( integer, intent(in)  KA,
integer, intent(in)  IA,
integer, intent(in)  JA,
real(rp), dimension(ka,ia,ja), intent(in)  RH,
real(rp), dimension(ka,ia,ja,n_ae), intent(out)  Re 
)

Calculate Effective Radius.

Definition at line 242 of file scale_atmos_phy_ae_offline.F90.

242  implicit none
243 
244  integer, intent(in) :: KA, IA, JA
245  real(RP), intent(in) :: RH(KA,IA,JA) ! relative humidity [%]
246  real(RP), intent(out) :: Re(KA,IA,JA,N_AE) ! effective radius
247 
248  real(RP), parameter :: AE_Re(N_AE) = & ! aerosol radius [m]
249  (/ 1.6e-6_rp, & ! Soil dust
250  -1.0_rp, & ! Carbonacerous (BC/OC=0.3)
251  -1.0_rp, & ! Carbonacerous (BC/OC=0.15)
252  -1.0_rp, & ! Carbonacerous (BC/OC=0.)
253  4.e-8_rp, & ! Black carbon
254  -1.0_rp, & ! Sulfate
255  -1.0_rp /) ! Sea salt
256 
257  integer :: iaero
258  !---------------------------------------------------------------------------
259 
260  do iaero = 1, n_ae
261 
262  if ( ae_re(iaero) < 0.0_rp ) then ! hygroscopic particle : look-up table is based on the RH
263 
264  re(:,:,:,iaero) = rh(:,:,:) * 1.e-2_rp
265 
266  else ! non-hygroscopic particle : look-up table is the effective radius
267 
268  re(:,:,:,iaero) = ae_re(iaero) * 100.0_rp ! [m=>cm]
269 
270  endif
271 
272  enddo
273 
274  return

References scale_atmos_aerosol::n_ae.

Referenced by mod_atmos_phy_ae_vars::atmos_phy_ae_vars_get_diagnostic().

Here is the caller graph for this function:

◆ atmos_phy_ae_offline_qtrc2qaero()

subroutine, public scale_atmos_phy_ae_offline::atmos_phy_ae_offline_qtrc2qaero ( integer, intent(in)  KA,
integer, intent(in)  IA,
integer, intent(in)  JA,
real(dp), intent(in)  time_now,
real(rp), dimension(ka,ia,ja,n_ae), intent(out)  Qe 
)

Calculate Effective Radius.

Definition at line 283 of file scale_atmos_phy_ae_offline.F90.

283  use scale_prc, only: &
284  prc_abort
285  use scale_file_external_input, only: &
286  file_external_input_update
287  use scale_const, only: &
288  undef => const_undef
289  implicit none
290 
291  integer, intent(in) :: KA, IA, JA
292  real(DP), intent(in) :: time_now
293  real(RP), intent(out) :: Qe(KA,IA,JA,N_AE) ! aerosol mixing ratio [kg/kg]
294 
295  logical :: error, error_sum
296  integer :: n, iaero
297  !---------------------------------------------------------------------------
298 
299  error_sum = .false.
300 
301  do n = 1, num_vars_3d-1
302  iaero = n
303 
304  if ( const_value(n) < undef*0.1 ) then ! read from external file
305 
306  call file_external_input_update( vars_3d(n), time_now, qe(:,:,:,iaero), error )
307  error_sum = ( error .OR. error_sum )
308 
309  else ! set constant value
310 
311  qe(:,:,:,iaero) = const_value(n)
312 
313  endif
314 
315  enddo
316 
317  if ( error_sum ) then
318  log_error("ATMOS_PHY_AE_offline_flux",*) 'Requested data is not found!'
319  call prc_abort
320  endif
321 
322  return

References scale_const::const_undef, and scale_prc::prc_abort().

Referenced by mod_atmos_phy_ae_vars::atmos_phy_ae_vars_get_diagnostic().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_ae_offline_mkinit()

subroutine, public scale_atmos_phy_ae_offline::atmos_phy_ae_offline_mkinit ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
real(rp), intent(in)  ccn_init,
real(rp), dimension(ka,ia,ja), intent(out)  CCN 
)

Definition at line 332 of file scale_atmos_phy_ae_offline.F90.

332  use scale_const, only: &
333  undef => const_undef
334  implicit none
335 
336  integer, intent(in) :: KA, KS, KE
337  integer, intent(in) :: IA, IS, IE
338  integer, intent(in) :: JA, JS, JE
339  real(RP), intent(in) :: ccn_init
340  real(RP), intent(out) :: CCN(KA,IA,JA)
341 
342  integer :: n
343  !---------------------------------------------------------------------------
344 
345  call atmos_phy_ae_offline_setup
346 
347  n = 8 ! UNCCN
348 
349  if ( const_value(n) < undef*0.1 ) then ! read from external file
350 
351  ccn(:,:,:) = ccn_init
352 
353  else ! set constant value
354 
355  ccn(:,:,:) = const_value(n)
356 
357  endif
358 
359  return

References atmos_phy_ae_offline_setup(), and scale_const::const_undef.

Referenced by mod_mkinit::rect_setup().

Here is the call graph for this function:
Here is the caller graph for this function:
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
scale_file_external_input::file_external_input_regist
subroutine, public file_external_input_regist(basename, basename_add_num, number_of_files, varname, axistype, enable_periodic_year, enable_periodic_month, enable_periodic_day, step_fixed, offset, defval, check_coordinates, aggregate, allow_missing, step_limit, exist)
Regist data.
Definition: scale_file_external_input.F90:324
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_file_external_input
module file / external_input
Definition: scale_file_external_input.F90:12
scale_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:41