SCALE-RM
scale_atmos_phy_sf_bulk.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
17 !-------------------------------------------------------------------------------
18 #include "inc_openmp.h"
20  !-----------------------------------------------------------------------------
21  !
22  !++ used modules
23  !
24  use scale_precision
25  use scale_stdio
26  use scale_prof
28  use scale_tracer
29  !-----------------------------------------------------------------------------
30  implicit none
31  private
32  !-----------------------------------------------------------------------------
33  !
34  !++ Public procedure
35  !
36  public :: atmos_phy_sf_bulk_setup
37  public :: atmos_phy_sf_bulk
38 
39  !-----------------------------------------------------------------------------
40  !
41  !++ Public parameters & variables
42  !
43  !-----------------------------------------------------------------------------
44  !
45  !++ Private procedure
46  !
47  !-----------------------------------------------------------------------------
48  !
49  !++ Private parameters & variables
50  !
51  real(RP), private :: atmos_phy_sf_beta = 1.0_rp ! evaporation efficiency [0-1]
52 
53  real(RP), private, parameter :: atmos_phy_sf_u_maxm = 100.0_rp ! maximum limit of absolute velocity for momentum [m/s]
54  real(RP), private, parameter :: atmos_phy_sf_u_maxh = 100.0_rp ! maximum limit of absolute velocity for heat [m/s]
55  real(RP), private, parameter :: atmos_phy_sf_u_maxe = 100.0_rp ! maximum limit of absolute velocity for vapor [m/s]
56  real(RP), private :: atmos_phy_sf_u_minm = 0.0_rp ! minimum limit of absolute velocity for momentum [m/s]
57  real(RP), private :: atmos_phy_sf_u_minh = 0.0_rp ! minimum limit of absolute velocity for heat [m/s]
58  real(RP), private :: atmos_phy_sf_u_mine = 0.0_rp ! minimum limit of absolute velocity for vapor [m/s]
59 
60  !-----------------------------------------------------------------------------
61 contains
62  !-----------------------------------------------------------------------------
64  subroutine atmos_phy_sf_bulk_setup( ATMOS_PHY_SF_TYPE )
65  use scale_process, only: &
67  use scale_atmos_phy_sf_bulkcoef, only: &
68  sf_bulkcoef_setup => atmos_phy_sf_bulkcoef_setup
69  implicit none
70 
71  character(len=*), intent(in) :: ATMOS_PHY_SF_TYPE
72 
73  namelist / param_atmos_phy_sf_bulk / &
74  atmos_phy_sf_beta, &
75  atmos_phy_sf_u_minm, &
76  atmos_phy_sf_u_minh, &
77  atmos_phy_sf_u_mine
78 
79  integer :: ierr
80  !---------------------------------------------------------------------------
81 
82  if( io_l ) write(io_fid_log,*)
83  if( io_l ) write(io_fid_log,*) '++++++ Module[SURFACE FLUX] / Categ[ATMOS PHYSICS] / Origin[SCALElib]'
84  if( io_l ) write(io_fid_log,*) '+++ Bulk scheme'
85 
86  if ( atmos_phy_sf_type /= 'BULK' ) then
87  write(*,*) 'xxx ATMOS_PHY_SF_TYPE is not BULK. Check!'
88  call prc_mpistop
89  endif
90 
91  !--- read namelist
92  rewind(io_fid_conf)
93  read(io_fid_conf,nml=param_atmos_phy_sf_bulk,iostat=ierr)
94  if( ierr < 0 ) then !--- missing
95  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
96  elseif( ierr > 0 ) then !--- fatal error
97  write(*,*) 'xxx Not appropriate names in namelist PARAM_ATMOS_PHY_SF_BULK. Check!'
98  call prc_mpistop
99  endif
100  if( io_lnml ) write(io_fid_log,nml=param_atmos_phy_sf_bulk)
101 
102  call sf_bulkcoef_setup
103 
104  return
105  end subroutine atmos_phy_sf_bulk_setup
106 
107  !-----------------------------------------------------------------------------
109  subroutine atmos_phy_sf_bulk( &
110  ATM_TEMP, ATM_PRES, ATM_W, ATM_U, ATM_V, &
111  ATM_DENS, &
112  ATM_QTRC, &
113  ATM_Z1, dt, &
114  SFC_DENS, SFC_PRES, &
115  SFLX_LW_dn, SFLX_SW_dn, &
116  SFC_TEMP, SFC_albedo, &
117  SFC_Z0M, SFC_Z0H, SFC_Z0E, &
118  SFLX_MW, SFLX_MU, SFLX_MV, SFLX_SH, SFLX_LH, &
119  SFLX_QTRC, &
120  U10, V10, T2, Q2 )
122  use scale_tracer
123  use scale_const, only: &
124  cpdry => const_cpdry, &
125  rdry => const_rdry
126  use scale_atmos_phy_sf_bulkcoef, only: &
127  sf_bulkcoef => atmos_phy_sf_bulkcoef
128  use scale_atmos_saturation, only: &
129  saturation_pres2qsat_all => atmos_saturation_pres2qsat_all
130  use scale_atmos_thermodyn, only: &
131  atmos_thermodyn_templhv
132  use scale_roughness, only: &
133  roughness
134  use scale_bulkflux, only: &
135  bulkflux
136  implicit none
137 
138  real(RP), intent(in) :: ATM_TEMP (ia,ja) ! temperature at the lowermost layer (cell center) [K]
139  real(RP), intent(in) :: ATM_PRES (ia,ja) ! pressure at the lowermost layer (cell center) [Pa]
140  real(RP), intent(in) :: ATM_W (ia,ja) ! velocity w at the lowermost layer (cell center) [m/s]
141  real(RP), intent(in) :: ATM_U (ia,ja) ! velocity u at the lowermost layer (cell center) [m/s]
142  real(RP), intent(in) :: ATM_V (ia,ja) ! velocity v at the lowermost layer (cell center) [m/s]
143  real(RP), intent(in) :: ATM_DENS (ia,ja) ! density at the lowermost layer (cell center) [kg/m3]
144  real(RP), intent(in) :: ATM_QTRC (ia,ja,qa) ! tracer at the lowermost layer (cell center) [kg/kg]
145  real(RP), intent(in) :: ATM_Z1 (ia,ja) ! height of the lowermost grid from surface (cell center) [m]
146  real(DP), intent(in) :: dt ! delta time
147  real(RP), intent(in) :: SFC_DENS (ia,ja) ! density at the surface atmosphere [kg/m3]
148  real(RP), intent(in) :: SFC_PRES (ia,ja) ! pressure at the surface atmosphere [Pa]
149  real(RP), intent(in) :: SFLX_LW_dn(ia,ja) ! downward longwave radiation flux at the surface [J/m2/s]
150  real(RP), intent(in) :: SFLX_SW_dn(ia,ja) ! downward shortwave radiation flux at the surface [J/m2/s]
151  real(RP), intent(in) :: SFC_TEMP (ia,ja) ! temperature at the surface skin [K]
152  real(RP), intent(in) :: SFC_albedo(ia,ja,2) ! surface albedo (LW/SW) [0-1]
153  real(RP), intent(inout) :: SFC_Z0M (ia,ja) ! surface roughness length (momentum) [m]
154  real(RP), intent(inout) :: SFC_Z0H (ia,ja) ! surface roughness length (heat) [m]
155  real(RP), intent(inout) :: SFC_Z0E (ia,ja) ! surface roughness length (vapor) [m]
156  real(RP), intent(out) :: SFLX_MW (ia,ja) ! surface flux for z-momentum (area center) [m/s*kg/m2/s]
157  real(RP), intent(out) :: SFLX_MU (ia,ja) ! surface flux for x-momentum (area center) [m/s*kg/m2/s]
158  real(RP), intent(out) :: SFLX_MV (ia,ja) ! surface flux for y-momentum (area center) [m/s*kg/m2/s]
159  real(RP), intent(out) :: SFLX_SH (ia,ja) ! surface flux for sensible heat (area center) [J/m2/s]
160  real(RP), intent(out) :: SFLX_LH (ia,ja) ! surface flux for latent heat (area center) [J/m2/s]
161  real(RP), intent(out) :: SFLX_QTRC (ia,ja,qa) ! surface flux for tracer mass (area center) [kg/m2/s]
162  real(RP), intent(out) :: U10 (ia,ja) ! velocity u at 10m height
163  real(RP), intent(out) :: V10 (ia,ja) ! velocity v at 10m height
164  real(RP), intent(out) :: T2 (ia,ja) ! temperature t at 2m height
165  real(RP), intent(out) :: Q2 (ia,ja) ! water vapor q at 2m height
166 
167  real(RP) :: SFC_Z0M_t(ia,ja)
168  real(RP) :: SFC_Z0H_t(ia,ja)
169  real(RP) :: SFC_Z0E_t(ia,ja)
170 
171  real(RP) :: SFC_QSAT(ia,ja) ! saturatad water vapor mixing ratio [kg/kg]
172 
173  real(RP) :: PBL(ia,ja)
174  real(RP) :: LHV (ia,ja)
175  real(RP) :: Ustar
176  real(RP) :: Tstar
177  real(RP) :: Qstar
178  real(RP) :: Uabs
179 
180  integer :: i, j
181  !---------------------------------------------------------------------------
182 
183  if( io_l ) write(io_fid_log,*) '*** Physics step: Surface flux(bulk)'
184 
185  call roughness( sfc_z0m_t(:,:), & ! [OUT]
186  sfc_z0h_t(:,:), & ! [OUT]
187  sfc_z0e_t(:,:), & ! [OUT]
188  sfc_z0m(:,:), & ! [IN]
189  sfc_z0h(:,:), & ! [IN]
190  sfc_z0e(:,:), & ! [IN]
191  atm_u(:,:), & ! [IN]
192  atm_v(:,:), & ! [IN]
193  atm_z1(:,:), & ! [IN]
194  dt ) ! [IN]
195 
196  sfc_z0m(:,:) = sfc_z0m(:,:) + sfc_z0m_t(:,:) * dt
197  sfc_z0h(:,:) = sfc_z0h(:,:) + sfc_z0h_t(:,:) * dt
198  sfc_z0e(:,:) = sfc_z0e(:,:) + sfc_z0e_t(:,:) * dt
199 
200  call saturation_pres2qsat_all( sfc_qsat(:,:), & ! [OUT]
201  sfc_temp(:,:), & ! [IN]
202  sfc_pres(:,:) ) ! [IN]
203 
204  call atmos_thermodyn_templhv( lhv, atm_temp )
205 
206  sflx_qtrc(:,:,:) = 0.0_rp
207  pbl(:,:) = 100.0_rp ! tentative
208  do j = js, je
209  do i = is, ie
210 
211  call bulkflux( &
212  ustar, & ! [OUT]
213  tstar, & ! [OUT]
214  qstar, & ! [OUT]
215  uabs, & ! [OUT]
216  atm_temp(i,j), & ! [IN]
217  sfc_temp(i,j), & ! [IN]
218  atm_pres(i,j), & ! [IN]
219  sfc_pres(i,j), & ! [IN]
220  atm_qtrc(i,j,i_qv), & ! [IN]
221  sfc_qsat(i,j), & ! [IN]
222  atm_u(i,j), & ! [IN]
223  atm_v(i,j), & ! [IN]
224  atm_z1(i,j), & ! [IN]
225  pbl(i,j), & ! [IN]
226  sfc_z0m(i,j), & ! [IN]
227  sfc_z0h(i,j), & ! [IN]
228  sfc_z0e(i,j) ) ! [IN]
229 
230  !-----< momentum >-----
231  sflx_mw(i,j) = -atm_dens(i,j) * ustar**2 / uabs * atm_w(i,j)
232  sflx_mu(i,j) = -atm_dens(i,j) * ustar**2 / uabs * atm_u(i,j)
233  sflx_mv(i,j) = -atm_dens(i,j) * ustar**2 / uabs * atm_v(i,j)
234 
235  !-----< heat flux >-----
236  sflx_sh(i,j) = -cpdry * atm_dens(i,j) * ustar * tstar
237  sflx_lh(i,j) = -lhv(i,j) * atm_dens(i,j) * ustar * qstar * atmos_phy_sf_beta
238 
239  !-----< mass flux >-----
240  sflx_qtrc(i,j,i_qv) = sflx_lh(i,j) / lhv(i,j)
241  enddo
242  enddo
243 
244  !-----< U10, T2, q2 >-----
245 
246  do j = js, je
247  do i = is, ie
248  u10(i,j) = atm_u(i,j) * log( 10.0_rp / sfc_z0m(i,j) ) / log( atm_z1(i,j) / sfc_z0m(i,j) )
249  v10(i,j) = atm_v(i,j) * log( 10.0_rp / sfc_z0m(i,j) ) / log( atm_z1(i,j) / sfc_z0m(i,j) )
250  t2(i,j) = sfc_temp(i,j) + ( atm_temp(i,j) - sfc_temp(i,j) ) &
251  * ( log( 2.0_rp / sfc_z0m(i,j) ) * log( 2.0_rp / sfc_z0h(i,j) ) ) &
252  / ( log( atm_z1(i,j) / sfc_z0m(i,j) ) * log( atm_z1(i,j) / sfc_z0h(i,j) ) )
253  q2(i,j) = sfc_qsat(i,j) + ( atm_qtrc(i,j,i_qv) - sfc_qsat(i,j) ) &
254  * ( log( 2.0_rp / sfc_z0m(i,j) ) * log( 2.0_rp / sfc_z0e(i,j) ) ) &
255  / ( log( atm_z1(i,j) / sfc_z0m(i,j) ) * log( atm_z1(i,j) / sfc_z0e(i,j) ) )
256  enddo
257  enddo
258 
259  return
260  end subroutine atmos_phy_sf_bulk
261 
262 end module scale_atmos_phy_sf_bulk
integer, public is
start point of inner domain: x, local
integer, public je
end point of inner domain: y, local
subroutine, public atmos_phy_sf_bulk_setup(ATMOS_PHY_SF_TYPE)
Setup.
real(rp), public const_cpdry
specific heat (dry air,constant pressure) [J/kg/K]
Definition: scale_const.F90:58
module ATMOSPHERE / Saturation adjustment
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_rdry
specific gas constant (dry air) [J/kg/K]
Definition: scale_const.F90:57
module grid index
module TRACER
integer, public ia
of x whole cells (local, with HALO)
integer, public i_qv
procedure(bc), pointer, public bulkflux
integer, public js
start point of inner domain: y, local
module ATMOSPHERE / Physics Surface fluxes
procedure(rl), pointer, public roughness
procedure(bc), pointer, public atmos_phy_sf_bulkcoef
module PROCESS
subroutine, public log(type, message)
Definition: dc_log.f90:133
module CONSTANT
Definition: scale_const.F90:14
module profiler
Definition: scale_prof.F90:10
integer, public ie
end point of inner domain: x, local
module Surface bulk flux
module ATMOSPHERE / Thermodynamics
logical, public io_lnml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:60
module PRECISION
subroutine, public atmos_phy_sf_bulk(ATM_TEMP, ATM_PRES, ATM_W, ATM_U, ATM_V, ATM_DENS, ATM_QTRC, ATM_Z1, dt, SFC_DENS, SFC_PRES, SFLX_LW_dn, SFLX_SW_dn, SFC_TEMP, SFC_albedo, SFC_Z0M, SFC_Z0H, SFC_Z0E, SFLX_MW, SFLX_MU, SFLX_MV, SFLX_SH, SFLX_LH, SFLX_QTRC, U10, V10, T2, Q2)
Calculate surface flux.
module Surface roughness length
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
module ATMOSPHERE / Physics Surface bulk coefficient
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
integer, public ja
of y whole cells (local, with HALO)