SCALE-RM
Data Types | Functions/Subroutines | Variables
scale_atmos_thermodyn Module Reference

module ATMOSPHERE / Thermodynamics More...

Functions/Subroutines

subroutine, public atmos_thermodyn_setup
 Setup. More...
 
subroutine atmos_thermodyn_qd_0d (qdry, q)
 calc dry air mass (0D) More...
 
subroutine, public atmos_thermodyn_tempre (temp, pres, Ein, dens, qdry, q)
 
subroutine, public atmos_thermodyn_tempre2 (temp, pres, dens, pott, qdry, q)
 

Variables

real(rp), public thermodyn_emask = 0.0_RP
 =0: SIMPLE, 1: EXACT More...
 
real(rp), dimension(:), allocatable, public aq_cp
 CP for each hydrometeors [J/kg/K]. More...
 
real(rp), dimension(:), allocatable, public aq_cv
 CV for each hydrometeors [J/kg/K]. More...
 

Detailed Description

module ATMOSPHERE / Thermodynamics

Description
Thermodynamics module
Author
Team SCALE
History
  • 2011-10-24 (T.Seiki) [new] Import from NICAM
  • 2012-02-10 (H.Yashiro) [mod] Reconstruction
  • 2012-03-23 (H.Yashiro) [mod] Explicit index parameter inclusion
  • 2012-12-22 (S.Nishizawa) [mod] Use thermodyn macro set

Function/Subroutine Documentation

◆ atmos_thermodyn_setup()

subroutine, public scale_atmos_thermodyn::atmos_thermodyn_setup ( )

Setup.

Definition at line 159 of file scale_atmos_sub_thermodyn.F90.

References aq_cp, aq_cv, scale_const::const_ci, scale_const::const_cl, scale_const::const_cpvap, scale_const::const_cvvap, scale_const::const_thermodyn_type, scale_tracer::i_qv, scale_stdio::io_fid_log, scale_stdio::io_l, scale_process::prc_mpistop(), scale_tracer::qie, scale_tracer::qis, scale_tracer::qqa, scale_tracer::qwe, scale_tracer::qws, and thermodyn_emask.

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

159  use scale_process, only: &
161  use scale_const, only: &
162  cpvap => const_cpvap, &
163  cvvap => const_cvvap, &
164  cl => const_cl, &
165  ci => const_ci, &
166  thermodyn_type => const_thermodyn_type
167  implicit none
168 
169  integer :: n
170  !---------------------------------------------------------------------------
171 
172  if( io_l ) write(io_fid_log,*)
173  if( io_l ) write(io_fid_log,*) '++++++ Module[THERMODYN] / Categ[ATMOS SHARE] / Origin[SCALElib]'
174 
175  allocate( aq_cp(qqa) )
176  allocate( aq_cv(qqa) )
177 
178  if ( thermodyn_type == 'EXACT' ) then
179  thermodyn_emask = 1.0_rp
180 
181  aq_cp(i_qv) = cpvap
182  aq_cv(i_qv) = cvvap
183 
184  if ( qws /= 0 ) then
185  do n = qws, qwe
186  aq_cp(n) = cl
187  aq_cv(n) = cl
188  enddo
189  endif
190 
191  if ( qis /= 0 ) then
192  do n = qis, qie
193  aq_cp(n) = ci
194  aq_cv(n) = ci
195  enddo
196  endif
197  elseif( thermodyn_type == 'SIMPLE' ) then
198  thermodyn_emask = 0.0_rp
199 
200  aq_cp(i_qv) = cpdry
201  aq_cv(i_qv) = cvdry
202 
203  if ( qws /= 0 ) then
204  do n = qws, qwe
205  aq_cp(n) = cvdry
206  aq_cv(n) = cvdry
207  enddo
208  endif
209 
210  if ( qis /= 0 ) then
211  do n = qis, qie
212  aq_cp(n) = cvdry
213  aq_cv(n) = cvdry
214  enddo
215  endif
216  endif
217 
218  return
integer, public qie
subroutine, public prc_mpistop
Abort MPI.
real(rp), parameter, public const_ci
specific heat (ice) [J/kg/K]
Definition: scale_const.F90:69
integer, public qwe
real(rp), parameter, public const_cl
specific heat (liquid water) [J/kg/K]
Definition: scale_const.F90:68
integer, public qws
real(rp), public const_cvvap
specific heat (water vapor, constant volume) [J/kg/K]
Definition: scale_const.F90:67
integer, public qis
integer, public i_qv
integer, public qqa
module PROCESS
module CONSTANT
Definition: scale_const.F90:14
real(rp), parameter, public const_cpvap
specific heat (water vapor, constant pressure) [J/kg/K]
Definition: scale_const.F90:66
character(len=h_short), public const_thermodyn_type
internal energy type
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_thermodyn_qd_0d()

subroutine scale_atmos_thermodyn::atmos_thermodyn_qd_0d ( real(rp), intent(out)  qdry,
real(rp), dimension(qa), intent(in)  q 
)

calc dry air mass (0D)

Parameters
[out]qdrydry mass concentration [kg/kg]
[in]qmass concentration [kg/kg]

Definition at line 226 of file scale_atmos_sub_thermodyn.F90.

References aq_cp, aq_cv, scale_tracer::i_qc, scale_tracer::i_qg, scale_tracer::i_qi, scale_tracer::i_qr, scale_tracer::i_qs, scale_tracer::i_qv, scale_grid_index::ieb, scale_grid_index::isb, scale_grid_index::jeb, scale_grid_index::jsb, scale_grid_index::ke, scale_grid_index::ks, dc_log::log(), scale_tracer::qqe, scale_tracer::qqs, and thermodyn_emask.

226  implicit none
227 
228  real(RP), intent(out) :: qdry
229  real(RP), intent(in) :: q(qa)
230 
231  integer :: iqw
232  !-----------------------------------------------------------------------------
233 
234  qdry = 1.0_rp
235 #ifndef DRY
236  do iqw = qqs, qqe
237  qdry = qdry - q(iqw)
238  enddo
239 #endif
240 
241  return
integer, public qqe
integer, public qa
integer, public qqs
Here is the call graph for this function:

◆ atmos_thermodyn_tempre()

subroutine, public scale_atmos_thermodyn::atmos_thermodyn_tempre ( real(rp), dimension(ka,ia,ja), intent(out)  temp,
real(rp), dimension(ka,ia,ja), intent(out)  pres,
real(rp), dimension (ka,ia,ja), intent(in)  Ein,
real(rp), dimension(ka,ia,ja), intent(in)  dens,
real(rp), dimension(ka,ia,ja), intent(in)  qdry,
real(rp), dimension (ka,ia,ja,qa), intent(in)  q 
)

Definition at line 1282 of file scale_atmos_sub_thermodyn.F90.

References aq_cv, scale_tracer::i_qv, scale_grid_index::ieb, scale_grid_index::isb, scale_grid_index::jeb, scale_grid_index::jsb, scale_grid_index::ke, and scale_grid_index::ks.

1282  implicit none
1283 
1284  real(RP), intent(out) :: temp(ka,ia,ja) ! temperature
1285  real(RP), intent(out) :: pres(ka,ia,ja) ! pressure
1286  real(RP), intent(in) :: ein (ka,ia,ja) ! internal energy
1287  real(RP), intent(in) :: dens(ka,ia,ja) ! density
1288  real(RP), intent(in) :: qdry(ka,ia,ja) ! dry concentration
1289  real(RP), intent(in) :: q (ka,ia,ja,qa) ! water concentration
1290 
1291  real(RP) :: cv, rmoist
1292 
1293  integer :: i, j, k, iqw
1294  !---------------------------------------------------------------------------
1295 
1296  !$omp parallel do private(i,j,k,iqw,cv,Rmoist) OMP_SCHEDULE_ collapse(2)
1297  do j = jsb, jeb
1298  do i = isb, ieb
1299  do k = ks, ke
1300 
1301  calc_cv(cv, qdry(k,i,j), q, k, i, j, iqw, cvdry, aq_cv)
1302  calc_r(rmoist, q(k,i,j,i_qv), qdry(k,i,j), rdry, rvap)
1303 
1304  temp(k,i,j) = ein(k,i,j) / cv
1305 
1306  pres(k,i,j) = dens(k,i,j) * rmoist * temp(k,i,j)
1307 
1308  enddo
1309  enddo
1310  enddo
1311 
1312  return
integer, public jeb
integer, public ke
end point of inner domain: z, local
integer, public qa
integer, public ieb
integer, public ia
of x whole cells (local, with HALO)
integer, public ka
of z whole cells (local, with HALO)
integer, public i_qv
integer, public ks
start point of inner domain: z, local
integer, public isb
integer, public jsb
integer, public ja
of y whole cells (local, with HALO)

◆ atmos_thermodyn_tempre2()

subroutine, public scale_atmos_thermodyn::atmos_thermodyn_tempre2 ( real(rp), dimension(ka,ia,ja), intent(out)  temp,
real(rp), dimension(ka,ia,ja), intent(out)  pres,
real(rp), dimension(ka,ia,ja), intent(in)  dens,
real(rp), dimension(ka,ia,ja), intent(in)  pott,
real(rp), dimension(ka,ia,ja), intent(in)  qdry,
real(rp), dimension (ka,ia,ja,qa), intent(in)  q 
)

Definition at line 1319 of file scale_atmos_sub_thermodyn.F90.

References aq_cp, scale_tracer::i_qv, scale_grid_index::ieb, scale_grid_index::isb, scale_grid_index::jeb, scale_grid_index::jsb, scale_grid_index::ke, and scale_grid_index::ks.

1319  implicit none
1320 
1321  real(RP), intent(out) :: temp(ka,ia,ja) ! temperature
1322  real(RP), intent(out) :: pres(ka,ia,ja) ! pressure
1323  real(RP), intent(in) :: dens(ka,ia,ja) ! density
1324  real(RP), intent(in) :: pott(ka,ia,ja) ! potential temperature
1325  real(RP), intent(in) :: qdry(ka,ia,ja) ! dry concentration
1326  real(RP), intent(in) :: q (ka,ia,ja,qa) ! water concentration
1327 
1328  real(RP) :: rmoist, cp
1329 
1330  integer :: i, j, k, iqw
1331  !---------------------------------------------------------------------------
1332 
1333  !$omp parallel do private(i,j,k,iqw,cp,Rmoist) OMP_SCHEDULE_ collapse(2)
1334  do j = jsb, jeb
1335  do i = isb, ieb
1336  do k = ks, ke
1337 
1338  calc_cp(cp, qdry(k,i,j), q, k, i, j, iqw, cpdry, aq_cp)
1339  calc_r(rmoist, q(k,i,j,i_qv), qdry(k,i,j), rdry, rvap)
1340  calc_pre(pres(k,i,j), dens(k,i,j), pott(k,i,j), rmoist, cp, pre00)
1341 
1342  temp(k,i,j) = pres(k,i,j) / ( dens(k,i,j) * rmoist )
1343 
1344  enddo
1345  enddo
1346  enddo
1347 
1348  return
integer, public jeb
integer, public ke
end point of inner domain: z, local
integer, public qa
integer, public ieb
integer, public ia
of x whole cells (local, with HALO)
integer, public ka
of z whole cells (local, with HALO)
integer, public i_qv
integer, public ks
start point of inner domain: z, local
integer, public isb
integer, public jsb
integer, public ja
of y whole cells (local, with HALO)

Variable Documentation

◆ thermodyn_emask

real(rp), public scale_atmos_thermodyn::thermodyn_emask = 0.0_RP

=0: SIMPLE, 1: EXACT

Definition at line 140 of file scale_atmos_sub_thermodyn.F90.

Referenced by atmos_thermodyn_qd_0d(), and atmos_thermodyn_setup().

140  real(RP), public :: thermodyn_emask = 0.0_rp

◆ aq_cp

real(rp), dimension(:), allocatable, public scale_atmos_thermodyn::aq_cp

◆ aq_cv

real(rp), dimension(:), allocatable, public scale_atmos_thermodyn::aq_cv