SCALE-RM
mod_land_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 :: land_vars_setup
34  public :: land_vars_restart_read
35  public :: land_vars_restart_write
36  public :: land_vars_history
37  public :: land_vars_total
38  public :: land_vars_external_in
39 
40  public :: convert_ws2vwc
41 
42  !-----------------------------------------------------------------------------
43  !
44  !++ Public parameters & variables
45  !
46  logical, public :: land_restart_output = .false.
47 
48  character(len=H_LONG), public :: land_restart_in_basename = ''
49  character(len=H_LONG), public :: land_restart_out_basename = ''
50  character(len=H_MID), public :: land_restart_out_title = 'LAND restart'
51  character(len=H_MID), public :: land_restart_out_dtype = 'DEFAULT'
52 
53  ! prognostic variables
54  real(RP), public, allocatable :: land_temp (:,:,:)
55  real(RP), public, allocatable :: land_water (:,:,:)
56  real(RP), public, allocatable :: land_sfc_temp (:,:)
57  real(RP), public, allocatable :: land_sfc_albedo(:,:,:)
58 
59  ! tendency variables
60  real(RP), public, allocatable :: land_temp_t (:,:,:)
61  real(RP), public, allocatable :: land_water_t (:,:,:)
62  real(RP), public, allocatable :: land_sfc_temp_t (:,:)
63  real(RP), public, allocatable :: land_sfc_albedo_t(:,:,:)
64 
65  ! surface variables for restart
66  real(RP), public, allocatable :: land_sflx_mw (:,:)
67  real(RP), public, allocatable :: land_sflx_mu (:,:)
68  real(RP), public, allocatable :: land_sflx_mv (:,:)
69  real(RP), public, allocatable :: land_sflx_sh (:,:)
70  real(RP), public, allocatable :: land_sflx_lh (:,:)
71  real(RP), public, allocatable :: land_sflx_gh (:,:)
72  real(RP), public, allocatable :: land_sflx_evap(:,:)
73 
74  ! diagnostic variables
75  real(RP), public, allocatable :: land_u10(:,:)
76  real(RP), public, allocatable :: land_v10(:,:)
77  real(RP), public, allocatable :: land_t2 (:,:)
78  real(RP), public, allocatable :: land_q2 (:,:)
79 
80  ! recieved atmospheric variables
81  real(RP), public, allocatable :: atmos_temp (:,:)
82  real(RP), public, allocatable :: atmos_pres (:,:)
83  real(RP), public, allocatable :: atmos_w (:,:)
84  real(RP), public, allocatable :: atmos_u (:,:)
85  real(RP), public, allocatable :: atmos_v (:,:)
86  real(RP), public, allocatable :: atmos_dens (:,:)
87  real(RP), public, allocatable :: atmos_qv (:,:)
88  real(RP), public, allocatable :: atmos_pbl (:,:)
89  real(RP), public, allocatable :: atmos_sfc_pres (:,:)
90  real(RP), public, allocatable :: atmos_sflx_lw (:,:)
91  real(RP), public, allocatable :: atmos_sflx_sw (:,:)
92  real(RP), public, allocatable :: atmos_cossza (:,:)
93  real(RP), public, allocatable :: atmos_sflx_prec(:,:)
94 
95  real(RP), public, allocatable :: land_property (:,:,:)
96 
97  character(len=H_LONG), public :: land_property_in_filename = ''
98 
99  integer, public, parameter :: land_property_nmax = 8
100  integer, public, parameter :: i_waterlimit = 1 ! maximum soil moisture [m3/m3]
101  integer, public, parameter :: i_watercritical = 2 ! critical soil moisture [m3/m3]
102  integer, public, parameter :: i_thermalcond = 3 ! thermal conductivity for soil [W/K/m]
103  integer, public, parameter :: i_heatcapacity = 4 ! heat capacity for soil [J/K/m3]
104  integer, public, parameter :: i_waterdiff = 5 ! moisture diffusivity in the soil [m2/s]
105  integer, public, parameter :: i_z0m = 6 ! roughness length for momemtum [m]
106  integer, public, parameter :: i_z0h = 7 ! roughness length for heat [m]
107  integer, public, parameter :: i_z0e = 8 ! roughness length for vapor [m]
108 
109  !-----------------------------------------------------------------------------
110  !
111  !++ Private procedure
112  !
113  private :: land_param_read
114 
115  !-----------------------------------------------------------------------------
116  !
117  !++ Private parameters & variables
118  !
119  logical, private :: land_vars_checkrange = .false.
120 
121  integer, private, parameter :: vmax = 13
122  integer, private, parameter :: i_temp = 1
123  integer, private, parameter :: i_water = 2
124  integer, private, parameter :: i_waterds = 3
125  integer, private, parameter :: i_sfc_temp = 4
126  integer, private, parameter :: i_alb_lw = 5
127  integer, private, parameter :: i_alb_sw = 6
128  integer, private, parameter :: i_sflx_mw = 7
129  integer, private, parameter :: i_sflx_mu = 8
130  integer, private, parameter :: i_sflx_mv = 9
131  integer, private, parameter :: i_sflx_sh = 10
132  integer, private, parameter :: i_sflx_lh = 11
133  integer, private, parameter :: i_sflx_gh = 12
134  integer, private, parameter :: i_sflx_evap = 13
135 
136  character(len=H_SHORT), private :: var_name(vmax)
137  character(len=H_MID), private :: var_desc(vmax)
138  character(len=H_SHORT), private :: var_unit(vmax)
139 
140  data var_name / 'LAND_TEMP', &
141  'LAND_WATER', &
142  'LAND_DSAT', &
143  'LAND_SFC_TEMP', &
144  'LAND_ALB_LW', &
145  'LAND_ALB_SW', &
146  'LAND_SFLX_MW', &
147  'LAND_SFLX_MU', &
148  'LAND_SFLX_MV', &
149  'LAND_SFLX_SH', &
150  'LAND_SFLX_LH', &
151  'LAND_SFLX_GH', &
152  'LAND_SFLX_evap' /
153  data var_desc / 'temperature at each soil layer', &
154  'moisture at each soil layer', &
155  'degree of saturation at each soil layer', &
156  'land surface skin temperature', &
157  'land surface albedo (longwave)', &
158  'land surface albedo (shortwave)', &
159  'land surface w-momentum flux', &
160  'land surface u-momentum flux', &
161  'land surface v-momentum flux', &
162  'land surface sensible heat flux', &
163  'land surface latent heat flux', &
164  'land surface ground heat flux', &
165  'land surface water vapor flux' /
166  data var_unit / 'K', &
167  'm3/m3', &
168  '0-1', &
169  'K', &
170  '0-1', &
171  '0-1', &
172  'kg/m2/s', &
173  'kg/m2/s', &
174  'kg/m2/s', &
175  'J/m2/s', &
176  'J/m2/s', &
177  'J/m2/s', &
178  'kg/m2/s' /
179 
180  real(RP), private, allocatable :: land_property_table(:,:)
181 
182  integer, private :: land_qa_comm
183  real(RP), private, allocatable :: work_comm(:,:,:) ! for communication
184 
185  !-----------------------------------------------------------------------------
186 contains
187  !-----------------------------------------------------------------------------
189  subroutine land_vars_setup
190  use scale_process, only: &
192  use scale_const, only: &
193  undef => const_undef
194  use scale_comm, only: &
195  comm_vars8, &
196  comm_wait
197  use scale_landuse, only: &
200  implicit none
201 
202  namelist / param_land_vars / &
208  land_vars_checkrange
209 
210  integer :: ierr
211  integer :: i, j, iv, p
212  !---------------------------------------------------------------------------
213 
214  if( io_l ) write(io_fid_log,*)
215  if( io_l ) write(io_fid_log,*) '++++++ Module[VARS] / Categ[LAND] / Origin[SCALE-RM]'
216 
217  allocate( land_temp(lkmax,ia,ja) )
218  allocate( land_water(lkmax,ia,ja) )
219  allocate( land_sfc_temp(ia,ja) )
220  allocate( land_sfc_albedo(ia,ja,2) )
221  land_temp(:,:,:) = undef
222  land_water(:,:,:) = undef
223  land_sfc_temp(:,:) = undef
224  land_sfc_albedo(:,:,:) = undef
225 
226  allocate( land_temp_t(lkmax,ia,ja) )
227  allocate( land_water_t(lkmax,ia,ja) )
228  allocate( land_sfc_temp_t(ia,ja) )
229  allocate( land_sfc_albedo_t(ia,ja,2) )
230  land_temp_t(:,:,:) = undef
231  land_water_t(:,:,:) = undef
232  land_sfc_temp_t(:,:) = undef
233  land_sfc_albedo_t(:,:,:) = undef
234 
235  allocate( land_sflx_mw(ia,ja) )
236  allocate( land_sflx_mu(ia,ja) )
237  allocate( land_sflx_mv(ia,ja) )
238  allocate( land_sflx_sh(ia,ja) )
239  allocate( land_sflx_lh(ia,ja) )
240  allocate( land_sflx_gh(ia,ja) )
241  allocate( land_sflx_evap(ia,ja) )
242  land_sflx_mw(:,:) = undef
243  land_sflx_mu(:,:) = undef
244  land_sflx_mv(:,:) = undef
245  land_sflx_sh(:,:) = undef
246  land_sflx_lh(:,:) = undef
247  land_sflx_gh(:,:) = undef
248  land_sflx_evap(:,:) = undef
249 
250  allocate( land_u10(ia,ja) )
251  allocate( land_v10(ia,ja) )
252  allocate( land_t2(ia,ja) )
253  allocate( land_q2(ia,ja) )
254  land_u10(:,:) = undef
255  land_v10(:,:) = undef
256  land_t2(:,:) = undef
257  land_q2(:,:) = undef
258 
259  allocate( atmos_temp(ia,ja) )
260  allocate( atmos_pres(ia,ja) )
261  allocate( atmos_w(ia,ja) )
262  allocate( atmos_u(ia,ja) )
263  allocate( atmos_v(ia,ja) )
264  allocate( atmos_dens(ia,ja) )
265  allocate( atmos_qv(ia,ja) )
266  allocate( atmos_pbl(ia,ja) )
267  allocate( atmos_sfc_pres(ia,ja) )
268  allocate( atmos_sflx_lw(ia,ja) )
269  allocate( atmos_sflx_sw(ia,ja) )
270  allocate( atmos_cossza(ia,ja) )
271  allocate( atmos_sflx_prec(ia,ja) )
272  atmos_temp(:,:) = undef
273  atmos_pres(:,:) = undef
274  atmos_w(:,:) = undef
275  atmos_u(:,:) = undef
276  atmos_v(:,:) = undef
277  atmos_dens(:,:) = undef
278  atmos_qv(:,:) = undef
279  atmos_pbl(:,:) = undef
280  atmos_sfc_pres(:,:) = undef
281  atmos_sflx_lw(:,:) = undef
282  atmos_sflx_sw(:,:) = undef
283  atmos_cossza(:,:) = undef
284  atmos_sflx_prec(:,:) = undef
285 
286  land_qa_comm = lkmax &
287  + lkmax &
288  + 1 &
289  + 2
290 
291  allocate( work_comm(ia,ja,land_qa_comm) )
292 
293  !--- read namelist
294  rewind(io_fid_conf)
295  read(io_fid_conf,nml=param_land_vars,iostat=ierr)
296  if( ierr < 0 ) then !--- missing
297  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
298  elseif( ierr > 0 ) then !--- fatal error
299  write(*,*) 'xxx Not appropriate names in namelist PARAM_LAND_VARS. Check!'
300  call prc_mpistop
301  endif
302  if( io_lnml ) write(io_fid_log,nml=param_land_vars)
303 
304  if( io_l ) write(io_fid_log,*)
305  if( io_l ) write(io_fid_log,*) '*** List of prognostic variables (LAND) ***'
306  if( io_l ) write(io_fid_log,'(1x,A,A15,A,A32,3(A))') &
307  '*** |','VARNAME ','|', 'DESCRIPTION ','[', 'UNIT ',']'
308  do iv = 1, vmax
309  if( io_l ) write(io_fid_log,'(1x,A,i3,A,A15,A,A32,3(A))') &
310  '*** NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
311  enddo
312 
313  if( io_l ) write(io_fid_log,*)
314  if ( land_restart_in_basename /= '' ) then
315  if( io_l ) write(io_fid_log,*) '*** Restart input? : ', trim(land_restart_in_basename)
316  else
317  if( io_l ) write(io_fid_log,*) '*** Restart input? : NO'
318  endif
319  if ( land_restart_output &
320  .AND. land_restart_out_basename /= '' ) then
321  if( io_l ) write(io_fid_log,*) '*** Restart output? : ', trim(land_restart_out_basename)
322  else
323  if( io_l ) write(io_fid_log,*) '*** Restart output? : NO'
324  land_restart_output = .false.
325  endif
326 
327  ! Read land property table
328  allocate( land_property_table(landuse_pft_nmax,land_property_nmax) )
329  land_property_table(:,:) = undef
330 
331  call land_param_read
332 
333  ! Apply land property to 2D map
335 
336  ! tentative, mosaic is off
337  do p = 1, land_property_nmax
338  do j = js, je
339  do i = is, ie
340  land_property(i,j,p) = land_property_table( landuse_index_pft(i,j,1), p )
341  enddo
342  enddo
343  enddo
344 
345  do p = 1, land_property_nmax
346  call comm_vars8( land_property(:,:,p), p )
347  enddo
348  do p = 1, land_property_nmax
349  call comm_wait ( land_property(:,:,p), p )
350  enddo
351 
352  return
353  end subroutine land_vars_setup
354 
355  !-----------------------------------------------------------------------------
357  subroutine land_vars_restart_read
358  use scale_fileio, only: &
359  fileio_read
360  use mod_land_admin, only: &
361  land_sw
362  implicit none
363  !---------------------------------------------------------------------------
364 
365  if( io_l ) write(io_fid_log,*)
366  if( io_l ) write(io_fid_log,*) '*** Input restart file (LAND) ***'
367 
368  if ( land_sw .and. land_restart_in_basename /= '' ) then
369  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(land_restart_in_basename)
370 
371  call fileio_read( land_temp(:,:,:), & ! [OUT]
372  land_restart_in_basename, var_name(i_temp), 'Land', step=1 ) ! [IN]
373  call fileio_read( land_water(:,:,:), & ! [OUT]
374  land_restart_in_basename, var_name(i_water), 'Land', step=1 ) ! [IN]
375  call fileio_read( land_sfc_temp(:,:), & ! [OUT]
376  land_restart_in_basename, var_name(i_sfc_temp), 'XY', step=1 ) ! [IN]
377  call fileio_read( land_sfc_albedo(:,:,i_lw), & ! [OUT]
378  land_restart_in_basename, var_name(i_alb_lw), 'XY', step=1 ) ! [IN]
379  call fileio_read( land_sfc_albedo(:,:,i_sw), & ! [OUT]
380  land_restart_in_basename, var_name(i_alb_sw), 'XY', step=1 ) ! [IN]
381  call fileio_read( land_sflx_mw(:,:), & ! [OUT]
382  land_restart_in_basename, var_name(i_sflx_mw), 'XY', step=1 ) ! [IN]
383  call fileio_read( land_sflx_mu(:,:), & ! [OUT]
384  land_restart_in_basename, var_name(i_sflx_mu), 'XY', step=1 ) ! [IN]
385  call fileio_read( land_sflx_mv(:,:), & ! [OUT]
386  land_restart_in_basename, var_name(i_sflx_mv), 'XY', step=1 ) ! [IN]
387  call fileio_read( land_sflx_sh(:,:), & ! [OUT]
388  land_restart_in_basename, var_name(i_sflx_sh), 'XY', step=1 ) ! [IN]
389  call fileio_read( land_sflx_lh(:,:), & ! [OUT]
390  land_restart_in_basename, var_name(i_sflx_lh), 'XY', step=1 ) ! [IN]
391  call fileio_read( land_sflx_gh(:,:), & ! [OUT]
392  land_restart_in_basename, var_name(i_sflx_gh), 'XY', step=1 ) ! [IN]
393  call fileio_read( land_sflx_evap(:,:), & ! [OUT]
394  land_restart_in_basename, var_name(i_sflx_evap), 'XY', step=1 ) ! [IN]
395 
396  call land_vars_total
397  else
398  if( io_l ) write(io_fid_log,*) '*** restart file for land is not specified.'
399  endif
400 
401  return
402  end subroutine land_vars_restart_read
403 
404  !-----------------------------------------------------------------------------
406  subroutine land_vars_restart_write
407  use scale_time, only: &
409  use scale_fileio, only: &
410  fileio_write
411  use mod_land_admin, only: &
412  land_sw
413  implicit none
414 
415  character(len=20) :: timelabel
416  character(len=H_LONG) :: basename
417  !---------------------------------------------------------------------------
418 
419  if ( land_sw .and. land_restart_out_basename /= '' ) then
420 
421  call time_gettimelabel( timelabel )
422  write(basename,'(A,A,A)') trim(land_restart_out_basename), '_', trim(timelabel)
423 
424  if( io_l ) write(io_fid_log,*)
425  if( io_l ) write(io_fid_log,*) '*** Output restart file (LAND) ***'
426  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
427 
428  call land_vars_total
429 
430  call fileio_write( land_temp(:,:,:), basename, land_restart_out_title, & ! [IN]
431  var_name(i_temp), var_desc(i_temp), var_unit(i_temp), & ! [IN]
432  'Land', land_restart_out_dtype, nohalo=.true. ) ! [IN]
433  call fileio_write( land_water(:,:,:), basename, land_restart_out_title, & ! [IN]
434  var_name(i_water), var_desc(i_water), var_unit(i_water), & ! [IN]
435  'Land', land_restart_out_dtype, nohalo=.true. ) ! [IN]
436  call fileio_write( land_sfc_temp(:,:), basename, land_restart_out_title, & ! [IN]
437  var_name(i_sfc_temp), var_desc(i_sfc_temp), var_unit(i_sfc_temp), & ! [IN]
438  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
439  call fileio_write( land_sfc_albedo(:,:,i_lw), basename, land_restart_out_title, & ! [IN]
440  var_name(i_alb_lw), var_desc(i_alb_lw), var_unit(i_alb_lw), & ! [IN]
441  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
442  call fileio_write( land_sfc_albedo(:,:,i_sw), basename, land_restart_out_title, & ! [IN]
443  var_name(i_alb_sw), var_desc(i_alb_sw), var_unit(i_alb_sw), & ! [IN]
444  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
445  call fileio_write( land_sflx_mw(:,:), basename, land_restart_out_title, & ! [IN]
446  var_name(i_sflx_mw), var_desc(i_sflx_mw), var_unit(i_sflx_mw), & ! [IN]
447  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
448  call fileio_write( land_sflx_mu(:,:), basename, land_restart_out_title, & ! [IN]
449  var_name(i_sflx_mu), var_desc(i_sflx_mu), var_unit(i_sflx_mu), & ! [IN]
450  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
451  call fileio_write( land_sflx_mv(:,:), basename, land_restart_out_title, & ! [IN]
452  var_name(i_sflx_mv), var_desc(i_sflx_mv), var_unit(i_sflx_mv), & ! [IN]
453  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
454  call fileio_write( land_sflx_sh(:,:), basename, land_restart_out_title, & ! [IN]
455  var_name(i_sflx_sh), var_desc(i_sflx_sh), var_unit(i_sflx_sh), & ! [IN]
456  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
457  call fileio_write( land_sflx_lh(:,:), basename, land_restart_out_title, & ! [IN]
458  var_name(i_sflx_lh), var_desc(i_sflx_lh), var_unit(i_sflx_lh), & ! [IN]
459  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
460  call fileio_write( land_sflx_gh(:,:), basename, land_restart_out_title, & ! [IN]
461  var_name(i_sflx_gh), var_desc(i_sflx_gh), var_unit(i_sflx_gh), & ! [IN]
462  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
463  call fileio_write( land_sflx_evap(:,:), basename, land_restart_out_title, & ! [IN]
464  var_name(i_sflx_evap), var_desc(i_sflx_evap), var_unit(i_sflx_evap), & ! [IN]
465  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
466 
467  endif
468 
469  return
470  end subroutine land_vars_restart_write
471 
472  !-----------------------------------------------------------------------------
474  subroutine land_vars_history
475  use scale_history, only: &
476  hist_in
477  implicit none
478 
479  real(RP) :: LAND_WATERDS(lkmax,ia,ja)
480  integer :: k, i, j
481  !---------------------------------------------------------------------------
482 
483  if ( land_vars_checkrange ) then
484  call valcheck( land_temp(:,is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_temp), &
485  __file__, __line__ )
486  call valcheck( land_water(:,is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_water), &
487  __file__, __line__ )
488  call valcheck( land_sfc_temp(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_sfc_temp), &
489  __file__, __line__ )
490  call valcheck( land_sfc_albedo(is:ie,js:je,i_lw), 0.0_rp, 2.0_rp, var_name(i_alb_lw), &
491  __file__, __line__ )
492  call valcheck( land_sfc_albedo(is:ie,js:je,i_sw), 0.0_rp, 2.0_rp, var_name(i_alb_sw), &
493  __file__, __line__ )
494  endif
495 
496  call hist_in( land_temp(:,:,:), var_name(i_temp), var_desc(i_temp), var_unit(i_temp), zdim='land' )
497  call hist_in( land_water(:,:,:), var_name(i_water), var_desc(i_water), var_unit(i_water), zdim='land' )
498  do j = js, je
499  do i = is, ie
500  do k = 1, lkmax
501  land_waterds(k,i,j) = land_water(k,i,j) / land_property(i,j,i_waterlimit)
502  end do
503  end do
504  end do
505  call hist_in( land_waterds(:,:,:), var_name(i_waterds), var_desc(i_waterds), var_unit(i_waterds), zdim='land', nohalo=.true. )
506 
507 
508  call hist_in( land_sfc_temp(:,:), var_name(i_sfc_temp), var_desc(i_sfc_temp), var_unit(i_sfc_temp) )
509  call hist_in( land_sfc_albedo(:,:,i_lw), var_name(i_alb_lw), var_desc(i_alb_lw), var_unit(i_alb_lw) )
510  call hist_in( land_sfc_albedo(:,:,i_sw), var_name(i_alb_sw), var_desc(i_alb_sw), var_unit(i_alb_sw) )
511 
512  call hist_in( land_sflx_mw(:,:), var_name(i_sflx_mw), var_desc(i_sflx_mw), var_unit(i_sflx_mw) )
513  call hist_in( land_sflx_mu(:,:), var_name(i_sflx_mu), var_desc(i_sflx_mu), var_unit(i_sflx_mu) )
514  call hist_in( land_sflx_mv(:,:), var_name(i_sflx_mv), var_desc(i_sflx_mv), var_unit(i_sflx_mv) )
515  call hist_in( land_sflx_sh(:,:), var_name(i_sflx_sh), var_desc(i_sflx_sh), var_unit(i_sflx_sh) )
516  call hist_in( land_sflx_lh(:,:), var_name(i_sflx_lh), var_desc(i_sflx_lh), var_unit(i_sflx_lh) )
517  call hist_in( land_sflx_gh(:,:), var_name(i_sflx_gh), var_desc(i_sflx_gh), var_unit(i_sflx_gh) )
518  call hist_in( land_sflx_evap(:,:), var_name(i_sflx_evap), var_desc(i_sflx_evap), var_unit(i_sflx_evap) )
519 
520  return
521  end subroutine land_vars_history
522 
523  !-----------------------------------------------------------------------------
525  subroutine land_vars_total
526  use scale_rm_statistics, only: &
528  stat_total
529  implicit none
530 
531  real(RP) :: total
532 
533  character(len=2) :: sk
534  integer :: k
535  !---------------------------------------------------------------------------
536 
537  if ( statistics_checktotal ) then
538 
539  do k = lks, lke
540  write(sk,'(I2.2)') k
541 
542  call stat_total( total, land_temp(k,:,:), trim(var_name(i_temp) )//sk )
543  call stat_total( total, land_water(k,:,:), trim(var_name(i_water))//sk )
544  enddo
545 
546  call stat_total( total, land_sfc_temp(:,:), var_name(i_sfc_temp) )
547  call stat_total( total, land_sfc_albedo(:,:,i_lw), var_name(i_alb_lw) )
548  call stat_total( total, land_sfc_albedo(:,:,i_sw), var_name(i_alb_sw) )
549 
550  endif
551 
552  return
553  end subroutine land_vars_total
554 
555  !-----------------------------------------------------------------------------
557  subroutine land_vars_external_in( &
558  LAND_TEMP_in, &
559  LAND_WATER_in, &
560  LAND_SFC_TEMP_in, &
561  LAND_SFC_albedo_in )
562  implicit none
563 
564  real(RP), intent(in) :: LAND_TEMP_in (:,:,:)
565  real(RP), intent(in) :: LAND_WATER_in(:,:,:)
566  real(RP), intent(in) :: LAND_SFC_TEMP_in (ia,ja)
567  real(RP), intent(in) :: LAND_SFC_albedo_in(ia,ja,2)
568  !---------------------------------------------------------------------------
569 
570  if( io_l ) write(io_fid_log,*)
571  if( io_l ) write(io_fid_log,*) '*** External Input (land) ***'
572 
573  land_temp(:,:,:) = land_temp_in(:,:,:)
574  land_water(:,:,:) = land_water_in(:,:,:)
575  land_sfc_temp(:,:) = land_sfc_temp_in(:,:)
576  land_sfc_albedo(:,:,:) = land_sfc_albedo_in(:,:,:)
577 
578  land_sflx_mw(:,:) = 0.0_rp
579  land_sflx_mu(:,:) = 0.0_rp
580  land_sflx_mv(:,:) = 0.0_rp
581  land_sflx_sh(:,:) = 0.0_rp
582  land_sflx_lh(:,:) = 0.0_rp
583  land_sflx_gh(:,:) = 0.0_rp
584  land_sflx_evap(:,:) = 0.0_rp
585 
586  call land_vars_total
587 
588  return
589  end subroutine land_vars_external_in
590 
591  !-----------------------------------------------------------------------------
593  subroutine land_param_read
594  use scale_process, only: &
596  use scale_landuse, only: &
598  implicit none
599 
600  integer :: index
601  character(len=H_LONG) :: description
602  real(RP) :: STRGMAX
603  real(RP) :: STRGCRT
604  real(RP) :: TCS
605  real(RP) :: HCS
606  real(RP) :: DFW
607  real(RP) :: Z0M
608  real(RP) :: Z0H
609  real(RP) :: Z0E
610 
611  namelist / param_land_property / &
613 
614  namelist / param_land_data / &
615  index, &
616  description, &
617  strgmax, &
618  strgcrt, &
619  tcs, &
620  hcs, &
621  dfw, &
622  z0m, &
623  z0h, &
624  z0e
625 
626  integer :: n
627  integer :: ierr
628 
629  integer :: IO_FID_LAND_PROPERTY
630  !---------------------------------------------------------------------------
631 
632  !--- read namelist
633  rewind(io_fid_conf)
634  read(io_fid_conf,nml=param_land_property,iostat=ierr)
635  if( ierr < 0 ) then !--- missing
636  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
637  elseif( ierr > 0 ) then !--- fatal error
638  write(*,*) 'xxx Not appropriate names in namelist PARAM_LAND_PROPERTY. Check!'
639  call prc_mpistop
640  endif
641  if( io_lnml ) write(io_fid_log,nml=param_land_property)
642 
643  if( land_property_in_filename /= '' ) then
644  !--- Open land parameter file
645  io_fid_land_property = io_get_available_fid()
646  open( io_fid_land_property, &
647  file = trim(land_property_in_filename), &
648  form = 'formatted', &
649  status = 'old', &
650  iostat = ierr )
651 
652  if( ierr /= 0 ) then
653  if( io_l ) write(io_fid_log,*) 'Error: Failed to open land parameter file! :', trim(land_property_in_filename)
654  call prc_mpistop
655  else
656  if( io_l ) write(io_fid_log,*)
657  if( io_l ) write(io_fid_log,*) '*** Properties for each plant functional type (PFT)'
658  if( io_l ) write(io_fid_log,*) &
659  '--------------------------------------------------------------------------------------------------------'
660  if( io_l ) write(io_fid_log,'(1x,A,11(1x,A))') '*** ', &
661  ' description', &
662  ' Max Stg.', &
663  ' CRT Stg.', &
664  ' T condu.', &
665  ' H capac.', &
666  ' DFC Wat.', &
667  ' Z0(m)', &
668  ' Z0(h)', &
669  ' Z0(e)'
670 
671  !--- read namelist
672  rewind(io_fid_land_property)
673 
674  do n = 1, landuse_pft_nmax
675  ! undefined roughness length
676  z0h = -1.0_rp
677  z0e = -1.0_rp
678 
679  read(io_fid_land_property,nml=param_land_data,iostat=ierr)
680  if ( ierr < 0 ) then !--- no more data
681  exit
682  elseif( ierr > 0 ) then !--- fatal error
683  write(*,*) 'xxx Not appropriate names in namelist PARAM_LAND_DATA. Check!'
684  call prc_mpistop
685  endif
686 
687  if( z0h < 0.0_rp ) then
688  z0h = z0m / 7.4_rp ! defined by Garratt and Francey (1978)
689  endif
690  if( z0e < 0.0_rp ) then
691  z0e = z0m / 7.4_rp ! defined by Garratt and Francey (1978)
692  endif
693 
694  land_property_table(index,i_waterlimit ) = strgmax
695  land_property_table(index,i_watercritical) = strgcrt
696  land_property_table(index,i_thermalcond ) = tcs
697  land_property_table(index,i_heatcapacity ) = hcs
698  land_property_table(index,i_waterdiff ) = dfw
699  land_property_table(index,i_z0m ) = z0m
700  land_property_table(index,i_z0h ) = z0h
701  land_property_table(index,i_z0e ) = z0e
702 
703  if( io_l ) write(io_fid_log,'(1x,A8,I3,1x,A12,3(1x,F9.2),(1x,ES9.1),4(1x,F9.2))') &
704  '*** IDX =', index, &
705  trim(description), &
706  strgmax, &
707  strgcrt, &
708  tcs, &
709  hcs, &
710  dfw, &
711  z0m, &
712  z0h, &
713  z0e
714  enddo
715 
716  end if
717 
718  close( io_fid_land_property )
719 
720  if( io_l ) write(io_fid_log,*) &
721  '--------------------------------------------------------------------------------------------------------'
722 
723  endif
724 
725  return
726  end subroutine land_param_read
727 
728  !-----------------------------------------------------------------------------
730  function convert_ws2vwc( WS, critical ) result( VWC )
731  implicit none
732 
733  real(RP), intent(in) :: WS(ia,ja) ! water saturation [fraction]
734  logical, intent(in) :: critical ! is I_WaterCritical used?
735 
736  real(RP) :: VWC(ia,ja) ! volumetric water content [m3/m3]
737 
738  ! work
739  integer :: i, j, num
740  !---------------------------------------------------------------------------
741 
742  if( critical ) then
743  num = i_watercritical
744  else
745  num = i_waterlimit
746  end if
747 
748  do j = js, je
749  do i = is, ie
750  vwc(i,j) = max( min( ws(i,j)*land_property(i,j,num), land_property(i,j,num) ), 0.0_rp )
751  end do
752  end do
753 
754  return
755  end function convert_ws2vwc
756 
757 end module mod_land_vars
module Land admin
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?
real(rp), dimension(:,:), allocatable, public land_v10
land surface velocity v at 10m [m/s]
integer, public je
end point of inner domain: y, local
real(rp), dimension(:,:), allocatable, public land_sflx_mw
land surface w-momentum flux [kg/m2/s]
integer, public const_i_lw
long-wave radiation index
Definition: scale_const.F90:98
subroutine, public prc_mpistop
Abort MPI.
logical, public land_restart_output
output restart file?
integer, parameter, public i_heatcapacity
integer, parameter, public i_waterlimit
real(rp), dimension(:,:), allocatable, public atmos_qv
real(rp), dimension(:,:), allocatable, public land_sflx_sh
land surface sensible heat flux [J/m2/s]
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
real(rp), dimension(:,:), allocatable, public atmos_pbl
subroutine, public land_vars_setup
Setup.
real(rp), dimension(:,:), allocatable, public atmos_sflx_prec
real(rp), dimension(:,:), allocatable, public atmos_u
module STDIO
Definition: scale_stdio.F90:12
integer, parameter, public i_watercritical
real(rp), dimension(:,:,:), allocatable, public land_sfc_albedo_t
tendency of LAND_SFC_albedo
real(rp), dimension(:,:), allocatable, public land_sflx_lh
land surface latent heat flux [J/m2/s]
character(len=h_long), public land_restart_in_basename
basename of the restart file
real(rp), dimension(:,:), allocatable, public atmos_w
integer, parameter, public i_z0h
module FILE I/O (netcdf)
real(rp), dimension(:,:), allocatable, public land_sflx_evap
land surface water vapor flux [kg/m2/s]
integer, parameter, public i_z0e
real(rp), public const_undef
Definition: scale_const.F90:43
module Statistics
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
subroutine, public land_vars_restart_read
Read land restart.
real(rp), dimension(:,:), allocatable, public atmos_pres
module grid index
real(rp), dimension(:,:), allocatable, public land_sfc_temp
land surface skin temperature [K]
real(rp), dimension(:,:), allocatable, public atmos_temp
real(rp), dimension(:,:), allocatable, public land_sflx_mu
land surface u-momentum flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_q2
land surface water vapor at 2m [kg/kg]
integer, public ia
of x whole cells (local, with HALO)
real(rp), dimension(:,:), allocatable, public land_t2
land surface temperature at 2m [K]
integer function, public io_get_available_fid()
search & get available file ID
module LANDUSE
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
real(rp) function, dimension(ia, ja), public convert_ws2vwc(WS, critical)
conversion from water saturation [fraction] to volumetric water content [m3/m3]
character(len=h_long), public land_restart_out_basename
basename of the output file
real(rp), dimension(:,:,:), allocatable, public land_temp
temperature of each soil layer [K]
module COMMUNICATION
Definition: scale_comm.F90:23
integer, public js
start point of inner domain: y, local
module TIME
Definition: scale_time.F90:15
module PROCESS
real(rp), dimension(:,:), allocatable, public land_u10
land surface velocity u at 10m [m/s]
integer, dimension(:,:,:), allocatable, public landuse_index_pft
index of PFT for each mosaic
real(rp), dimension(:,:,:), allocatable, public land_water_t
tendency of LAND_WATER
real(rp), dimension(:,:,:), allocatable, public land_sfc_albedo
land surface albedo [0-1]
module LAND Variables
real(rp), dimension(:,:), allocatable, public land_sfc_temp_t
tendency of LAND_SFC_TEMP
module CONSTANT
Definition: scale_const.F90:14
real(rp), dimension(:,:), allocatable, public atmos_dens
real(rp), dimension(:,:), allocatable, public land_sflx_gh
land surface heat flux [J/m2/s]
real(rp), dimension(:,:), allocatable, public atmos_v
real(rp), dimension(:,:,:), allocatable, public land_water
moisture of each soil layer [m3/m3]
subroutine, public land_vars_external_in(LAND_TEMP_in, LAND_WATER_in, LAND_SFC_TEMP_in, LAND_SFC_albedo_in)
Input from External I/O.
character(len=h_mid), public land_restart_out_dtype
REAL4 or REAL8.
subroutine, public land_vars_total
Budget monitor for land.
module profiler
Definition: scale_prof.F90:10
real(rp), dimension(:,:), allocatable, public land_sflx_mv
land surface v-momentum flux [kg/m2/s]
character(len=h_mid), public land_restart_out_title
title of the output file
integer, public ie
end point of inner domain: x, local
real(rp), dimension(:,:,:), allocatable, public land_temp_t
tendency of LAND_TEMP
integer, parameter, public i_z0m
character(len=h_long), public land_property_in_filename
the file of land parameter table
logical, public io_lnml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:60
integer, public const_i_sw
short-wave radiation index
Definition: scale_const.F90:99
module PRECISION
module HISTORY
subroutine, public land_vars_history
History output set for land variables.
integer, public landuse_pft_nmax
number of plant functional type(PFT)
module land grid index
integer, parameter, public land_property_nmax
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
logical, public land_sw
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
subroutine, public land_vars_restart_write
Write land restart.
real(rp), dimension(:,:), allocatable, public atmos_sflx_sw
integer, parameter, public i_thermalcond
real(rp), dimension(:,:), allocatable, public atmos_cossza
integer, parameter, public i_waterdiff
real(rp), dimension(:,:,:), allocatable, public land_property
land surface property
real(rp), dimension(:,:), allocatable, public atmos_sflx_lw
integer, public ja
of y whole cells (local, with HALO)