SCALE-RM
mod_urban_vars.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
10 !-------------------------------------------------------------------------------
12  !-----------------------------------------------------------------------------
13  !
14  !++ used modules
15  !
16  use scale_precision
17  use scale_stdio
18  use scale_prof
19  use scale_debug
22 
23  use scale_const, only: &
24  i_sw => const_i_sw, &
25  i_lw => const_i_lw
26  !-----------------------------------------------------------------------------
27  implicit none
28  private
29  !-----------------------------------------------------------------------------
30  !
31  !++ Public procedure
32  !
33  public :: urban_vars_setup
34  public :: urban_vars_restart_read
35  public :: urban_vars_restart_write
36  public :: urban_vars_history
37  public :: urban_vars_total
38  public :: urban_vars_external_in
39 
40  !-----------------------------------------------------------------------------
41  !
42  !++ Public parameters & variables
43  !
44  logical, public :: urban_restart_output = .false.
45 
46  character(len=H_LONG), public :: urban_restart_in_basename = ''
47  character(len=H_LONG), public :: urban_restart_out_basename = ''
48  character(len=H_MID), public :: urban_restart_out_title = 'URBAN restart'
49  character(len=H_MID), public :: urban_restart_out_dtype = 'DEFAULT'
50 
51  ! prognostic variables
52  real(RP), public, allocatable :: urban_tr (:,:) ! urban surface temperature of roof [K]
53  real(RP), public, allocatable :: urban_tb (:,:) ! urban surface temperature of wall [K]
54  real(RP), public, allocatable :: urban_tg (:,:) ! urban surface temperature of road [K]
55  real(RP), public, allocatable :: urban_tc (:,:) ! urban canopy air temperature [K]
56  real(RP), public, allocatable :: urban_qc (:,:) ! urban canopy humidity [kg/kg]
57  real(RP), public, allocatable :: urban_uc (:,:) ! urban canopy wind [m/s]
58  real(RP), public, allocatable :: urban_trl (:,:,:) ! urban temperature in layer of roof [K]
59  real(RP), public, allocatable :: urban_tbl (:,:,:) ! urban temperature in layer of wall [K]
60  real(RP), public, allocatable :: urban_tgl (:,:,:) ! urban temperature in layer of road [K]
61  real(RP), public, allocatable :: urban_rainr(:,:) ! urban rain storage on roof [mm=kg/m2]
62  real(RP), public, allocatable :: urban_rainb(:,:) ! urban rain storage on wall [mm=kg/m2]
63  real(RP), public, allocatable :: urban_raing(:,:) ! urban rain storage on road [mm=kg/m2]
64  real(RP), public, allocatable :: urban_roff (:,:) ! urban runoff [mm=kg/m2]
65 
66  ! tendency variables
67  real(RP), public, allocatable :: urban_trl_t (:,:,:) ! tendency of URBAN_TRL
68  real(RP), public, allocatable :: urban_tbl_t (:,:,:) ! tendency of URBAN_TBL
69  real(RP), public, allocatable :: urban_tgl_t (:,:,:) ! tendency of URBAN_TGL
70  real(RP), public, allocatable :: urban_tc_t (:,:) ! tendency of URBAN_TC
71  real(RP), public, allocatable :: urban_uc_t (:,:) ! tendency of URBAN_UC
72  real(RP), public, allocatable :: urban_qc_t (:,:) ! tendency of URBAN_QC
73  real(RP), public, allocatable :: urban_tr_t (:,:) ! tendency of URBAN_TR
74  real(RP), public, allocatable :: urban_tb_t (:,:) ! tendency of URBAN_TB
75  real(RP), public, allocatable :: urban_tg_t (:,:) ! tendency of URBAN_TG
76  real(RP), public, allocatable :: urban_rainr_t(:,:) ! tendency of URBAN_RAINR
77  real(RP), public, allocatable :: urban_rainb_t(:,:) ! tendency of URBAN_RAINB
78  real(RP), public, allocatable :: urban_raing_t(:,:) ! tendency of URBAN_RAING
79  real(RP), public, allocatable :: urban_roff_t (:,:) ! tendency of URBAN_ROFF
80 
81  ! for restart
82  real(RP), public, allocatable :: urban_sfc_temp (:,:) ! urban grid average of surface temperature [K]
83  real(RP), public, allocatable :: urban_sfc_albedo(:,:,:) ! urban grid average of albedo [0-1]
84  real(RP), public, allocatable :: urban_sflx_mw (:,:) ! urban grid average of w-momentum flux [kg/m2/s]
85  real(RP), public, allocatable :: urban_sflx_mu (:,:) ! urban grid average of u-momentum flux [kg/m2/s]
86  real(RP), public, allocatable :: urban_sflx_mv (:,:) ! urban grid average of v-momentum flux [kg/m2/s]
87  real(RP), public, allocatable :: urban_sflx_sh (:,:) ! urban grid average of sensible heat flux [W/m2]
88  real(RP), public, allocatable :: urban_sflx_lh (:,:) ! urban grid average of latent heat flux [W/m2]
89  real(RP), public, allocatable :: urban_sflx_gh (:,:) ! urban grid average of ground heat flux [W/m2]
90  real(RP), public, allocatable :: urban_sflx_evap (:,:) ! urban grid average of water vapor flux [kg/m2/s]
91 
92  ! diagnostic variables
93  real(RP), public, allocatable :: urban_z0m(:,:) ! urban grid average of rougness length (momentum) [m]
94  real(RP), public, allocatable :: urban_z0h(:,:) ! urban grid average of rougness length (heat) [m]
95  real(RP), public, allocatable :: urban_z0e(:,:) ! urban grid average of rougness length (vapor) [m]
96  real(RP), public, allocatable :: urban_u10(:,:) ! urban grid average of velocity u at 10m [m/s]
97  real(RP), public, allocatable :: urban_v10(:,:) ! urban grid average of velocity v at 10m [m/s]
98  real(RP), public, allocatable :: urban_t2 (:,:) ! urban grid average of temperature at 2m [K]
99  real(RP), public, allocatable :: urban_q2 (:,:) ! urban grid average of water vapor at 2m [kg/kg]
100 
101  ! recieved atmospheric variables
102  real(RP), public, allocatable :: atmos_temp (:,:)
103  real(RP), public, allocatable :: atmos_pres (:,:)
104  real(RP), public, allocatable :: atmos_w (:,:)
105  real(RP), public, allocatable :: atmos_u (:,:)
106  real(RP), public, allocatable :: atmos_v (:,:)
107  real(RP), public, allocatable :: atmos_dens (:,:)
108  real(RP), public, allocatable :: atmos_qv (:,:)
109  real(RP), public, allocatable :: atmos_pbl (:,:)
110  real(RP), public, allocatable :: atmos_sfc_pres (:,:)
111  real(RP), public, allocatable :: atmos_sflx_lw (:,:,:)
112  real(RP), public, allocatable :: atmos_sflx_sw (:,:,:)
113  real(RP), public, allocatable :: atmos_cossza (:,:)
114  real(RP), public, allocatable :: atmos_sflx_prec(:,:)
115 
116  !-----------------------------------------------------------------------------
117  !
118  !++ Private procedure
119  !
120  !-----------------------------------------------------------------------------
121  !
122  !++ Private parameters & variables
123  !
124  logical, private :: urban_vars_checkrange = .false.
125 
126  integer, private, parameter :: vmax = 23
127  integer, private, parameter :: i_tr = 1
128  integer, private, parameter :: i_tb = 2
129  integer, private, parameter :: i_tg = 3
130  integer, private, parameter :: i_tc = 4
131  integer, private, parameter :: i_qc = 5
132  integer, private, parameter :: i_uc = 6
133  integer, private, parameter :: i_trl = 7
134  integer, private, parameter :: i_tbl = 8
135  integer, private, parameter :: i_tgl = 9
136  integer, private, parameter :: i_rainr = 10
137  integer, private, parameter :: i_rainb = 11
138  integer, private, parameter :: i_raing = 12
139  integer, private, parameter :: i_roff = 13
140  integer, private, parameter :: i_sfc_temp = 14
141  integer, private, parameter :: i_alb_lw = 15
142  integer, private, parameter :: i_alb_sw = 16
143  integer, private, parameter :: i_sflx_mw = 17
144  integer, private, parameter :: i_sflx_mu = 18
145  integer, private, parameter :: i_sflx_mv = 19
146  integer, private, parameter :: i_sflx_sh = 20
147  integer, private, parameter :: i_sflx_lh = 21
148  integer, private, parameter :: i_sflx_gh = 22
149  integer, private, parameter :: i_sflx_evap = 23
150 
151  character(len=H_SHORT), private :: var_name(vmax)
152  character(len=H_MID), private :: var_desc(vmax)
153  character(len=H_SHORT), private :: var_unit(vmax)
154 
155  data var_name / 'URBAN_TR' , &
156  'URBAN_TB' , &
157  'URBAN_TG' , &
158  'URBAN_TC' , &
159  'URBAN_QC' , &
160  'URBAN_UC' , &
161  'URBAN_TRL' , &
162  'URBAN_TBL' , &
163  'URBAN_TGL' , &
164  'URBAN_RAINR' , &
165  'URBAN_RAINB' , &
166  'URBAN_RAING' , &
167  'URBAN_ROFF', &
168  'URBAN_SFC_TEMP', &
169  'URBAN_ALB_LW', &
170  'URBAN_ALB_SW', &
171  'URBAN_SFLX_MW', &
172  'URBAN_SFLX_MU', &
173  'URBAN_SFLX_MV', &
174  'URBAN_SFLX_SH', &
175  'URBAN_SFLX_LH', &
176  'URBAN_SFLX_GH', &
177  'URBAN_SFLX_evap' /
178 
179  data var_desc / 'urban surface temperature of roof', &
180  'urban surface temperature of wall', &
181  'urban surface temperature of road', &
182  'urban canopy air temperature', &
183  'urban canopy humidity', &
184  'urban canopy wind', &
185  'urban temperature in layer of roof', &
186  'urban temperature in layer of wall', &
187  'urban temperature in layer of road', &
188  'urban rain strage on roof', &
189  'urban rain strage on wall', &
190  'urban rain strage on road', &
191  'urban runoff ', &
192  'urban grid average of temperature', &
193  'urban grid average of albedo LW', &
194  'urban grid average of albedo SW', &
195  'urban grid average of w-momentum flux', &
196  'urban grid average of u-momentum flux', &
197  'urban grid average of v-momentum flux', &
198  'urban grid average of sensible heat flux', &
199  'urban grid average of latent heat flux', &
200  'urban grid average of ground heat flux', &
201  'urban grid average of water vapor flux' /
202 
203  data var_unit / 'K', &
204  'K', &
205  'K', &
206  'K', &
207  'kg/kg', &
208  'm/s', &
209  'K', &
210  'K', &
211  'K', &
212  'kg/m2', &
213  'kg/m2', &
214  'kg/m2', &
215  'kg/m2', &
216  'K', &
217  '0-1', &
218  '0-1', &
219  'kg/m2/s', &
220  'kg/m2/s', &
221  'kg/m2/s', &
222  'W/m2', &
223  'W/m2', &
224  'W/m2', &
225  'kg/m2/s' /
226 
227  !-----------------------------------------------------------------------------
228 contains
229  !-----------------------------------------------------------------------------
231  subroutine urban_vars_setup
232  use scale_process, only: &
234  use scale_const, only: &
235  undef => const_undef
236  implicit none
237 
238  namelist / param_urban_vars / &
244  urban_vars_checkrange
245 
246  integer :: ierr
247  integer :: iv
248  !---------------------------------------------------------------------------
249 
250  if( io_l ) write(io_fid_log,*)
251  if( io_l ) write(io_fid_log,*) '++++++ Module[VARS] / Categ[URBAN] / Origin[SCALE-RM]'
252 
253  allocate( urban_tr(ia,ja) )
254  allocate( urban_tb(ia,ja) )
255  allocate( urban_tg(ia,ja) )
256  allocate( urban_tc(ia,ja) )
257  allocate( urban_qc(ia,ja) )
258  allocate( urban_uc(ia,ja) )
259  allocate( urban_trl(uks:uke,ia,ja) )
260  allocate( urban_tbl(uks:uke,ia,ja) )
261  allocate( urban_tgl(uks:uke,ia,ja) )
262  allocate( urban_rainr(ia,ja) )
263  allocate( urban_rainb(ia,ja) )
264  allocate( urban_raing(ia,ja) )
265  allocate( urban_roff(ia,ja) )
266  urban_tr(:,:) = undef
267  urban_tb(:,:) = undef
268  urban_tg(:,:) = undef
269  urban_tc(:,:) = undef
270  urban_qc(:,:) = undef
271  urban_uc(:,:) = undef
272  urban_trl(:,:,:) = undef
273  urban_tbl(:,:,:) = undef
274  urban_tgl(:,:,:) = undef
275  urban_rainr(:,:) = undef
276  urban_rainb(:,:) = undef
277  urban_raing(:,:) = undef
278  urban_roff(:,:) = undef
279 
280  allocate( urban_tr_t(ia,ja) )
281  allocate( urban_tb_t(ia,ja) )
282  allocate( urban_tg_t(ia,ja) )
283  allocate( urban_tc_t(ia,ja) )
284  allocate( urban_qc_t(ia,ja) )
285  allocate( urban_uc_t(ia,ja) )
286  allocate( urban_trl_t(uks:uke,ia,ja) )
287  allocate( urban_tbl_t(uks:uke,ia,ja) )
288  allocate( urban_tgl_t(uks:uke,ia,ja) )
289  allocate( urban_rainr_t(ia,ja) )
290  allocate( urban_rainb_t(ia,ja) )
291  allocate( urban_raing_t(ia,ja) )
292  allocate( urban_roff_t(ia,ja) )
293  urban_tr_t(:,:) = undef
294  urban_tb_t(:,:) = undef
295  urban_tg_t(:,:) = undef
296  urban_tc_t(:,:) = undef
297  urban_qc_t(:,:) = undef
298  urban_uc_t(:,:) = undef
299  urban_trl_t(:,:,:) = undef
300  urban_tbl_t(:,:,:) = undef
301  urban_tgl_t(:,:,:) = undef
302  urban_rainr_t(:,:) = undef
303  urban_rainb_t(:,:) = undef
304  urban_raing_t(:,:) = undef
305  urban_roff_t(:,:) = undef
306 
307  allocate( urban_sfc_temp(ia,ja) )
308  allocate( urban_sfc_albedo(ia,ja,2) )
309  allocate( urban_sflx_mw(ia,ja) )
310  allocate( urban_sflx_mu(ia,ja) )
311  allocate( urban_sflx_mv(ia,ja) )
312  allocate( urban_sflx_sh(ia,ja) )
313  allocate( urban_sflx_lh(ia,ja) )
314  allocate( urban_sflx_gh(ia,ja) )
315  allocate( urban_sflx_evap(ia,ja) )
316  urban_sfc_temp(:,:) = undef
317  urban_sfc_albedo(:,:,:) = undef
318  urban_sflx_mw(:,:) = undef
319  urban_sflx_mu(:,:) = undef
320  urban_sflx_mv(:,:) = undef
321  urban_sflx_sh(:,:) = undef
322  urban_sflx_lh(:,:) = undef
323  urban_sflx_gh(:,:) = undef
324  urban_sflx_evap(:,:) = undef
325 
326  allocate( urban_z0m(ia,ja) )
327  allocate( urban_z0h(ia,ja) )
328  allocate( urban_z0e(ia,ja) )
329  allocate( urban_u10(ia,ja) )
330  allocate( urban_v10(ia,ja) )
331  allocate( urban_t2(ia,ja) )
332  allocate( urban_q2(ia,ja) )
333  urban_z0m(:,:) = undef
334  urban_z0h(:,:) = undef
335  urban_z0e(:,:) = undef
336  urban_u10(:,:) = undef
337  urban_v10(:,:) = undef
338  urban_t2(:,:) = undef
339  urban_q2(:,:) = undef
340 
341  allocate( atmos_temp(ia,ja) )
342  allocate( atmos_pres(ia,ja) )
343  allocate( atmos_w(ia,ja) )
344  allocate( atmos_u(ia,ja) )
345  allocate( atmos_v(ia,ja) )
346  allocate( atmos_dens(ia,ja) )
347  allocate( atmos_qv(ia,ja) )
348  allocate( atmos_pbl(ia,ja) )
349  allocate( atmos_sfc_pres(ia,ja) )
350  allocate( atmos_sflx_lw(ia,ja,2) )
351  allocate( atmos_sflx_sw(ia,ja,2) )
352  allocate( atmos_cossza(ia,ja) )
353  allocate( atmos_sflx_prec(ia,ja) )
354  atmos_temp(:,:) = undef
355  atmos_pres(:,:) = undef
356  atmos_w(:,:) = undef
357  atmos_u(:,:) = undef
358  atmos_v(:,:) = undef
359  atmos_dens(:,:) = undef
360  atmos_qv(:,:) = undef
361  atmos_pbl(:,:) = undef
362  atmos_sfc_pres(:,:) = undef
363  atmos_sflx_lw(:,:,:) = undef
364  atmos_sflx_sw(:,:,:) = undef
365  atmos_cossza(:,:) = undef
366  atmos_sflx_prec(:,:) = undef
367 
368  !--- read namelist
369  rewind(io_fid_conf)
370  read(io_fid_conf,nml=param_urban_vars,iostat=ierr)
371  if( ierr < 0 ) then !--- missing
372  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
373  elseif( ierr > 0 ) then !--- fatal error
374  write(*,*) 'xxx Not appropriate names in namelist PARAM_URBAN_VARS. Check!'
375  call prc_mpistop
376  endif
377  if( io_lnml ) write(io_fid_log,nml=param_urban_vars)
378 
379  if( io_l ) write(io_fid_log,*)
380  if( io_l ) write(io_fid_log,*) '*** List of prognostic variables (URBAN) ***'
381  if( io_l ) write(io_fid_log,'(1x,A,A15,A,A32,3(A))') &
382  '*** |','VARNAME ','|', 'DESCRIPTION ','[', 'UNIT ',']'
383  do iv = 1, vmax
384  if( io_l ) write(io_fid_log,'(1x,A,i3,A,A15,A,A32,3(A))') &
385  '*** NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
386  enddo
387 
388  if( io_l ) write(io_fid_log,*)
389  if ( urban_restart_in_basename /= '' ) then
390  if( io_l ) write(io_fid_log,*) '*** Restart input? : ', trim(urban_restart_in_basename)
391  else
392  if( io_l ) write(io_fid_log,*) '*** Restart input? : NO'
393  endif
394  if ( urban_restart_output &
395  .AND. urban_restart_out_basename /= '' ) then
396  if( io_l ) write(io_fid_log,*) '*** Restart output? : ', trim(urban_restart_out_basename)
397  else
398  if( io_l ) write(io_fid_log,*) '*** Restart output? : NO'
399  urban_restart_output = .false.
400  endif
401 
402  return
403  end subroutine urban_vars_setup
404 
405  !-----------------------------------------------------------------------------
407  subroutine urban_vars_restart_read
408  use scale_fileio, only: &
409  fileio_read
410  use mod_urban_admin, only: &
411  urban_sw
412  implicit none
413  !---------------------------------------------------------------------------
414 
415  if( io_l ) write(io_fid_log,*)
416  if( io_l ) write(io_fid_log,*) '*** Input restart file (URBAN) ***'
417 
418  if ( urban_sw .and. urban_restart_in_basename /= '' ) then
419  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(urban_restart_in_basename)
420 
421  call fileio_read( urban_tr(:,:), & ! [OUT]
422  urban_restart_in_basename, var_name(i_tr), 'XY', step=1 ) ! [IN]
423  call fileio_read( urban_tb(:,:), & ! [OUT]
424  urban_restart_in_basename, var_name(i_tb), 'XY', step=1 ) ! [IN]
425  call fileio_read( urban_tg(:,:), & ! [OUT]
426  urban_restart_in_basename, var_name(i_tg), 'XY', step=1 ) ! [IN]
427  call fileio_read( urban_tc(:,:), & ! [OUT]
428  urban_restart_in_basename, var_name(i_tc), 'XY', step=1 ) ! [IN]
429  call fileio_read( urban_qc(:,:), & ! [OUT]
430  urban_restart_in_basename, var_name(i_qc), 'XY', step=1 ) ! [IN]
431  call fileio_read( urban_uc(:,:), & ! [OUT]
432  urban_restart_in_basename, var_name(i_uc), 'XY', step=1 ) ! [IN]
433 
434  call fileio_read( urban_trl(:,:,:), & ! [OUT]
435  urban_restart_in_basename, var_name(i_trl), 'Urban', step=1 ) ! [IN]
436  call fileio_read( urban_tbl(:,:,:), & ! [OUT]
437  urban_restart_in_basename, var_name(i_tbl), 'Urban', step=1 ) ! [IN]
438  call fileio_read( urban_tgl(:,:,:), & ! [OUT]
439  urban_restart_in_basename, var_name(i_tgl), 'Urban', step=1 ) ! [IN]
440 
441  call fileio_read( urban_rainr(:,:), & ! [OUT]
442  urban_restart_in_basename, var_name(i_rainr), 'XY', step=1 ) ! [IN]
443  call fileio_read( urban_rainb(:,:), & ! [OUT]
444  urban_restart_in_basename, var_name(i_rainb), 'XY', step=1 ) ! [IN]
445  call fileio_read( urban_raing(:,:), & ! [OUT]
446  urban_restart_in_basename, var_name(i_raing), 'XY', step=1 ) ! [IN]
447  call fileio_read( urban_roff(:,:), & ! [OUT]
448  urban_restart_in_basename, var_name(i_roff), 'XY', step=1 ) ! [IN]
449 
450  call fileio_read( urban_sfc_temp(:,:), & ! [OUT]
451  urban_restart_in_basename, var_name(i_sfc_temp), 'XY', step=1 ) ! [IN]
452  call fileio_read( urban_sfc_albedo(:,:,i_lw), & ! [OUT]
453  urban_restart_in_basename, var_name(i_alb_lw), 'XY', step=1 ) ! [IN]
454  call fileio_read( urban_sfc_albedo(:,:,i_sw), & ! [OUT]
455  urban_restart_in_basename, var_name(i_alb_sw), 'XY', step=1 ) ! [IN]
456 
457  call fileio_read( urban_sflx_mw(:,:), & ! [OUT]
458  urban_restart_in_basename, var_name(i_sflx_mw), 'XY', step=1 ) ! [IN]
459  call fileio_read( urban_sflx_mu(:,:), & ! [OUT]
460  urban_restart_in_basename, var_name(i_sflx_mu), 'XY', step=1 ) ! [IN]
461  call fileio_read( urban_sflx_mv(:,:), & ! [OUT]
462  urban_restart_in_basename, var_name(i_sflx_mv), 'XY', step=1 ) ! [IN]
463  call fileio_read( urban_sflx_sh(:,:), & ! [OUT]
464  urban_restart_in_basename, var_name(i_sflx_sh), 'XY', step=1 ) ! [IN]
465  call fileio_read( urban_sflx_lh(:,:), & ! [OUT]
466  urban_restart_in_basename, var_name(i_sflx_lh), 'XY', step=1 ) ! [IN]
467  call fileio_read( urban_sflx_gh(:,:), & ! [OUT]
468  urban_restart_in_basename, var_name(i_sflx_gh), 'XY', step=1 ) ! [IN]
469  call fileio_read( urban_sflx_evap(:,:), & ! [OUT]
470  urban_restart_in_basename, var_name(i_sflx_evap), 'XY', step=1 ) ! [IN]
471 
472  call urban_vars_total
473 
474  else
475  if( io_l ) write(io_fid_log,*) '*** restart file for urban is not specified.'
476  endif
477 
478  return
479  end subroutine urban_vars_restart_read
480 
481  !-----------------------------------------------------------------------------
483  subroutine urban_vars_restart_write
484  use scale_time, only: &
486  use scale_fileio, only: &
487  fileio_write
488  use mod_urban_admin, only: &
489  urban_sw
490  implicit none
491 
492  character(len=20) :: timelabel
493  character(len=H_LONG) :: basename
494  !---------------------------------------------------------------------------
495 
496  if ( urban_sw .and. urban_restart_out_basename /= '' ) then
497 
498  call time_gettimelabel( timelabel )
499  write(basename,'(A,A,A)') trim(urban_restart_out_basename), '_', trim(timelabel)
500 
501  if( io_l ) write(io_fid_log,*)
502  if( io_l ) write(io_fid_log,*) '*** Output restart file (URBAN) ***'
503  if( io_l ) write(io_fid_log,*) '*** filename: ', trim(basename)
504 
505  call urban_vars_total
506 
507  call fileio_write( urban_tr(:,:), basename, urban_restart_out_title, & ! [IN]
508  var_name(i_tr), var_desc(i_tr), var_unit(i_tr), & ! [IN]
509  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
510  call fileio_write( urban_tb(:,:), basename, urban_restart_out_title, & ! [IN]
511  var_name(i_tb), var_desc(i_tb), var_unit(i_tb), & ! [IN]
512  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
513  call fileio_write( urban_tg(:,:), basename, urban_restart_out_title, & ! [IN]
514  var_name(i_tg), var_desc(i_tg), var_unit(i_tg), & ! [IN]
515  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
516  call fileio_write( urban_tc(:,:), basename, urban_restart_out_title, & ! [IN]
517  var_name(i_tc), var_desc(i_tc), var_unit(i_tc), & ! [IN]
518  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
519  call fileio_write( urban_qc(:,:), basename, urban_restart_out_title, & ! [IN]
520  var_name(i_qc), var_desc(i_qc), var_unit(i_qc), & ! [IN]
521  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
522  call fileio_write( urban_uc(:,:), basename, urban_restart_out_title, & ! [IN]
523  var_name(i_uc), var_desc(i_uc), var_unit(i_uc), & ! [IN]
524  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
525 
526  call fileio_write( urban_trl(:,:,:), basename, urban_restart_out_title, & ! [IN]
527  var_name(i_trl), var_desc(i_trl), var_unit(i_trl), & ! [IN]
528  'Urban', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
529  call fileio_write( urban_tbl(:,:,:), basename, urban_restart_out_title, & ! [IN]
530  var_name(i_tbl), var_desc(i_tbl), var_unit(i_tbl), & ! [IN]
531  'Urban', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
532  call fileio_write( urban_tgl(:,:,:), basename, urban_restart_out_title, & ! [IN]
533  var_name(i_tgl), var_desc(i_tgl), var_unit(i_tgl), & ! [IN]
534  'Urban', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
535 
536  call fileio_write( urban_rainr(:,:), basename, urban_restart_out_title, & ! [IN]
537  var_name(i_rainr), var_desc(i_rainr), var_unit(i_rainr), & ! [IN]
538  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
539  call fileio_write( urban_rainb(:,:), basename, urban_restart_out_title, & ! [IN]
540  var_name(i_rainb), var_desc(i_rainb), var_unit(i_rainb), & ! [IN]
541  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
542  call fileio_write( urban_raing(:,:), basename, urban_restart_out_title, & ! [IN]
543  var_name(i_raing), var_desc(i_raing), var_unit(i_raing), & ! [IN]
544  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
545  call fileio_write( urban_roff(:,:), basename, urban_restart_out_title, & ! [IN]
546  var_name(i_roff), var_desc(i_roff), var_unit(i_roff), & ! [IN]
547  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
548 
549  call fileio_write( urban_sfc_temp(:,:), basename, urban_restart_out_title, & ! [IN]
550  var_name(i_sfc_temp), var_desc(i_sfc_temp), var_unit(i_sfc_temp), & ! [IN]
551  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
552  call fileio_write( urban_sfc_albedo(:,:,i_lw), basename, urban_restart_out_title, & ! [IN]
553  var_name(i_alb_lw), var_desc(i_alb_lw), var_unit(i_alb_lw), & ! [IN]
554  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
555  call fileio_write( urban_sfc_albedo(:,:,i_sw), basename, urban_restart_out_title, & ! [IN]
556  var_name(i_alb_sw), var_desc(i_alb_sw), var_unit(i_alb_sw), & ! [IN]
557  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
558 
559  call fileio_write( urban_sflx_mw(:,:), basename, urban_restart_out_title, & ! [IN]
560  var_name(i_sflx_mw), var_desc(i_sflx_mw), var_unit(i_sflx_mw), & ! [IN]
561  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
562  call fileio_write( urban_sflx_mu(:,:), basename, urban_restart_out_title, & ! [IN]
563  var_name(i_sflx_mu), var_desc(i_sflx_mu), var_unit(i_sflx_mu), & ! [IN]
564  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
565  call fileio_write( urban_sflx_mv(:,:), basename, urban_restart_out_title, & ! [IN]
566  var_name(i_sflx_mv), var_desc(i_sflx_mv), var_unit(i_sflx_mv), & ! [IN]
567  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
568  call fileio_write( urban_sflx_sh(:,:), basename, urban_restart_out_title, & ! [IN]
569  var_name(i_sflx_sh), var_desc(i_sflx_sh), var_unit(i_sflx_sh), & ! [IN]
570  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
571  call fileio_write( urban_sflx_lh(:,:), basename, urban_restart_out_title, & ! [IN]
572  var_name(i_sflx_lh), var_desc(i_sflx_lh), var_unit(i_sflx_lh), & ! [IN]
573  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
574  call fileio_write( urban_sflx_gh(:,:), basename, urban_restart_out_title, & ! [IN]
575  var_name(i_sflx_gh), var_desc(i_sflx_gh), var_unit(i_sflx_gh), & ! [IN]
576  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
577  call fileio_write( urban_sflx_evap(:,:), basename, urban_restart_out_title, & ! [IN]
578  var_name(i_sflx_evap), var_desc(i_sflx_evap), var_unit(i_sflx_evap), & ! [IN]
579  'XY', urban_restart_out_dtype, nohalo=.true. ) ! [IN]
580 
581  endif
582 
583  return
584  end subroutine urban_vars_restart_write
585 
586  !-----------------------------------------------------------------------------
588  subroutine urban_vars_history
589  use scale_history, only: &
590  hist_in
591  implicit none
592  !---------------------------------------------------------------------------
593 
594  if ( urban_vars_checkrange ) then
595  call valcheck( urban_tr(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_tr), &
596  __file__, __line__ )
597  call valcheck( urban_tb(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_tb), &
598  __file__, __line__ )
599  call valcheck( urban_tg(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_tg), &
600  __file__, __line__ )
601  call valcheck( urban_tc(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_tc), &
602  __file__, __line__ )
603  call valcheck( urban_qc(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_qc), &
604  __file__, __line__ )
605  call valcheck( urban_uc(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_uc), &
606  __file__, __line__ )
607  call valcheck( urban_trl(:,is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_trl), &
608  __file__, __line__ )
609  call valcheck( urban_tbl(:,is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_tbl), &
610  __file__, __line__ )
611  call valcheck( urban_tgl(:,is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_tgl), &
612  __file__, __line__ )
613  call valcheck( urban_rainr(is:ie,js:je), -1000.0_rp, 1000.0_rp, var_name(i_rainr), &
614  __file__, __line__ )
615  call valcheck( urban_rainb(is:ie,js:je), -1000.0_rp, 1000.0_rp, var_name(i_rainb), &
616  __file__, __line__ )
617  call valcheck( urban_raing(is:ie,js:je), -1000.0_rp, 1000.0_rp, var_name(i_raing), &
618  __file__, __line__ )
619  call valcheck( urban_roff(is:ie,js:je), -1000.0_rp, 1000.0_rp, var_name(i_roff), &
620  __file__, __line__ )
621  call valcheck( urban_sfc_temp(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_sfc_temp), &
622  __file__, __line__ )
623  call valcheck( urban_sfc_albedo(is:ie,js:je,i_lw), 0.0_rp, 2.0_rp, var_name(i_alb_lw), &
624  __file__, __line__ )
625  call valcheck( urban_sfc_albedo(is:ie,js:je,i_sw), 0.0_rp, 2.0_rp, var_name(i_alb_sw), &
626  __file__, __line__ )
627  endif
628 
629  call hist_in( urban_tr(:,:), var_name(i_tr), var_desc(i_tr), var_unit(i_tr) )
630  call hist_in( urban_tb(:,:), var_name(i_tb), var_desc(i_tb), var_unit(i_tb) )
631  call hist_in( urban_tg(:,:), var_name(i_tg), var_desc(i_tg), var_unit(i_tg) )
632  call hist_in( urban_tc(:,:), var_name(i_tc), var_desc(i_tc), var_unit(i_tc) )
633  call hist_in( urban_qc(:,:), var_name(i_qc), var_desc(i_qc), var_unit(i_qc) )
634  call hist_in( urban_uc(:,:), var_name(i_uc), var_desc(i_uc), var_unit(i_uc) )
635 
636  call hist_in( urban_trl(:,:,:), var_name(i_trl), var_desc(i_trl), var_unit(i_trl), zdim='urban' )
637  call hist_in( urban_tbl(:,:,:), var_name(i_tbl), var_desc(i_tbl), var_unit(i_tbl), zdim='urban' )
638  call hist_in( urban_tgl(:,:,:), var_name(i_tgl), var_desc(i_tgl), var_unit(i_tgl), zdim='urban' )
639 
640  call hist_in( urban_rainr(:,:), var_name(i_rainr), var_desc(i_rainr), var_unit(i_rainr) )
641  call hist_in( urban_rainb(:,:), var_name(i_rainb), var_desc(i_rainb), var_unit(i_rainb) )
642  call hist_in( urban_raing(:,:), var_name(i_raing), var_desc(i_raing), var_unit(i_raing) )
643  call hist_in( urban_roff(:,:), var_name(i_roff), var_desc(i_roff), var_unit(i_roff) )
644 
645  call hist_in( urban_sfc_temp(:,:), var_name(i_sfc_temp), var_desc(i_sfc_temp), var_unit(i_sfc_temp) )
646  call hist_in( urban_sfc_albedo(:,:,i_lw), var_name(i_alb_lw), var_desc(i_alb_lw), var_unit(i_alb_lw) )
647  call hist_in( urban_sfc_albedo(:,:,i_sw), var_name(i_alb_sw), var_desc(i_alb_sw), var_unit(i_alb_sw) )
648 
649  call hist_in( urban_sflx_mw(:,:), var_name(i_sflx_mw), var_desc(i_sflx_mw), var_unit(i_sflx_mw) )
650  call hist_in( urban_sflx_mu(:,:), var_name(i_sflx_mu), var_desc(i_sflx_mu), var_unit(i_sflx_mu) )
651  call hist_in( urban_sflx_mv(:,:), var_name(i_sflx_mv), var_desc(i_sflx_mv), var_unit(i_sflx_mv) )
652  call hist_in( urban_sflx_sh(:,:), var_name(i_sflx_sh), var_desc(i_sflx_sh), var_unit(i_sflx_sh) )
653  call hist_in( urban_sflx_lh(:,:), var_name(i_sflx_lh), var_desc(i_sflx_lh), var_unit(i_sflx_lh) )
654  call hist_in( urban_sflx_gh(:,:), var_name(i_sflx_gh), var_desc(i_sflx_gh), var_unit(i_sflx_gh) )
655  call hist_in( urban_sflx_evap(:,:), var_name(i_sflx_evap), var_desc(i_sflx_evap), var_unit(i_sflx_evap) )
656 
657  return
658  end subroutine urban_vars_history
659 
660  !-----------------------------------------------------------------------------
662  subroutine urban_vars_total
663  use scale_rm_statistics, only: &
665  stat_total
666  implicit none
667 
668  real(RP) :: total
669  integer :: k
670  !---------------------------------------------------------------------------
671 
672  if ( statistics_checktotal ) then
673  call stat_total( total, urban_tr(:,:), var_name(i_tr) )
674  call stat_total( total, urban_tb(:,:), var_name(i_tb) )
675  call stat_total( total, urban_tg(:,:), var_name(i_tg) )
676  call stat_total( total, urban_tc(:,:), var_name(i_tc) )
677  call stat_total( total, urban_qc(:,:), var_name(i_qc) )
678  call stat_total( total, urban_uc(:,:), var_name(i_uc) )
679 
680  do k = uks, uke
681  call stat_total( total, urban_trl(k,:,:), var_name(i_trl) )
682  call stat_total( total, urban_tbl(k,:,:), var_name(i_tbl) )
683  call stat_total( total, urban_tgl(k,:,:), var_name(i_tgl) )
684  enddo
685 
686  call stat_total( total, urban_rainr(:,:), var_name(i_rainr) )
687  call stat_total( total, urban_rainb(:,:), var_name(i_rainb) )
688  call stat_total( total, urban_raing(:,:), var_name(i_raing) )
689  call stat_total( total, urban_roff(:,:), var_name(i_roff) )
690 
691  call stat_total( total, urban_sfc_temp(:,:), var_name(i_sfc_temp) )
692  call stat_total( total, urban_sfc_albedo(:,:,i_lw), var_name(i_alb_lw) )
693  call stat_total( total, urban_sfc_albedo(:,:,i_sw), var_name(i_alb_sw) )
694 
695  call stat_total( total, urban_sflx_mw(:,:), var_name(i_sflx_mw) )
696  call stat_total( total, urban_sflx_mu(:,:), var_name(i_sflx_mu) )
697  call stat_total( total, urban_sflx_mv(:,:), var_name(i_sflx_mv) )
698  call stat_total( total, urban_sflx_sh(:,:), var_name(i_sflx_sh) )
699  call stat_total( total, urban_sflx_lh(:,:), var_name(i_sflx_lh) )
700  call stat_total( total, urban_sflx_gh(:,:), var_name(i_sflx_gh) )
701  call stat_total( total, urban_sflx_evap(:,:), var_name(i_sflx_evap) )
702 
703  endif
704 
705  return
706  end subroutine urban_vars_total
707 
708  !-----------------------------------------------------------------------------
710  subroutine urban_vars_external_in( &
711  URBAN_TC_in, &
712  URBAN_QC_in, &
713  URBAN_UC_in, &
714  URBAN_SFC_TEMP_in, &
715  URBAN_SFC_albedo_in )
716  implicit none
717 
718  real(RP), intent(in) :: URBAN_TC_in (ia,ja)
719  real(RP), intent(in) :: URBAN_QC_in (ia,ja)
720  real(RP), intent(in) :: URBAN_UC_in (ia,ja)
721  real(RP), intent(in) :: URBAN_SFC_TEMP_in (ia,ja)
722  real(RP), intent(in) :: URBAN_SFC_albedo_in(ia,ja,2)
723 
724  integer :: k
725  !---------------------------------------------------------------------------
726 
727  if( io_l ) write(io_fid_log,*)
728  if( io_l ) write(io_fid_log,*) '*** External Input (coupler) ***'
729 
730  urban_tr(:,:) = urban_sfc_temp_in(:,:)
731  urban_tb(:,:) = urban_sfc_temp_in(:,:)
732  urban_tg(:,:) = urban_sfc_temp_in(:,:)
733 
734  urban_tc(:,:) = urban_tc_in(:,:)
735  urban_qc(:,:) = urban_qc_in(:,:)
736  urban_uc(:,:) = urban_uc_in(:,:)
737 
738  do k = uks, uke
739  urban_trl(k,:,:) = urban_sfc_temp_in(:,:)
740  urban_tbl(k,:,:) = urban_sfc_temp_in(:,:)
741  urban_tgl(k,:,:) = urban_sfc_temp_in(:,:)
742  end do
743 
744  urban_rainr(:,:) = 0.0_rp
745  urban_rainb(:,:) = 0.0_rp
746  urban_raing(:,:) = 0.0_rp
747  urban_roff(:,:) = 0.0_rp
748 
749  urban_sfc_temp(:,:) = urban_sfc_temp_in(:,:)
750  urban_sfc_albedo(:,:,:) = urban_sfc_albedo_in(:,:,:)
751 
752  urban_z0m(:,:) = 2.0_rp ! tentative, will be replace in urban scheme
753  urban_z0h(:,:) = 0.2_rp ! tentative, will be replace in urban scheme
754  urban_z0e(:,:) = 0.2_rp ! tentative, will be replace in urban scheme
755  urban_sflx_mw(:,:) = 0.0_rp
756  urban_sflx_mu(:,:) = 0.0_rp
757  urban_sflx_mv(:,:) = 0.0_rp
758  urban_sflx_sh(:,:) = 0.0_rp
759  urban_sflx_lh(:,:) = 0.0_rp
760  urban_sflx_gh(:,:) = 0.0_rp
761  urban_sflx_evap(:,:) = 0.0_rp
762 
763  call urban_vars_total
764 
765  return
766  end subroutine urban_vars_external_in
767 
768 end module mod_urban_vars
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 statistics_checktotal
calc&report variable totals to logfile?
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
subroutine, public prc_mpistop
Abort MPI.
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
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.
subroutine, public urban_vars_restart_read
Read urban restart.
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
subroutine, public urban_vars_external_in(URBAN_TC_in, URBAN_QC_in, URBAN_UC_in, URBAN_SFC_TEMP_in, URBAN_SFC_albedo_in)
Input from External I/O.
module URBAN Variables
real(rp), dimension(:,:), allocatable, public urban_raing
module FILE I/O (netcdf)
real(rp), dimension(:,:), allocatable, public urban_uc
real(rp), dimension(:,:), allocatable, public atmos_sflx_prec
real(rp), public const_undef
Definition: scale_const.F90:43
module Statistics
subroutine, public urban_vars_restart_write
Write urban restart.
module grid index
real(rp), dimension(:,:), allocatable, public atmos_pbl
real(rp), dimension(:,:), allocatable, public urban_sflx_sh
character(len=h_long), public urban_restart_out_basename
basename of the output file
real(rp), dimension(:,:), allocatable, public urban_tr
integer, public ia
of x whole cells (local, with HALO)
real(rp), dimension(:,:,:), allocatable, public urban_tgl
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
real(rp), dimension(:,:), allocatable, public atmos_qv
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
real(rp), dimension(:,:), allocatable, public atmos_cossza
real(rp), dimension(:,:), allocatable, public urban_uc_t
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
module PROCESS
real(rp), dimension(:,:), allocatable, public atmos_dens
subroutine, public urban_vars_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
character(len=h_mid), public urban_restart_out_dtype
REAL4 or REAL8.
real(rp), dimension(:,:), allocatable, public urban_tc
real(rp), dimension(:,:), allocatable, public atmos_pres
logical, public urban_restart_output
output restart file?
real(rp), dimension(:,:), allocatable, public urban_rainr
module profiler
Definition: scale_prof.F90:10
integer, public ie
end point of inner domain: x, local
logical, public io_lnml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:60
real(rp), dimension(:,:), allocatable, public atmos_temp
integer, public const_i_sw
short-wave radiation index
Definition: scale_const.F90:99
module PRECISION
module HISTORY
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
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
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
module Urban admin
real(rp), dimension(:,:,:), allocatable, public urban_tbl
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
character(len=h_long), public urban_restart_in_basename
basename of the restart file
real(rp), dimension(:,:), allocatable, public urban_roff_t
real(rp), dimension(:,:,:), allocatable, public urban_tbl_t
real(rp), dimension(:,:), allocatable, public urban_sflx_mw
character(len=h_mid), public urban_restart_out_title
title of the output file
module urban grid index
integer, public ja
of y whole cells (local, with HALO)