SCALE-RM
Functions/Subroutines
mod_atmos_phy_cp_driver Module Reference

module ATMOSPHERE / Physics Cumulus More...

Functions/Subroutines

subroutine, public atmos_phy_cp_driver_setup
 Setup. More...
 
subroutine, public atmos_phy_cp_driver_resume
 Redume. More...
 
subroutine, public atmos_phy_cp_driver (update_flag)
 Driver. More...
 

Detailed Description

module ATMOSPHERE / Physics Cumulus

Description
Cumulus parameterization driver
Author
Team SCALE
History
  • 2014-05-04 (H.Yashiro) [new]
NAMELIST
  • No namelist group
History Output
namedescriptionunitvariable
CBMFX cloud base mass flux kg/m2/s MFLX_cloudbase
CUBASE CP cloud base height m cloudbase
CUMFRC_DP CP cloud fraction (deep) 0-1 cldfrac_dp
CUMFRC_SH CP cloud fraction (shallow) 0-1 cldfrac_sh
CUMHGT CP cloud top height m cloudtop
DENS_t_CP tendency DENS in CP kg/m3/s DENS_t_CP
MOMX_t_CP tendency MOMX in CP kg/m2/s2 MOMX_t_CP
MOMY_t_CP tendency MOMY in CP kg/m2/s2 MOMY_t_CP
MOMZ_t_CP tendency MOMZ in CP kg/m2/s2 MOMZ_t_CP
PREC_CP surface precipitation rate by CP kg/m2/s SFLX_rain
RAIN_CP surface rain rate by CP kg/m2/s SFLX_rain
RHOT_t_CP tendency RHOT in CP K*kg/m3/s RHOT_t_CP
kf_nca advection or cumulus convection timescale for KF s kf_nca
kf_w0avg rannning mean vertical wind velocity for KF kg/m2/s kf_w0avg
trim(AQ_NAME(iq))//'_t_CP' tendency rho*'//trim(AQ_NAME(iq))//'in CP kg/m3/s RHOQ_t_CP

Function/Subroutine Documentation

◆ atmos_phy_cp_driver_setup()

subroutine, public mod_atmos_phy_cp_driver::atmos_phy_cp_driver_setup ( )

Setup.

Definition at line 52 of file mod_atmos_phy_cp_driver.f90.

References scale_atmos_phy_cp::atmos_phy_cp_setup(), mod_atmos_admin::atmos_phy_cp_type, mod_atmos_admin::atmos_sw_phy_cp, scale_stdio::io_fid_log, and scale_stdio::io_l.

Referenced by mod_atmos_driver::atmos_driver_setup().

52  use scale_atmos_phy_cp, only: &
54  use mod_atmos_admin, only: &
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_CP] / Origin[SCALE-RM]'
62 
63  if ( atmos_sw_phy_cp ) then
64 
65  ! setup library component
67 
68  else
69  if( io_l ) write(io_fid_log,*) '*** this component is never called.'
70  endif
71 
72  return
module ATMOS admin
logical, public atmos_sw_phy_cp
subroutine, public atmos_phy_cp_setup(CP_TYPE)
Setup Cumulus parameterization.
module ATMOSPHERE / Physics Cumulus Parameterization
character(len=h_short), public atmos_phy_cp_type
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_cp_driver_resume()

subroutine, public mod_atmos_phy_cp_driver::atmos_phy_cp_driver_resume ( )

Redume.

Definition at line 78 of file mod_atmos_phy_cp_driver.f90.

References atmos_phy_cp_driver(), mod_atmos_admin::atmos_sw_phy_cp, scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by mod_atmos_driver::atmos_driver_resume2().

78  use mod_atmos_admin, only: &
80  implicit none
81 
82  if ( atmos_sw_phy_cp ) then
83 
84  ! run once (only for the diagnostic value)
85  call prof_rapstart('ATM_Cumulus', 1)
86  call atmos_phy_cp_driver( update_flag = .true. )
87  call prof_rapend ('ATM_Cumulus', 1)
88 
89  endif
90 
91  return
module ATMOS admin
logical, public atmos_sw_phy_cp
subroutine, public atmos_phy_cp_driver(update_flag)
Driver.
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_cp_driver()

subroutine, public mod_atmos_phy_cp_driver::atmos_phy_cp_driver ( logical, intent(in)  update_flag)

Driver.

Definition at line 97 of file mod_atmos_phy_cp_driver.f90.

References scale_tracer::aq_name, scale_atmos_phy_cp::atmos_phy_cp, mod_atmos_phy_cp_vars::atmos_phy_cp_dens_t, mod_atmos_phy_cp_vars::atmos_phy_cp_mflx_cloudbase, mod_atmos_phy_cp_vars::atmos_phy_cp_momx_t, mod_atmos_phy_cp_vars::atmos_phy_cp_momy_t, mod_atmos_phy_cp_vars::atmos_phy_cp_momz_t, mod_atmos_phy_cp_vars::atmos_phy_cp_rhoq_t, mod_atmos_phy_cp_vars::atmos_phy_cp_rhot_t, mod_atmos_phy_cp_vars::atmos_phy_cp_sflx_rain, mod_atmos_vars::dens, mod_atmos_vars::dens_tp, scale_grid_index::ie, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, scale_grid_index::ke, scale_grid_index::ks, mod_atmos_vars::momx, mod_atmos_vars::momx_tp, mod_atmos_vars::momy, mod_atmos_vars::momy_tp, mod_atmos_vars::momz, mod_atmos_vars::momz_tp, scale_tracer::qa, mod_atmos_vars::qtrc, mod_atmos_vars::rhoq_tp, mod_atmos_vars::rhot, mod_atmos_vars::rhot_tp, scale_rm_statistics::statistics_checktotal, and scale_time::time_dtsec_atmos_phy_cp.

Referenced by mod_atmos_driver::atmos_driver(), and atmos_phy_cp_driver_resume().

