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

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 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: &
53 ! ATMOS_PHY_CP_setup
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
66  !call ATMOS_PHY_CP_setup( ATMOS_PHY_CP_TYPE )
67 
68  else
69  if( io_l ) write(io_fid_log,*) '*** this component is never called.'
70  end if
71 
72  return
module ATMOS admin
logical, public atmos_sw_phy_cp
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
character(len=h_short), public atmos_phy_cp_type
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
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.
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:132
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:178
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, 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, 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_tp, mod_atmos_vars::momy_tp, mod_atmos_vars::momz_tp, scale_tracer::qa, mod_atmos_vars::rhoq_tp, mod_atmos_vars::rhot_tp, and scale_rm_statistics::statistics_checktotal.

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

97 ! use scale_time, only: &
98 ! dt_CP => TIME_DTSEC_ATMOS_PHY_CP
99  use scale_rm_statistics, only: &
101  stat_total
102  use scale_history, only: &
103  hist_in
104 ! use scale_atmos_phy_cp, only: &
105 ! ATMOS_PHY_CP
106  use mod_atmos_vars, only: &
107 ! DENS, &
108 ! MOMZ, &
109 ! MOMX, &
110 ! MOMY, &
111 ! RHOT, &
112 ! QTRC, &
113  momz_t => momz_tp, &
114  momx_t => momx_tp, &
115  momy_t => momy_tp, &
116  rhot_t => rhot_tp, &
117  rhoq_t => rhoq_tp
118  use mod_atmos_phy_cp_vars, only: &
119  momz_t_cp => atmos_phy_cp_momz_t, &
120  momx_t_cp => atmos_phy_cp_momx_t, &
121  momy_t_cp => atmos_phy_cp_momy_t, &
122  rhot_t_cp => atmos_phy_cp_rhot_t, &
123  rhoq_t_cp => atmos_phy_cp_rhoq_t, &
124  mflx_cloudbase => atmos_phy_cp_mflx_cloudbase
125  implicit none
126 
127  logical, intent(in) :: update_flag
128 
129  real(RP) :: total ! dummy
130 
131  integer :: k, i, j, iq
132  !---------------------------------------------------------------------------
133 
134  if ( update_flag ) then
135 
136 ! call ATMOS_PHY_CP( DENS, & ! [IN]
137 ! MOMZ, & ! [IN]
138 ! MOMX, & ! [IN]
139 ! MOMY, & ! [IN]
140 ! RHOT, & ! [IN]
141 ! QTRC, & ! [IN]
142 ! MOMZ_t_CP, & ! [INOUT]
143 ! MOMX_t_CP, & ! [INOUT]
144 ! MOMY_t_CP, & ! [INOUT]
145 ! RHOT_t_CP, & ! [INOUT]
146 ! RHOQ_t_CP, & ! [INOUT]
147 ! MFLX_cloudbase ) ! [INOUT]
148 
149  ! tentative!
150 !OCL XFILL
151  momz_t_cp(:,:,:) = 0.0_rp
152 !OCL XFILL
153  momx_t_cp(:,:,:) = 0.0_rp
154 !OCL XFILL
155  momy_t_cp(:,:,:) = 0.0_rp
156 !OCL XFILL
157  rhot_t_cp(:,:,:) = 0.0_rp
158 !OCL XFILL
159  rhoq_t_cp(:,:,:,:) = 0.0_rp
160 !OCL XFILL
161  mflx_cloudbase(:,:) = 0.0_rp
162 
163  call hist_in( mflx_cloudbase(:,:), 'CBMFX', 'cloud base mass flux', 'kg/m2/s' )
164  endif
165 
166  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
167  do j = js, je
168  do i = is, ie
169  do k = ks, ke
170  momz_t(k,i,j) = momz_t(k,i,j) + momz_t_cp(k,i,j)
171  momx_t(k,i,j) = momx_t(k,i,j) + momx_t_cp(k,i,j)
172  momy_t(k,i,j) = momy_t(k,i,j) + momy_t_cp(k,i,j)
173  rhot_t(k,i,j) = rhot_t(k,i,j) + rhot_t_cp(k,i,j)
174  enddo
175  enddo
176  enddo
177 
178  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(3)
179  do iq = 1, qa
180  do j = js, je
181  do i = is, ie
182  do k = ks, ke
183  rhoq_t(k,i,j,iq) = rhoq_t(k,i,j,iq) + rhoq_t_cp(k,i,j,iq)
184  enddo
185  enddo
186  enddo
187  enddo
188 
189  if ( statistics_checktotal ) then
190  call stat_total( total, momz_t_cp(:,:,:), 'MOMZ_t_CP' )
191  call stat_total( total, momx_t_cp(:,:,:), 'MOMX_t_CP' )
192  call stat_total( total, momy_t_cp(:,:,:), 'MOMY_t_CP' )
193  call stat_total( total, rhot_t_cp(:,:,:), 'RHOT_t_CP' )
194 
195  do iq = 1, qa
196  call stat_total( total, rhoq_t_cp(:,:,:,iq), trim(aq_name(iq))//'_t_CP' )
197  enddo
198  endif
199 
200  return
integer, public is
start point of inner domain: x, local
logical, public statistics_checktotal
calc&report variable totals to logfile?
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momy_t
integer, public je
end point of inner domain: y, local
module Atmosphere / Physics Cumulus
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momx_t
real(rp), dimension(:,:,:), allocatable, public momy_tp
module ATMOSPHERIC Variables
integer, public ke
end point of inner domain: z, local
real(rp), dimension(:,:,:), allocatable, public rhot_tp
integer, public qa
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_cp_rhoq_t
module Statistics
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
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_momz_t
real(rp), dimension(:,:,:), allocatable, public atmos_phy_cp_rhot_t
integer, public ks
start point of inner domain: z, local
real(rp), dimension(:,:,:), allocatable, public momx_tp
real(rp), dimension(:,:,:), allocatable, public momz_tp
integer, public ie
end point of inner domain: x, local
module HISTORY
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_mflx_cloudbase
Here is the caller graph for this function: