SCALE-RM
mod_urban_driver.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
9 !-------------------------------------------------------------------------------
11  !-----------------------------------------------------------------------------
12  !
13  !++ used modules
14  !
15  use scale_precision
16  use scale_stdio
17  use scale_prof
18  use scale_debug
21 
22  use scale_const, only: &
23  i_sw => const_i_sw, &
24  i_lw => const_i_lw
25  !-----------------------------------------------------------------------------
26  implicit none
27  private
28  !-----------------------------------------------------------------------------
29  !
30  !++ Public procedure
31  !
32  public :: urban_driver_setup
33  public :: urban_driver_resume
34  public :: urban_driver
35  public :: urban_surface_get
36  public :: urban_surface_set
37 
38  !-----------------------------------------------------------------------------
39  !
40  !++ Public parameters & variables
41  !
42  !-----------------------------------------------------------------------------
43  !
44  !++ Private procedure
45  !
46  !-----------------------------------------------------------------------------
47  !
48  !++ Private parameters & variables
49  !
50  !-----------------------------------------------------------------------------
51 contains
52  !-----------------------------------------------------------------------------
54  subroutine urban_driver_setup
55  use mod_urban_phy_driver, 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[URBAN] / Origin[SCALE-RM]'
62 
64 
65  return
66  end subroutine urban_driver_setup
67 
68  !-----------------------------------------------------------------------------
70  subroutine urban_driver_resume
71  use mod_urban_phy_driver, only: &
73  use mod_urban_vars, only: &
75  use mod_urban_admin, only: &
76  urban_sw
77  implicit none
78  !---------------------------------------------------------------------------
79 
80  if( io_l ) write(io_fid_log,*)
81  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[URBAN] / Origin[SCALE-RM]'
82 
83  !########## Get Surface Boundary from coupler ##########
85 
87 
88  !########## Set Surface Boundary to coupler ##########
89  call urban_surface_set( countup=.true. )
90 
91  !########## History & Monitor ##########
92  if ( urban_sw ) then
93  call prof_rapstart('URB_History', 1)
95  call prof_rapend ('URB_History', 1)
96  endif
97 
98  return
99  end subroutine urban_driver_resume
100 
101  !-----------------------------------------------------------------------------
103  subroutine urban_driver
104  use scale_time, only: &
105  dt => time_dtsec_urban
106  use mod_urban_admin, only: &
107  urban_sw
108  use mod_urban_vars, only: &
109  urban_tr_t, &
110  urban_tb_t, &
111  urban_tg_t, &
112  urban_tc_t, &
113  urban_qc_t, &
114  urban_uc_t, &
115  urban_trl_t, &
116  urban_tbl_t, &
117  urban_tgl_t, &
118  urban_rainr_t, &
119  urban_rainb_t, &
120  urban_raing_t, &
121  urban_roff_t, &
122  urban_tr, &
123  urban_tb, &
124  urban_tg, &
125  urban_tc, &
126  urban_qc, &
127  urban_uc, &
128  urban_trl, &
129  urban_tbl, &
130  urban_tgl, &
131  urban_rainr, &
132  urban_rainb, &
133  urban_raing, &
134  urban_roff, &
137  use mod_urban_phy_driver, only: &
139  implicit none
140 
141  integer :: k, i, j
142  !---------------------------------------------------------------------------
143 
144  !########## Get Surface Boundary from coupler ##########
145  call prof_rapstart('URB_SfcExch', 2)
146  call urban_surface_get
147  call prof_rapend ('URB_SfcExch', 2)
148 
149  !########## Physics ##########
150  if ( urban_sw ) then
151  call prof_rapstart('URB_Physics', 1)
152  call urban_phy_driver( update_flag = .true. )
153  call prof_rapend ('URB_Physics', 1)
154  endif
155 
156  !########## Update ##########
157  do j = js, je
158  do i = is, ie
159  do k = uks, uke
160  urban_trl(k,i,j) = urban_trl(k,i,j) + urban_trl_t(k,i,j) * dt
161  urban_tbl(k,i,j) = urban_tbl(k,i,j) + urban_tbl_t(k,i,j) * dt
162  urban_tgl(k,i,j) = urban_tgl(k,i,j) + urban_tgl_t(k,i,j) * dt
163  end do
164  end do
165  end do
166  do j = js, je
167  do i = is, ie
168  urban_tr(i,j) = urban_tr(i,j) + urban_tr_t(i,j) * dt
169  urban_tb(i,j) = urban_tb(i,j) + urban_tb_t(i,j) * dt
170  urban_tg(i,j) = urban_tg(i,j) + urban_tg_t(i,j) * dt
171  urban_tc(i,j) = urban_tc(i,j) + urban_tc_t(i,j) * dt
172  urban_qc(i,j) = urban_qc(i,j) + urban_qc_t(i,j) * dt
173  urban_uc(i,j) = urban_uc(i,j) + urban_uc_t(i,j) * dt
174 
175  urban_rainr(i,j) = urban_rainr(i,j) + urban_rainr_t(i,j) * dt
176  urban_rainb(i,j) = urban_rainb(i,j) + urban_rainb_t(i,j) * dt
177  urban_raing(i,j) = urban_raing(i,j) + urban_raing_t(i,j) * dt
178  urban_roff(i,j) = urban_roff(i,j) + urban_roff_t(i,j) * dt
179  end do
180  end do
181 
182  call urban_vars_total
183 
184  !########## Set Surface Boundary to coupler ##########
185  call prof_rapstart('URB_SfcExch', 2)
186  call urban_surface_set( countup=.true. )
187  call prof_rapend ('URB_SfcExch', 2)
188 
189  !########## reset tendencies ##########
190 !OCL XFILL
191  do j = js, je
192  do i = is, ie
193  do k = uks, uke
194  urban_trl_t(k,i,j) = 0.0_rp
195  urban_tbl_t(k,i,j) = 0.0_rp
196  urban_tgl_t(k,i,j) = 0.0_rp
197  end do
198  end do
199  end do
200 
201 !OCL XFILL
202  do j = js, je
203  do i = is, ie
204  urban_tr_t(i,j) = 0.0_rp
205  urban_tb_t(i,j) = 0.0_rp
206  urban_tg_t(i,j) = 0.0_rp
207  urban_tc_t(i,j) = 0.0_rp
208  urban_qc_t(i,j) = 0.0_rp
209  urban_uc_t(i,j) = 0.0_rp
210 
211  urban_rainr_t(i,j) = 0.0_rp
212  urban_rainb_t(i,j) = 0.0_rp
213  urban_raing_t(i,j) = 0.0_rp
214  urban_roff_t(i,j) = 0.0_rp
215  enddo
216  enddo
217 
218  !########## History & Monitor ##########
219  call prof_rapstart('URB_History', 1)
220  call urban_vars_history
221  call prof_rapend ('URB_History', 1)
222 
223  return
224  end subroutine urban_driver
225 
226  !-----------------------------------------------------------------------------
228  subroutine urban_surface_get
229  use mod_urban_admin, only: &
230  urban_sw
231  use mod_urban_vars, only: &
232  atmos_temp, &
233  atmos_pres, &
234  atmos_w, &
235  atmos_u, &
236  atmos_v, &
237  atmos_dens, &
238  atmos_qv, &
239  atmos_pbl, &
240  atmos_sfc_pres, &
241  atmos_sflx_lw, &
242  atmos_sflx_sw, &
243  atmos_cossza, &
245  use mod_cpl_vars, only: &
247  implicit none
248 
249  real(RP) :: ATMOS_SFLX_rad_dn(ia,ja,2,2)
250  real(RP) :: ATMOS_SFLX_rain (ia,ja)
251  real(RP) :: ATMOS_SFLX_snow (ia,ja)
252  !---------------------------------------------------------------------------
253 
254  if ( urban_sw ) then
255  call cpl_getatm_urb( atmos_temp(:,:), & ! [OUT]
256  atmos_pres(:,:), & ! [OUT]
257  atmos_w(:,:), & ! [OUT]
258  atmos_u(:,:), & ! [OUT]
259  atmos_v(:,:), & ! [OUT]
260  atmos_dens(:,:), & ! [OUT]
261  atmos_qv(:,:), & ! [OUT]
262  atmos_pbl(:,:), & ! [OUT]
263  atmos_sfc_pres(:,:), & ! [OUT]
264  atmos_sflx_rad_dn(:,:,:,:), & ! [OUT]
265  atmos_cossza(:,:), & ! [OUT]
266  atmos_sflx_rain(:,:), & ! [OUT]
267  atmos_sflx_snow(:,:) ) ! [OUT]
268  endif
269 
270  atmos_sflx_sw(:,:,:) = atmos_sflx_rad_dn(:,:,i_sw,:) ! direct/diffuse
271  atmos_sflx_lw(:,:,:) = atmos_sflx_rad_dn(:,:,i_lw,:) ! direct/diffuse
272 
273  atmos_sflx_prec(:,:) = atmos_sflx_rain(:,:) + atmos_sflx_snow(:,:) ! liquid+ice
274 
275  return
276  end subroutine urban_surface_get
277 
278  !-----------------------------------------------------------------------------
280  subroutine urban_surface_set( countup )
281  use mod_urban_admin, only: &
282  urban_sw
283  use mod_urban_vars, only: &
284  urban_sfc_temp, &
286  urban_sflx_mw, &
287  urban_sflx_mu, &
288  urban_sflx_mv, &
289  urban_sflx_sh, &
290  urban_sflx_lh, &
291  urban_sflx_gh, &
292  urban_sflx_evap, &
293  urban_z0m, &
294  urban_z0h, &
295  urban_z0e, &
296  urban_u10, &
297  urban_v10, &
298  urban_t2, &
299  urban_q2
300  use mod_cpl_vars, only: &
301  cpl_puturb
302  implicit none
303 
304  ! arguments
305  logical, intent(in) :: countup
306  !---------------------------------------------------------------------------
307 
308  if ( urban_sw ) then
309  call cpl_puturb( urban_sfc_temp(:,:), & ! [IN]
310  urban_sfc_albedo(:,:,:), & ! [IN]
311  urban_z0m(:,:), & ! [IN]
312  urban_z0h(:,:), & ! [IN]
313  urban_z0e(:,:), & ! [IN]
314  urban_sflx_mw(:,:), & ! [IN]
315  urban_sflx_mu(:,:), & ! [IN]
316  urban_sflx_mv(:,:), & ! [IN]
317  urban_sflx_sh(:,:), & ! [IN]
318  urban_sflx_lh(:,:), & ! [IN]
319  urban_sflx_gh(:,:), & ! [IN]
320  urban_sflx_evap(:,:), & ! [IN]
321  urban_u10(:,:), & ! [IN]
322  urban_v10(:,:), & ! [IN]
323  urban_t2(:,:), & ! [IN]
324  urban_q2(:,:), & ! [IN]
325  countup ) ! [IN]
326  endif
327 
328  return
329  end subroutine urban_surface_set
330 
331 end module mod_urban_driver
real(rp), dimension(:,:), allocatable, public urban_qc_t
integer, public is
start point of inner domain: x, local
module DEBUG
Definition: scale_debug.F90:13
logical, public urban_sw
integer, public je
end point of inner domain: y, local
integer, public const_i_lw
long-wave radiation index
Definition: scale_const.F90:98
real(rp), dimension(:,:), allocatable, public urban_qc
real(rp), dimension(:,:), allocatable, public urban_rainr_t
real(rp), dimension(:,:,:), allocatable, public urban_trl_t
real(rp), dimension(:,:), allocatable, public urban_tg_t
real(rp), dimension(:,:), allocatable, public urban_u10
module URBAN driver
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
real(rp), dimension(:,:), allocatable, public urban_v10
real(rp), dimension(:,:), allocatable, public urban_raing_t
real(rp), dimension(:,:), allocatable, public urban_z0e
real(rp), dimension(:,:), allocatable, public urban_sflx_mu
real(rp), dimension(:,:), allocatable, public urban_sflx_evap
real(rp), dimension(:,:), allocatable, public urban_z0m
subroutine, public urban_vars_total
Budget monitor for urban.
module STDIO
Definition: scale_stdio.F90:12
real(rp), dimension(:,:), allocatable, public urban_tb_t
real(rp), dimension(:,:), allocatable, public urban_t2
subroutine, public urban_vars_history
History output set for urban variables.
real(rp), dimension(:,:), allocatable, public urban_tb
module URBAN / Physics Urban Canopy Model (UCM)
module URBAN Variables
real(rp), dimension(:,:), allocatable, public urban_raing
real(rp), dimension(:,:), allocatable, public urban_uc
subroutine, public cpl_getatm_urb(TEMP, PRES, W, U, V, DENS, QV, PBL, SFC_PRES, SFLX_rad_dn, cosSZA, SFLX_rain, SFLX_snow)
real(rp), dimension(:,:), allocatable, public atmos_sflx_prec
subroutine, public cpl_puturb(SFC_TEMP, SFC_albedo, SFC_Z0M, SFC_Z0H, SFC_Z0E, SFLX_MW, SFLX_MU, SFLX_MV, SFLX_SH, SFLX_LH, SFLX_GH, SFLX_evap, U10, V10, T2, Q2, countup)
subroutine, public urban_phy_driver_setup
Setup.
subroutine, public urban_surface_set(countup)
Set surface boundary to other model.
module grid index
real(rp), dimension(:,:), allocatable, public atmos_pbl
real(rp), dimension(:,:), allocatable, public urban_sflx_sh
real(rp), dimension(:,:), allocatable, public urban_tr
integer, public ia
of x whole cells (local, with HALO)
real(rp), dimension(:,:,:), allocatable, public urban_tgl
real(rp), dimension(:,:), allocatable, public atmos_qv
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
real(rp), dimension(:,:), allocatable, public atmos_cossza
module COUPLER Variables
subroutine, public urban_driver
Urban step.
real(rp), dimension(:,:), allocatable, public urban_uc_t
subroutine, public urban_phy_driver(update_flag)
Driver.
real(rp), dimension(:,:), allocatable, public urban_z0h
real(rp), dimension(:,:,:), allocatable, public atmos_sflx_sw
real(rp), dimension(:,:), allocatable, public atmos_v
integer, public js
start point of inner domain: y, local
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:), allocatable, public urban_roff
subroutine, public urban_driver_resume
Resume.
real(rp), dimension(:,:), allocatable, public atmos_dens
subroutine, public urban_driver_setup
Setup.
module CONSTANT
Definition: scale_const.F90:14
real(rp), dimension(:,:,:), allocatable, public urban_sfc_albedo
real(rp), dimension(:,:), allocatable, public urban_sflx_lh
subroutine, public urban_phy_driver_resume
Resume.
real(rp), dimension(:,:), allocatable, public urban_tc
real(rp), dimension(:,:), allocatable, public atmos_pres
real(rp), dimension(:,:), allocatable, public urban_rainr
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:132
module profiler
Definition: scale_prof.F90:10
integer, public ie
end point of inner domain: x, local
real(rp), dimension(:,:), allocatable, public atmos_temp
integer, public const_i_sw
short-wave radiation index
Definition: scale_const.F90:99
module PRECISION
real(rp), dimension(:,:), allocatable, public urban_q2
real(rp), dimension(:,:), allocatable, public urban_tg
real(rp), dimension(:,:), allocatable, public atmos_u
real(rp), dimension(:,:), allocatable, public urban_sfc_temp
real(rp), dimension(:,:,:), allocatable, public urban_trl
real(rp), dimension(:,:), allocatable, public urban_rainb_t
real(rp), dimension(:,:,:), allocatable, public atmos_sflx_lw
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:178
module Urban admin
real(rp), dimension(:,:,:), allocatable, public urban_tbl
subroutine, public urban_surface_get
Get surface boundary.
real(dp), public time_dtsec_urban
time interval of urban step [sec]
Definition: scale_time.F90:49
real(rp), dimension(:,:), allocatable, public urban_tr_t
real(rp), dimension(:,:,:), allocatable, public urban_tgl_t
real(rp), dimension(:,:), allocatable, public urban_sflx_gh
real(rp), dimension(:,:), allocatable, public urban_sflx_mv
real(rp), dimension(:,:), allocatable, public atmos_w
real(rp), dimension(:,:), allocatable, public urban_rainb
real(rp), dimension(:,:), allocatable, public urban_tc_t
real(rp), dimension(:,:), allocatable, public urban_roff_t
real(rp), dimension(:,:,:), allocatable, public urban_tbl_t
real(rp), dimension(:,:), allocatable, public urban_sflx_mw
module urban grid index
integer, public ja
of y whole cells (local, with HALO)