97  use scale_time, only: &
99  use scale_rm_statistics, only: &
101  stat_total
102  use scale_history, only: &
103  hist_in
104  use scale_atmos_phy_cp, only: &
106  use mod_atmos_vars, only: &
107  dens, &
108  momz, &
109  momx, &
110  momy, &
111  rhot, &
112  qtrc, &
113  dens_t => dens_tp, &
114  momz_t => momz_tp, &
115  momx_t => momx_tp, &
116  momy_t => momy_tp, &
117  rhot_t => rhot_tp, &
118  rhoq_t => rhoq_tp
119  use mod_atmos_phy_cp_vars, only: &
120  dens_t_cp => atmos_phy_cp_dens_t, &
121  momz_t_cp => atmos_phy_cp_momz_t, &
122  momx_t_cp => atmos_phy_cp_momx_t, &
123  momy_t_cp => atmos_phy_cp_momy_t, &
124  rhot_t_cp => atmos_phy_cp_rhot_t, &
125  rhoq_t_cp => atmos_phy_cp_rhoq_t, &
126  mflx_cloudbase => atmos_phy_cp_mflx_cloudbase, &
127  sflx_rain => atmos_phy_cp_sflx_rain, & ! convective rain [kg/m2/s]
128  cloudtop => atmos_phy_cp_cloudtop, & ! cloud top height [m]
129  cloudbase => atmos_phy_cp_cloudbase, & ! cloud base height [m]
130  cldfrac_dp => atmos_phy_cp_cldfrac_dp, & ! cloud fraction (deep convection) [0-1]
131  cldfrac_sh => atmos_phy_cp_cldfrac_sh, & ! cloud fraction (shallow convection) [0-1]
132  kf_nca => atmos_phy_cp_kf_nca, & ! advection/cumulus convection timescale/dt for KF [step]
133  kf_w0avg => atmos_phy_cp_kf_w0avg ! rannning mean vertical wind velocity for KF [m/s]
134  implicit none
135 
136  logical, intent(in) :: update_flag
137 
138  real(RP) :: total ! dummy
139 
140  integer :: k, i, j, iq
141  !---------------------------------------------------------------------------
142 
143  if ( update_flag ) then
144 
145  call atmos_phy_cp( dens, & ! [IN]
146  momz, & ! [IN]
147  momx, & ! [IN]
148  momy, & ! [IN]
149  rhot, & ! [IN]
150  qtrc, & ! [IN]
151  dens_t_cp, & ! [INOUT]
152  momz_t_cp, & ! [INOUT]
153  momx_t_cp, & ! [INOUT]
154  momy_t_cp, & ! [INOUT]
155  rhot_t_cp, & ! [INOUT]
156  rhoq_t_cp, & ! [INOUT]
157  mflx_cloudbase, & ! [INOUT]
158  sflx_rain, & ! [OUT]
159  cloudtop, & ! [OUT]
160  cloudbase, & ! [OUT]
161  cldfrac_dp, & ! [OUT]
162  cldfrac_sh, & ! [OUT]
163  kf_nca, & ! [OUT]
164  kf_w0avg ) ! [OUT]
165 
166  ! tentative reset
167 !OCL XFILL
168  do j = js, je
169  do i = is, ie
170  do k = ks, ke
171  momz_t_cp(k,i,j) = 0.0_rp
172  momx_t_cp(k,i,j) = 0.0_rp
173  momy_t_cp(k,i,j) = 0.0_rp
174  enddo
175  enddo
176  enddo
177 
178 !OCL XFILL
179  do j = js, je
180  do i = is, ie
181  mflx_cloudbase(i,j) = 0.0_rp
182  enddo
183  enddo
184 
185  call hist_in( mflx_cloudbase(:,:), 'CBMFX', 'cloud base mass flux', 'kg/m2/s', nohalo=.true. )
186  call hist_in( sflx_rain(:,:), 'RAIN_CP', 'surface rain rate by CP', 'kg/m2/s', nohalo=.true. )
187  call hist_in( sflx_rain(:,:), 'PREC_CP', 'surface precipitation rate by CP', 'kg/m2/s', nohalo=.true. )
188  call hist_in( cloudtop(:,:), 'CUMHGT', 'CP cloud top height', 'm', nohalo=.true. )
189  call hist_in( cloudbase(:,:), 'CUBASE', 'CP cloud base height', 'm', nohalo=.true. )
190  call hist_in( cldfrac_dp(:,:,:), 'CUMFRC_DP', 'CP cloud fraction (deep)', '0-1', nohalo=.true. )
191  call hist_in( cldfrac_sh(:,:,:), 'CUMFRC_SH', 'CP cloud fraction (shallow)', '0-1', nohalo=.true. )
192 
193  call hist_in( kf_nca(:,:), 'kf_nca', 'advection or cumulus convection timescale for KF', 's', nohalo=.true. )
194  call hist_in( kf_w0avg(:,:,:), 'kf_w0avg', 'rannning mean vertical wind velocity for KF', 'kg/m2/s', nohalo=.true. )
195 
196  call hist_in( dens_t_cp(:,:,:), 'DENS_t_CP', 'tendency DENS in CP', 'kg/m3/s' , nohalo=.true. )
197  call hist_in( momz_t_cp(:,:,:), 'MOMZ_t_CP', 'tendency MOMZ in CP', 'kg/m2/s2' , nohalo=.true. )
198  call hist_in( momx_t_cp(:,:,:), 'MOMX_t_CP', 'tendency MOMX in CP', 'kg/m2/s2' , nohalo=.true. )
199  call hist_in( momy_t_cp(:,:,:), 'MOMY_t_CP', 'tendency MOMY in CP', 'kg/m2/s2' , nohalo=.true. )
200  call hist_in( rhot_t_cp(:,:,:), 'RHOT_t_CP', 'tendency RHOT in CP', 'K*kg/m3/s', nohalo=.true. )
201 
202  do iq = 1, qa
203  call hist_in( rhoq_t_cp(:,:,:,iq), trim(aq_name(iq))//'_t_CP', &
204  'tendency rho*'//trim(aq_name(iq))//'in CP', 'kg/m3/s', nohalo=.true. )
205  enddo
206 
207  endif
208 
209  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
210  do j = js, je
211  do i = is, ie
212  do k = ks, ke
213  dens_t(k,i,j) = dens_t(k,i,j) + dens_t_cp(k,i,j)
214  momz_t(k,i,j) = momz_t(k,i,j) + momz_t_cp(k,i,j)
215  momx_t(k,i,j) = momx_t(k,i,j) + momx_t_cp(k,i,j)
216  momy_t(k,i,j) = momy_t(k,i,j) + momy_t_cp(k,i,j)
217  rhot_t(k,i,j) = rhot_t(k,i,j) + rhot_t_cp(k,i,j)
218  enddo
219  enddo
220  enddo
221 
222  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(3)
223  do iq = 1, qa
224  do j = js, je
225  do i = is, ie
226  do k = ks, ke
227  rhoq_t(k,i,j,iq) = rhoq_t(k,i,j,iq) + rhoq_t_cp(k,i,j,iq)
228  enddo
229  enddo
230  enddo
231  enddo
232 
233  if ( statistics_checktotal ) then
234  call stat_total( total, dens_t_cp(:,:,:), 'DENS_t_CP' )
235  call stat_total( total, momz_t_cp(:,:,:), 'MOMZ_t_CP' )
236  call stat_total( total, momx_t_cp(:,:,:), 'MOMX_t_CP' )
237  call stat_total( total, momy_t_cp(:,:,:), 'MOMY_t_CP' )
238  call stat_total( total, rhot_t_cp(:,:,:), 'RHOT_t_CP' )
239 
240  do iq = 1, qa
241  call stat_total( total, rhoq_t_cp(:,:,:,iq), trim(aq_name(iq))//'_t_CP' )
242  enddo
243  endif
244 
245  return
real(rp), dimension(:,:,:), allocatable, public dens_tp
logical, public statistics_checktotal
calc&report variable totals to logfile?
real(rp), dimension(:,:,:), allocatable, target, public momz
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momy_t
module Atmosphere / Physics Cumulus
module ATMOSPHERE / Physics Cumulus Parameterization
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momx_t
real(rp), dimension(:,:,:), allocatable, target, public rhot
real(rp), dimension(:,:,:), allocatable, public momy_tp
module ATMOSPHERIC Variables
real(rp), dimension(:,:,:), allocatable, target, public momx
real(rp), dimension(:,:,:), allocatable, public rhot_tp
real(rp), dimension(:,:,:), allocatable, target, public dens
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_dens_t
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhoq_t
module Statistics
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momz_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t
real(dp), public time_dtsec_atmos_phy_cp
time interval of physics(cumulus ) [sec]
Definition: scale_time.F90:40
real(rp), dimension(:,:,:), allocatable, public momx_tp
real(rp), dimension(:,:,:), allocatable, target, public momy
procedure(cp), pointer, public atmos_phy_cp
real(rp), dimension(:,:,:), allocatable, public momz_tp
module HISTORY
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the caller graph for this function: