SCALE-RM
scale_atmos_phy_ae_dummy.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
13 !-------------------------------------------------------------------------------
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  !
31  public :: atmos_phy_ae_dummy_setup
32  public :: atmos_phy_ae_dummy
33 
35 
36  !-----------------------------------------------------------------------------
37  !
38  !++ Public parameters & variables
39  !
40  real(RP), public, allocatable :: ae_dens(:) ! aerosol density [kg/m3]=[g/L]
41 
42  !-----------------------------------------------------------------------------
43  !
44  !++ Private procedure
45  !
46  !-----------------------------------------------------------------------------
47  !
48  !++ Private parameters & variables
49  !
50  !-----------------------------------------------------------------------------
51 contains
52  !-----------------------------------------------------------------------------
54  subroutine atmos_phy_ae_dummy_setup( AE_TYPE )
55  use scale_process, only: &
57  implicit none
58 
59  character(len=*), intent(in) :: AE_TYPE
60  !---------------------------------------------------------------------------
61 
62  if( io_l ) write(io_fid_log,*)
63  if( io_l ) write(io_fid_log,*) '++++++ Module[AEROSOL] / Categ[ATMOS PHYSICS] / Origin[SCALElib]'
64  if( io_l ) write(io_fid_log,*) '+++ dummy aerosol process'
65  if( io_l ) write(io_fid_log,*) '*** No namelists.'
66 
67  if ( ae_type /= 'DUMMY' .AND. ae_type /= 'NONE' ) then
68  write(*,*) 'xxx ATMOS_PHY_AE_TYPE is not DUMMY. Check!'
69  call prc_mpistop
70  endif
71 
72  allocate( ae_dens(ae_qa) )
73  ae_dens(:) = 0.0_rp
74 
75  return
76  end subroutine atmos_phy_ae_dummy_setup
77 
78  !-----------------------------------------------------------------------------
80  subroutine atmos_phy_ae_dummy( &
81  DENS, &
82  MOMZ, &
83  MOMX, &
84  MOMY, &
85  RHOT, &
86  EMIT, &
87  NREG, &
88  QTRC, &
89  CN, &
90  CCN, &
91  RHOQ_t_AE )
93  use scale_tracer
94  implicit none
95  real(RP), intent(inout) :: DENS(ka,ia,ja)
96  real(RP), intent(inout) :: MOMZ(ka,ia,ja)
97  real(RP), intent(inout) :: MOMX(ka,ia,ja)
98  real(RP), intent(inout) :: MOMY(ka,ia,ja)
99  real(RP), intent(inout) :: RHOT(ka,ia,ja)
100  real(RP), intent(inout) :: EMIT(ka,ia,ja,qa_ae)
101  real(RP), intent(in) :: NREG(ka,ia,ja)
102  real(RP), intent(inout) :: QTRC(ka,ia,ja,qa)
103  real(RP), intent(out) :: CN(ka,ia,ja)
104  real(RP), intent(out) :: CCN(ka,ia,ja)
105  real(RP), intent(inout) :: RHOQ_t_AE(ka,ia,ja,qa)
106 
107  if( io_l ) write(io_fid_log,*) '*** Physics step: Aerosol(dummy)'
108 
109  cn(:,:,:) = 0.0_rp
110  ccn(:,:,:) = 0.0_rp
111 
112  return
113  end subroutine atmos_phy_ae_dummy
114 
115  !-----------------------------------------------------------------------------
118  Re, &
119  QTRC, &
120  RH )
122  use scale_tracer
123  use scale_const, only: &
124  undef => const_undef
125  implicit none
126 
127  real(RP), intent(out) :: Re (ka,ia,ja,ae_qa) ! effective radius
128  real(RP), intent(in) :: QTRC(ka,ia,ja,qa) ! tracer mass concentration [kg/kg]
129  real(RP), intent(in) :: RH (ka,ia,ja) ! relative humidity [0-1]
130  !---------------------------------------------------------------------------
131 
132  re(:,:,:,:) = undef
133 
134 ! Re(:,:,:,I_ae_seasalt) = 2.E-4_RP
135 ! Re(:,:,:,I_ae_dust ) = 4.E-6_RP
136 ! Re(:,:,:,I_ae_bc ) = 4.E-8_RP
137 ! Re(:,:,:,I_ae_oc ) = RH(:,:,:)
138 ! Re(:,:,:,I_ae_sulfate) = RH(:,:,:)
139 
140  return
142 
143 end module scale_atmos_phy_ae_dummy
real(rp), dimension(:), allocatable, public ae_dens
subroutine, public atmos_phy_ae_dummy_effectiveradius(Re, QTRC, RH)
Calculate Effective Radius.
integer, public qa_ae
subroutine, public prc_mpistop
Abort MPI.
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
module STDIO
Definition: scale_stdio.F90:12
integer, public qa
real(rp), public const_undef
Definition: scale_const.F90:43
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)
module ATMOSPHERE / Physics Aerosol Microphysics
integer, public ae_qa
module PROCESS
module CONSTANT
Definition: scale_const.F90:14
subroutine, public atmos_phy_ae_dummy_setup(AE_TYPE)
Setup.
module profiler
Definition: scale_prof.F90:10
subroutine, public atmos_phy_ae_dummy(DENS, MOMZ, MOMX, MOMY, RHOT, EMIT, NREG, QTRC, CN, CCN, RHOQ_t_AE)
Aerosol Microphysics.
module PRECISION
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
integer, public ja
of y whole cells (local, with HALO)