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 :: land_vars_restart_create
42  public :: land_vars_restart_enddef
44  public :: land_vars_restart_close
45 
46  public :: convert_ws2vwc
47 
48  !-----------------------------------------------------------------------------
49  !
50  !++ Public parameters & variables
51  !
52  logical, public :: land_restart_output = .false.
53 
54  character(len=H_LONG), public :: land_restart_in_basename = ''
55  character(len=H_LONG), public :: land_restart_out_basename = ''
56  character(len=H_MID), public :: land_restart_out_title = 'LAND restart'
57  character(len=H_MID), public :: land_restart_out_dtype = 'DEFAULT'
58 
59  ! prognostic variables
60  real(RP), public, allocatable :: land_temp (:,:,:)
61  real(RP), public, allocatable :: land_water (:,:,:)
62  real(RP), public, allocatable :: land_sfc_temp (:,:)
63  real(RP), public, allocatable :: land_sfc_albedo(:,:,:)
64 
65  ! tendency variables
66  real(RP), public, allocatable :: land_temp_t (:,:,:)
67  real(RP), public, allocatable :: land_water_t (:,:,:)
68  real(RP), public, allocatable :: land_sfc_temp_t (:,:)
69  real(RP), public, allocatable :: land_sfc_albedo_t(:,:,:)
70 
71  ! surface variables for restart
72  real(RP), public, allocatable :: land_sflx_mw (:,:)
73  real(RP), public, allocatable :: land_sflx_mu (:,:)
74  real(RP), public, allocatable :: land_sflx_mv (:,:)
75  real(RP), public, allocatable :: land_sflx_sh (:,:)
76  real(RP), public, allocatable :: land_sflx_lh (:,:)
77  real(RP), public, allocatable :: land_sflx_gh (:,:)
78  real(RP), public, allocatable :: land_sflx_evap(:,:)
79 
80  ! diagnostic variables
81  real(RP), public, allocatable :: land_u10(:,:)
82  real(RP), public, allocatable :: land_v10(:,:)
83  real(RP), public, allocatable :: land_t2 (:,:)
84  real(RP), public, allocatable :: land_q2 (:,:)
85 
86  ! recieved atmospheric variables
87  real(RP), public, allocatable :: atmos_temp (:,:)
88  real(RP), public, allocatable :: atmos_pres (:,:)
89  real(RP), public, allocatable :: atmos_w (:,:)
90  real(RP), public, allocatable :: atmos_u (:,:)
91  real(RP), public, allocatable :: atmos_v (:,:)
92  real(RP), public, allocatable :: atmos_dens (:,:)
93  real(RP), public, allocatable :: atmos_qv (:,:)
94  real(RP), public, allocatable :: atmos_pbl (:,:)
95  real(RP), public, allocatable :: atmos_sfc_pres (:,:)
96  real(RP), public, allocatable :: atmos_sflx_lw (:,:)
97  real(RP), public, allocatable :: atmos_sflx_sw (:,:)
98  real(RP), public, allocatable :: atmos_cossza (:,:)
99  real(RP), public, allocatable :: atmos_sflx_prec(:,:)
100 
101  real(RP), public, allocatable :: land_property (:,:,:)
102 
103  character(len=H_LONG), public :: land_property_in_filename = ''
104 
105  integer, public, parameter :: land_property_nmax = 8
106  integer, public, parameter :: i_waterlimit = 1 ! maximum soil moisture [m3/m3]
107  integer, public, parameter :: i_watercritical = 2 ! critical soil moisture [m3/m3]
108  integer, public, parameter :: i_thermalcond = 3 ! thermal conductivity for soil [W/K/m]
109  integer, public, parameter :: i_heatcapacity = 4 ! heat capacity for soil [J/K/m3]
110  integer, public, parameter :: i_waterdiff = 5 ! moisture diffusivity in the soil [m2/s]
111  integer, public, parameter :: i_z0m = 6 ! roughness length for momemtum [m]
112  integer, public, parameter :: i_z0h = 7 ! roughness length for heat [m]
113  integer, public, parameter :: i_z0e = 8 ! roughness length for vapor [m]
114 
115  !-----------------------------------------------------------------------------
116  !
117  !++ Private procedure
118  !
119  private :: land_param_read
120 
121  !-----------------------------------------------------------------------------
122  !
123  !++ Private parameters & variables
124  !
125  logical, private :: land_vars_checkrange = .false.
126 
127  integer, private, parameter :: vmax = 13
128  integer, private, parameter :: i_temp = 1
129  integer, private, parameter :: i_water = 2
130  integer, private, parameter :: i_waterds = 3
131  integer, private, parameter :: i_sfc_temp = 4
132  integer, private, parameter :: i_alb_lw = 5
133  integer, private, parameter :: i_alb_sw = 6
134  integer, private, parameter :: i_sflx_mw = 7
135  integer, private, parameter :: i_sflx_mu = 8
136  integer, private, parameter :: i_sflx_mv = 9
137  integer, private, parameter :: i_sflx_sh = 10
138  integer, private, parameter :: i_sflx_lh = 11
139  integer, private, parameter :: i_sflx_gh = 12
140  integer, private, parameter :: i_sflx_evap = 13
141 
142  character(len=H_SHORT), private :: var_name(vmax)
143  character(len=H_MID), private :: var_desc(vmax)
144  character(len=H_SHORT), private :: var_unit(vmax)
145  integer, private :: var_id(vmax)
146  integer, private :: restart_fid = -1 ! file ID
147 
148  data var_name / 'LAND_TEMP', &
149  'LAND_WATER', &
150  'LAND_DSAT', &
151  'LAND_SFC_TEMP', &
152  'LAND_ALB_LW', &
153  'LAND_ALB_SW', &
154  'LAND_SFLX_MW', &
155  'LAND_SFLX_MU', &
156  'LAND_SFLX_MV', &
157  'LAND_SFLX_SH', &
158  'LAND_SFLX_LH', &
159  'LAND_SFLX_GH', &
160  'LAND_SFLX_evap' /
161  data var_desc / 'temperature at each soil layer', &
162  'moisture at each soil layer', &
163  'degree of saturation at each soil layer', &
164  'land surface skin temperature', &
165  'land surface albedo (longwave)', &
166  'land surface albedo (shortwave)', &
167  'land surface w-momentum flux', &
168  'land surface u-momentum flux', &
169  'land surface v-momentum flux', &
170  'land surface sensible heat flux', &
171  'land surface latent heat flux', &
172  'land surface ground heat flux', &
173  'land surface water vapor flux' /
174  data var_unit / 'K', &
175  'm3/m3', &
176  '0-1', &
177  'K', &
178  '0-1', &
179  '0-1', &
180  'kg/m2/s', &
181  'kg/m2/s', &
182  'kg/m2/s', &
183  'J/m2/s', &
184  'J/m2/s', &
185  'J/m2/s', &
186  'kg/m2/s' /
187 
188  real(RP), private, allocatable :: land_property_table(:,:)
189 
190  integer, private :: land_qa_comm
191  real(RP), private, allocatable :: work_comm(:,:,:) ! for communication
192 
193  !-----------------------------------------------------------------------------
194 contains
195  !-----------------------------------------------------------------------------
197  subroutine land_vars_setup
198  use scale_process, only: &
200  use scale_const, only: &
201  undef => const_undef
202  use scale_comm, only: &
203  comm_vars8, &
204  comm_wait
205  use scale_landuse, only: &
208  implicit none
209 
210  namelist / param_land_vars / &
216  land_vars_checkrange
217 
218  integer :: ierr
219  integer :: i, j, iv, p
220  !---------------------------------------------------------------------------
221 
222  if( io_l ) write(io_fid_log,*)
223  if( io_l ) write(io_fid_log,*) '++++++ Module[VARS] / Categ[LAND] / Origin[SCALE-RM]'
224 
225  allocate( land_temp(lkmax,ia,ja) )
226  allocate( land_water(lkmax,ia,ja) )
227  allocate( land_sfc_temp(ia,ja) )
228  allocate( land_sfc_albedo(ia,ja,2) )
229  land_temp(:,:,:) = undef
230  land_water(:,:,:) = undef
231  land_sfc_temp(:,:) = undef
232  land_sfc_albedo(:,:,:) = undef
233 
234  allocate( land_temp_t(lkmax,ia,ja) )
235  allocate( land_water_t(lkmax,ia,ja) )
236  allocate( land_sfc_temp_t(ia,ja) )
237  allocate( land_sfc_albedo_t(ia,ja,2) )
238  land_temp_t(:,:,:) = undef
239  land_water_t(:,:,:) = undef
240  land_sfc_temp_t(:,:) = undef
241  land_sfc_albedo_t(:,:,:) = undef
242 
243  allocate( land_sflx_mw(ia,ja) )
244  allocate( land_sflx_mu(ia,ja) )
245  allocate( land_sflx_mv(ia,ja) )
246  allocate( land_sflx_sh(ia,ja) )
247  allocate( land_sflx_lh(ia,ja) )
248  allocate( land_sflx_gh(ia,ja) )
249  allocate( land_sflx_evap(ia,ja) )
250  land_sflx_mw(:,:) = undef
251  land_sflx_mu(:,:) = undef
252  land_sflx_mv(:,:) = undef
253  land_sflx_sh(:,:) = undef
254  land_sflx_lh(:,:) = undef
255  land_sflx_gh(:,:) = undef
256  land_sflx_evap(:,:) = undef
257 
258  allocate( land_u10(ia,ja) )
259  allocate( land_v10(ia,ja) )
260  allocate( land_t2(ia,ja) )
261  allocate( land_q2(ia,ja) )
262  land_u10(:,:) = undef
263  land_v10(:,:) = undef
264  land_t2(:,:) = undef
265  land_q2(:,:) = undef
266 
267  allocate( atmos_temp(ia,ja) )
268  allocate( atmos_pres(ia,ja) )
269  allocate( atmos_w(ia,ja) )
270  allocate( atmos_u(ia,ja) )
271  allocate( atmos_v(ia,ja) )
272  allocate( atmos_dens(ia,ja) )
273  allocate( atmos_qv(ia,ja) )
274  allocate( atmos_pbl(ia,ja) )
275  allocate( atmos_sfc_pres(ia,ja) )
276  allocate( atmos_sflx_lw(ia,ja) )
277  allocate( atmos_sflx_sw(ia,ja) )
278  allocate( atmos_cossza(ia,ja) )
279  allocate( atmos_sflx_prec(ia,ja) )
280  atmos_temp(:,:) = undef
281  atmos_pres(:,:) = undef
282  atmos_w(:,:) = undef
283  atmos_u(:,:) = undef
284  atmos_v(:,:) = undef
285  atmos_dens(:,:) = undef
286  atmos_qv(:,:) = undef
287  atmos_pbl(:,:) = undef
288  atmos_sfc_pres(:,:) = undef
289  atmos_sflx_lw(:,:) = undef
290  atmos_sflx_sw(:,:) = undef
291  atmos_cossza(:,:) = undef
292  atmos_sflx_prec(:,:) = undef
293 
294  land_qa_comm = lkmax &
295  + lkmax &
296  + 1 &
297  + 2
298 
299  allocate( work_comm(ia,ja,land_qa_comm) )
300 
301  !--- read namelist
302  rewind(io_fid_conf)
303  read(io_fid_conf,nml=param_land_vars,iostat=ierr)
304  if( ierr < 0 ) then !--- missing
305  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
306  elseif( ierr > 0 ) then !--- fatal error
307  write(*,*) 'xxx Not appropriate names in namelist PARAM_LAND_VARS. Check!'
308  call prc_mpistop
309  endif
310  if( io_lnml ) write(io_fid_log,nml=param_land_vars)
311 
312  if( io_l ) write(io_fid_log,*)
313  if( io_l ) write(io_fid_log,*) '*** List of prognostic variables (LAND) ***'
314  if( io_l ) write(io_fid_log,'(1x,A,A15,A,A32,3(A))') &
315  '*** |','VARNAME ','|', 'DESCRIPTION ','[', 'UNIT ',']'
316  do iv = 1, vmax
317  if( io_l ) write(io_fid_log,'(1x,A,i3,A,A15,A,A32,3(A))') &
318  '*** NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
319  enddo
320 
321  if( io_l ) write(io_fid_log,*)
322  if ( land_restart_in_basename /= '' ) then
323  if( io_l ) write(io_fid_log,*) '*** Restart input? : ', trim(land_restart_in_basename)
324  else
325  if( io_l ) write(io_fid_log,*) '*** Restart input? : NO'
326  endif
327  if ( land_restart_output &
328  .AND. land_restart_out_basename /= '' ) then
329  if( io_l ) write(io_fid_log,*) '*** Restart output? : ', trim(land_restart_out_basename)
330  else
331  if( io_l ) write(io_fid_log,*) '*** Restart output? : NO'
332  land_restart_output = .false.
333  endif
334 
335  ! Read land property table
336  allocate( land_property_table(landuse_pft_nmax,land_property_nmax) )
337  land_property_table(:,:) = undef
338 
339  call land_param_read
340 
341  ! Apply land property to 2D map
343 
344  ! tentative, mosaic is off
345  do p = 1, land_property_nmax
346  do j = js, je
347  do i = is, ie
348  land_property(i,j,p) = land_property_table( landuse_index_pft(i,j,1), p )
349  enddo
350  enddo
351  enddo
352 
353  do p = 1, land_property_nmax
354  call comm_vars8( land_property(:,:,p), p )
355  enddo
356  do p = 1, land_property_nmax
357  call comm_wait ( land_property(:,:,p), p )
358  enddo
359 
360  return
361  end subroutine land_vars_setup
362 
363  !-----------------------------------------------------------------------------
365  subroutine land_vars_restart_read
366  use scale_fileio, only: &
367  fileio_read
368  use mod_land_admin, only: &
369  land_sw
370  implicit none
371  !---------------------------------------------------------------------------
372 
373  if( io_l ) write(io_fid_log,*)
374  if( io_l ) write(io_fid_log,*) '*** Input restart file (LAND) ***'
375 
376  if ( land_sw .and. land_restart_in_basename /= '' ) then
377  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(land_restart_in_basename)
378 
379  call fileio_read( land_temp(:,:,:), & ! [OUT]
380  land_restart_in_basename, var_name(i_temp), 'Land', step=1 ) ! [IN]
381  call fileio_read( land_water(:,:,:), & ! [OUT]
382  land_restart_in_basename, var_name(i_water), 'Land', step=1 ) ! [IN]
383  call fileio_read( land_sfc_temp(:,:), & ! [OUT]
384  land_restart_in_basename, var_name(i_sfc_temp), 'XY', step=1 ) ! [IN]
385  call fileio_read( land_sfc_albedo(:,:,i_lw), & ! [OUT]
386  land_restart_in_basename, var_name(i_alb_lw), 'XY', step=1 ) ! [IN]
387  call fileio_read( land_sfc_albedo(:,:,i_sw), & ! [OUT]
388  land_restart_in_basename, var_name(i_alb_sw), 'XY', step=1 ) ! [IN]
389  call fileio_read( land_sflx_mw(:,:), & ! [OUT]
390  land_restart_in_basename, var_name(i_sflx_mw), 'XY', step=1 ) ! [IN]
391  call fileio_read( land_sflx_mu(:,:), & ! [OUT]
392  land_restart_in_basename, var_name(i_sflx_mu), 'XY', step=1 ) ! [IN]
393  call fileio_read( land_sflx_mv(:,:), & ! [OUT]
394  land_restart_in_basename, var_name(i_sflx_mv), 'XY', step=1 ) ! [IN]
395  call fileio_read( land_sflx_sh(:,:), & ! [OUT]
396  land_restart_in_basename, var_name(i_sflx_sh), 'XY', step=1 ) ! [IN]
397  call fileio_read( land_sflx_lh(:,:), & ! [OUT]
398  land_restart_in_basename, var_name(i_sflx_lh), 'XY', step=1 ) ! [IN]
399  call fileio_read( land_sflx_gh(:,:), & ! [OUT]
400  land_restart_in_basename, var_name(i_sflx_gh), 'XY', step=1 ) ! [IN]
401  call fileio_read( land_sflx_evap(:,:), & ! [OUT]
402  land_restart_in_basename, var_name(i_sflx_evap), 'XY', step=1 ) ! [IN]
403 
404  call land_vars_total
405  else
406  if( io_l ) write(io_fid_log,*) '*** restart file for land is not specified.'
407  endif
408 
409  return
410  end subroutine land_vars_restart_read
411 
412  !-----------------------------------------------------------------------------
414  subroutine land_vars_restart_write
415  use scale_time, only: &
417  use scale_fileio, only: &
418  fileio_write
419  use mod_land_admin, only: &
420  land_sw
421  implicit none
422 
423  character(len=20) :: timelabel
424  character(len=H_LONG) :: basename
425  !---------------------------------------------------------------------------
426 
427  if ( land_sw .and. land_restart_out_basename /= '' ) then
428 
429  call time_gettimelabel( timelabel )
430  write(basename,'(A,A,A)') trim(land_restart_out_basename), '_', trim(timelabel)
431 
432  if( io_l ) write(io_fid_log,*)
433  if( io_l ) write(io_fid_log,*) '*** Output restart file (LAND) ***'
434  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
435 
436  call land_vars_total
437 
438  call fileio_write( land_temp(:,:,:), basename, land_restart_out_title, & ! [IN]
439  var_name(i_temp), var_desc(i_temp), var_unit(i_temp), & ! [IN]
440  'Land', land_restart_out_dtype, nohalo=.true. ) ! [IN]
441  call fileio_write( land_water(:,:,:), basename, land_restart_out_title, & ! [IN]
442  var_name(i_water), var_desc(i_water), var_unit(i_water), & ! [IN]
443  'Land', land_restart_out_dtype, nohalo=.true. ) ! [IN]
444  call fileio_write( land_sfc_temp(:,:), basename, land_restart_out_title, & ! [IN]
445  var_name(i_sfc_temp), var_desc(i_sfc_temp), var_unit(i_sfc_temp), & ! [IN]
446  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
447  call fileio_write( land_sfc_albedo(:,:,i_lw), basename, land_restart_out_title, & ! [IN]
448  var_name(i_alb_lw), var_desc(i_alb_lw), var_unit(i_alb_lw), & ! [IN]
449  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
450  call fileio_write( land_sfc_albedo(:,:,i_sw), basename, land_restart_out_title, & ! [IN]
451  var_name(i_alb_sw), var_desc(i_alb_sw), var_unit(i_alb_sw), & ! [IN]
452  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
453  call fileio_write( land_sflx_mw(:,:), basename, land_restart_out_title, & ! [IN]
454  var_name(i_sflx_mw), var_desc(i_sflx_mw), var_unit(i_sflx_mw), & ! [IN]
455  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
456  call fileio_write( land_sflx_mu(:,:), basename, land_restart_out_title, & ! [IN]
457  var_name(i_sflx_mu), var_desc(i_sflx_mu), var_unit(i_sflx_mu), & ! [IN]
458  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
459  call fileio_write( land_sflx_mv(:,:), basename, land_restart_out_title, & ! [IN]
460  var_name(i_sflx_mv), var_desc(i_sflx_mv), var_unit(i_sflx_mv), & ! [IN]
461  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
462  call fileio_write( land_sflx_sh(:,:), basename, land_restart_out_title, & ! [IN]
463  var_name(i_sflx_sh), var_desc(i_sflx_sh), var_unit(i_sflx_sh), & ! [IN]
464  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
465  call fileio_write( land_sflx_lh(:,:), basename, land_restart_out_title, & ! [IN]
466  var_name(i_sflx_lh), var_desc(i_sflx_lh), var_unit(i_sflx_lh), & ! [IN]
467  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
468  call fileio_write( land_sflx_gh(:,:), basename, land_restart_out_title, & ! [IN]
469  var_name(i_sflx_gh), var_desc(i_sflx_gh), var_unit(i_sflx_gh), & ! [IN]
470  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
471  call fileio_write( land_sflx_evap(:,:), basename, land_restart_out_title, & ! [IN]
472  var_name(i_sflx_evap), var_desc(i_sflx_evap), var_unit(i_sflx_evap), & ! [IN]
473  'XY', land_restart_out_dtype, nohalo=.true. ) ! [IN]
474 
475  endif
476 
477  return
478  end subroutine land_vars_restart_write
479 
480  !-----------------------------------------------------------------------------
482  subroutine land_vars_history
483  use scale_history, only: &
484  hist_in
485  implicit none
486 
487  real(RP) :: LAND_WATERDS(lkmax,ia,ja)
488  integer :: k, i, j
489  !---------------------------------------------------------------------------
490 
491  if ( land_vars_checkrange ) then
492  call valcheck( land_temp(:,is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_temp), &
493  __file__, __line__ )
494  call valcheck( land_water(:,is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_water), &
495  __file__, __line__ )
496  call valcheck( land_sfc_temp(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_sfc_temp), &
497  __file__, __line__ )
498  call valcheck( land_sfc_albedo(is:ie,js:je,i_lw), 0.0_rp, 2.0_rp, var_name(i_alb_lw), &
499  __file__, __line__ )
500  call valcheck( land_sfc_albedo(is:ie,js:je,i_sw), 0.0_rp, 2.0_rp, var_name(i_alb_sw), &
501  __file__, __line__ )
502  endif
503 
504  call hist_in( land_temp(:,:,:), var_name(i_temp), var_desc(i_temp), var_unit(i_temp), zdim='land' )
505  call hist_in( land_water(:,:,:), var_name(i_water), var_desc(i_water), var_unit(i_water), zdim='land' )
506  do j = js, je
507  do i = is, ie
508  do k = 1, lkmax
509  land_waterds(k,i,j) = land_water(k,i,j) / land_property(i,j,i_waterlimit)
510  end do
511  end do
512  end do
513  call hist_in( land_waterds(:,:,:), var_name(i_waterds), var_desc(i_waterds), var_unit(i_waterds), zdim='land', nohalo=.true. )
514 
515 
516  call hist_in( land_sfc_temp(:,:), var_name(i_sfc_temp), var_desc(i_sfc_temp), var_unit(i_sfc_temp) )
517  call hist_in( land_sfc_albedo(:,:,i_lw), var_name(i_alb_lw), var_desc(i_alb_lw), var_unit(i_alb_lw) )
518  call hist_in( land_sfc_albedo(:,:,i_sw), var_name(i_alb_sw), var_desc(i_alb_sw), var_unit(i_alb_sw) )
519 
520  call hist_in( land_sflx_mw(:,:), var_name(i_sflx_mw), var_desc(i_sflx_mw), var_unit(i_sflx_mw) )
521  call hist_in( land_sflx_mu(:,:), var_name(i_sflx_mu), var_desc(i_sflx_mu), var_unit(i_sflx_mu) )
522  call hist_in( land_sflx_mv(:,:), var_name(i_sflx_mv), var_desc(i_sflx_mv), var_unit(i_sflx_mv) )
523  call hist_in( land_sflx_sh(:,:), var_name(i_sflx_sh), var_desc(i_sflx_sh), var_unit(i_sflx_sh) )
524  call hist_in( land_sflx_lh(:,:), var_name(i_sflx_lh), var_desc(i_sflx_lh), var_unit(i_sflx_lh) )
525  call hist_in( land_sflx_gh(:,:), var_name(i_sflx_gh), var_desc(i_sflx_gh), var_unit(i_sflx_gh) )
526  call hist_in( land_sflx_evap(:,:), var_name(i_sflx_evap), var_desc(i_sflx_evap), var_unit(i_sflx_evap) )
527 
528  return
529  end subroutine land_vars_history
530 
531  !-----------------------------------------------------------------------------
533  subroutine land_vars_total
534  use scale_rm_statistics, only: &
536  stat_total
537  implicit none
538 
539  real(RP) :: total
540 
541  character(len=2) :: sk
542  integer :: k
543  !---------------------------------------------------------------------------
544 
545  if ( statistics_checktotal ) then
546 
547  do k = lks, lke
548  write(sk,'(I2.2)') k
549 
550  call stat_total( total, land_temp(k,:,:), trim(var_name(i_temp) )//sk )
551  call stat_total( total, land_water(k,:,:), trim(var_name(i_water))//sk )
552  enddo
553 
554  call stat_total( total, land_sfc_temp(:,:), var_name(i_sfc_temp) )
555  call stat_total( total, land_sfc_albedo(:,:,i_lw), var_name(i_alb_lw) )
556  call stat_total( total, land_sfc_albedo(:,:,i_sw), var_name(i_alb_sw) )
557 
558  endif
559 
560  return
561  end subroutine land_vars_total
562 
563  !-----------------------------------------------------------------------------
565  subroutine land_vars_external_in( &
566  LAND_TEMP_in, &
567  LAND_WATER_in, &
568  LAND_SFC_TEMP_in, &
569  LAND_SFC_albedo_in )
570  implicit none
571 
572  real(RP), intent(in) :: LAND_TEMP_in (:,:,:)
573  real(RP), intent(in) :: LAND_WATER_in(:,:,:)
574  real(RP), intent(in) :: LAND_SFC_TEMP_in (ia,ja)
575  real(RP), intent(in) :: LAND_SFC_albedo_in(ia,ja,2)
576  !---------------------------------------------------------------------------
577 
578  if( io_l ) write(io_fid_log,*)
579  if( io_l ) write(io_fid_log,*) '*** External Input (land) ***'
580 
581  land_temp(:,:,:) = land_temp_in(:,:,:)
582  land_water(:,:,:) = land_water_in(:,:,:)
583  land_sfc_temp(:,:) = land_sfc_temp_in(:,:)
584  land_sfc_albedo(:,:,:) = land_sfc_albedo_in(:,:,:)
585 
586  land_sflx_mw(:,:) = 0.0_rp
587  land_sflx_mu(:,:) = 0.0_rp
588  land_sflx_mv(:,:) = 0.0_rp
589  land_sflx_sh(:,:) = 0.0_rp
590  land_sflx_lh(:,:) = 0.0_rp
591  land_sflx_gh(:,:) = 0.0_rp
592  land_sflx_evap(:,:) = 0.0_rp
593 
594  call land_vars_total
595 
596  return
597  end subroutine land_vars_external_in
598 
599  !-----------------------------------------------------------------------------
601  subroutine land_param_read
602  use scale_process, only: &
604  use scale_landuse, only: &
606  implicit none
607 
608  integer :: index
609  character(len=H_LONG) :: description
610  real(RP) :: STRGMAX
611  real(RP) :: STRGCRT
612  real(RP) :: TCS
613  real(RP) :: HCS
614  real(RP) :: DFW
615  real(RP) :: Z0M
616  real(RP) :: Z0H
617  real(RP) :: Z0E
618 
619  namelist / param_land_property / &
621 
622  namelist / param_land_data / &
623  index, &
624  description, &
625  strgmax, &
626  strgcrt, &
627  tcs, &
628  hcs, &
629  dfw, &
630  z0m, &
631  z0h, &
632  z0e
633 
634  integer :: n
635  integer :: ierr
636 
637  integer :: IO_FID_LAND_PROPERTY
638  !---------------------------------------------------------------------------
639 
640  !--- read namelist
641  rewind(io_fid_conf)
642  read(io_fid_conf,nml=param_land_property,iostat=ierr)
643  if( ierr < 0 ) then !--- missing
644  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
645  elseif( ierr > 0 ) then !--- fatal error
646  write(*,*) 'xxx Not appropriate names in namelist PARAM_LAND_PROPERTY. Check!'
647  call prc_mpistop
648  endif
649  if( io_lnml ) write(io_fid_log,nml=param_land_property)
650 
651  if( land_property_in_filename /= '' ) then
652  !--- Open land parameter file
653  io_fid_land_property = io_get_available_fid()
654  open( io_fid_land_property, &
655  file = trim(land_property_in_filename), &
656  form = 'formatted', &
657  status = 'old', &
658  iostat = ierr )
659 
660  if( ierr /= 0 ) then
661  if( io_l ) write(io_fid_log,*) 'Error: Failed to open land parameter file! :', trim(land_property_in_filename)
662  call prc_mpistop
663  else
664  if( io_l ) write(io_fid_log,*)
665  if( io_l ) write(io_fid_log,*) '*** Properties for each plant functional type (PFT)'
666  if( io_l ) write(io_fid_log,*) &
667  '--------------------------------------------------------------------------------------------------------'
668  if( io_l ) write(io_fid_log,'(1x,A,11(1x,A))') '*** ', &
669  ' description', &
670  ' Max Stg.', &
671  ' CRT Stg.', &
672  ' T condu.', &
673  ' H capac.', &
674  ' DFC Wat.', &
675  ' Z0(m)', &
676  ' Z0(h)', &
677  ' Z0(e)'
678 
679  !--- read namelist
680  rewind(io_fid_land_property)
681 
682  do n = 1, landuse_pft_nmax
683  ! undefined roughness length
684  z0h = -1.0_rp
685  z0e = -1.0_rp
686 
687  read(io_fid_land_property,nml=param_land_data,iostat=ierr)
688  if ( ierr < 0 ) then !--- no more data
689  exit
690  elseif( ierr > 0 ) then !--- fatal error
691  write(*,*) 'xxx Not appropriate names in namelist PARAM_LAND_DATA. Check!'
692  call prc_mpistop
693  endif
694 
695  if( z0h < 0.0_rp ) then
696  z0h = z0m / 7.4_rp ! defined by Garratt and Francey (1978)
697  endif
698  if( z0e < 0.0_rp ) then
699  z0e = z0m / 7.4_rp ! defined by Garratt and Francey (1978)
700  endif
701 
702  land_property_table(index,i_waterlimit ) = strgmax
703  land_property_table(index,i_watercritical) = strgcrt
704  land_property_table(index,i_thermalcond ) = tcs
705  land_property_table(index,i_heatcapacity ) = hcs
706  land_property_table(index,i_waterdiff ) = dfw
707  land_property_table(index,i_z0m ) = z0m
708  land_property_table(index,i_z0h ) = z0h
709  land_property_table(index,i_z0e ) = z0e
710 
711  if( io_l ) write(io_fid_log,'(1x,A8,I3,1x,A12,3(1x,F9.2),(1x,ES9.1),4(1x,F9.2))') &
712  '*** IDX =', index, &
713  trim(description), &
714  strgmax, &
715  strgcrt, &
716  tcs, &
717  hcs, &
718  dfw, &
719  z0m, &
720  z0h, &
721  z0e
722  enddo
723 
724  end if
725 
726  close( io_fid_land_property )
727 
728  if( io_l ) write(io_fid_log,*) &
729  '--------------------------------------------------------------------------------------------------------'
730 
731  endif
732 
733  return
734  end subroutine land_param_read
735 
736  !-----------------------------------------------------------------------------
738  function convert_ws2vwc( WS, critical ) result( VWC )
739  implicit none
740 
741  real(RP), intent(in) :: WS(ia,ja) ! water saturation [fraction]
742  logical, intent(in) :: critical ! is I_WaterCritical used?
743 
744  real(RP) :: VWC(ia,ja) ! volumetric water content [m3/m3]
745 
746  ! work
747  integer :: i, j, num
748  !---------------------------------------------------------------------------
749 
750  if( critical ) then
751  num = i_watercritical
752  else
753  num = i_waterlimit
754  end if
755 
756  do j = js, je
757  do i = is, ie
758  vwc(i,j) = max( min( ws(i,j)*land_property(i,j,num), land_property(i,j,num) ), 0.0_rp )
759  end do
760  end do
761 
762  return
763  end function convert_ws2vwc
764 
765  !-----------------------------------------------------------------------------
767  subroutine land_vars_restart_create
768  use scale_time, only: &
770  use scale_fileio, only: &
772  use mod_land_admin, only: &
773  land_sw
774  implicit none
775 
776  character(len=20) :: timelabel
777  character(len=H_LONG) :: basename
778  !---------------------------------------------------------------------------
779 
780  if ( land_sw .and. land_restart_out_basename /= '' ) then
781 
782  call time_gettimelabel( timelabel )
783  write(basename,'(A,A,A)') trim(land_restart_out_basename), '_', trim(timelabel)
784 
785  if( io_l ) write(io_fid_log,*)
786  if( io_l ) write(io_fid_log,*) '*** Output restart file (LAND) ***'
787  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
788 
789  call fileio_create(restart_fid, basename, land_restart_out_title, land_restart_out_dtype)
790  endif
791 
792  return
793  end subroutine land_vars_restart_create
794 
795  !-----------------------------------------------------------------------------
797  subroutine land_vars_restart_enddef
798  use scale_fileio, only: &
800  implicit none
801 
802  if ( restart_fid .NE. -1 ) then
803  call fileio_enddef( restart_fid ) ! [IN]
804  endif
805 
806  return
807  end subroutine land_vars_restart_enddef
808 
809  !-----------------------------------------------------------------------------
811  subroutine land_vars_restart_close
812  use scale_fileio, only: &
814  implicit none
815 
816  if ( restart_fid .NE. -1 ) then
817  call fileio_close( restart_fid ) ! [IN]
818  restart_fid = -1
819  endif
820 
821  return
822  end subroutine land_vars_restart_close
823 
824  !-----------------------------------------------------------------------------
826  subroutine land_vars_restart_def_var
827  use scale_fileio, only: &
829  implicit none
830 
831  !---------------------------------------------------------------------------
832 
833  if ( restart_fid .NE. -1 ) then
834 
835  call fileio_def_var( restart_fid, var_id(i_temp), var_name(i_temp), var_desc(i_temp), &
836  var_unit(i_temp), 'Land', land_restart_out_dtype)
837  call fileio_def_var( restart_fid, var_id(i_water), var_name(i_water), var_desc(i_water), &
838  var_unit(i_water), 'Land', land_restart_out_dtype)
839  call fileio_def_var( restart_fid, var_id(i_sfc_temp), var_name(i_sfc_temp), var_desc(i_sfc_temp), &
840  var_unit(i_sfc_temp), 'XY', land_restart_out_dtype)
841  call fileio_def_var( restart_fid, var_id(i_alb_lw), var_name(i_alb_lw), var_desc(i_alb_lw), &
842  var_unit(i_alb_lw), 'XY', land_restart_out_dtype)
843  call fileio_def_var( restart_fid, var_id(i_alb_sw), var_name(i_alb_sw), var_desc(i_alb_sw), &
844  var_unit(i_alb_sw), 'XY', land_restart_out_dtype)
845  call fileio_def_var( restart_fid, var_id(i_sflx_mw), var_name(i_sflx_mw), var_desc(i_sflx_mw), &
846  var_unit(i_sflx_mw), 'XY', land_restart_out_dtype)
847  call fileio_def_var( restart_fid, var_id(i_sflx_mu), var_name(i_sflx_mu), var_desc(i_sflx_mu), &
848  var_unit(i_sflx_mu), 'XY', land_restart_out_dtype)
849  call fileio_def_var( restart_fid, var_id(i_sflx_mv), var_name(i_sflx_mv), var_desc(i_sflx_mv), &
850  var_unit(i_sflx_mv), 'XY', land_restart_out_dtype)
851  call fileio_def_var( restart_fid, var_id(i_sflx_sh), var_name(i_sflx_sh), var_desc(i_sflx_sh), &
852  var_unit(i_sflx_sh), 'XY', land_restart_out_dtype)
853  call fileio_def_var( restart_fid, var_id(i_sflx_lh), var_name(i_sflx_lh), var_desc(i_sflx_lh), &
854  var_unit(i_sflx_lh), 'XY', land_restart_out_dtype)
855  call fileio_def_var( restart_fid, var_id(i_sflx_gh), var_name(i_sflx_gh), var_desc(i_sflx_gh), &
856  var_unit(i_sflx_gh), 'XY', land_restart_out_dtype)
857  call fileio_def_var( restart_fid, var_id(i_sflx_evap), var_name(i_sflx_evap), var_desc(i_sflx_evap), &
858  var_unit(i_sflx_evap), 'XY', land_restart_out_dtype)
859 
860  endif
861 
862  return
863  end subroutine land_vars_restart_def_var
864 
865  !-----------------------------------------------------------------------------
867  subroutine land_vars_restart_write_var
868  use scale_fileio, only: &
869  fileio_write_var
870  implicit none
871 
872  !---------------------------------------------------------------------------
873 
874  if ( restart_fid .NE. -1 ) then
875 
876  call land_vars_total
877 
878  call fileio_write_var( restart_fid, var_id(i_temp), land_temp(:,:,:), & ! [IN]
879  var_name(i_temp), 'Land', nohalo=.true. ) ! [IN]
880  call fileio_write_var( restart_fid, var_id(i_water), land_water(:,:,:), & ! [IN]
881  var_name(i_water), 'Land', nohalo=.true. ) ! [IN]
882  call fileio_write_var( restart_fid, var_id(i_sfc_temp), land_sfc_temp(:,:), & ! [IN]
883  var_name(i_sfc_temp), 'XY', nohalo=.true. ) ! [IN]
884  call fileio_write_var( restart_fid, var_id(i_alb_lw), land_sfc_albedo(:,:,i_lw), & ! [IN]
885  var_name(i_alb_lw), 'XY', nohalo=.true. ) ! [IN]
886  call fileio_write_var( restart_fid, var_id(i_alb_sw), land_sfc_albedo(:,:,i_sw), & ! [IN]
887  var_name(i_alb_sw), 'XY', nohalo=.true. ) ! [IN]
888  call fileio_write_var( restart_fid, var_id(i_sflx_mw), land_sflx_mw(:,:), & ! [IN]
889  var_name(i_sflx_mw), 'XY', nohalo=.true. ) ! [IN]
890  call fileio_write_var( restart_fid, var_id(i_sflx_mu), land_sflx_mu(:,:), & ! [IN]
891  var_name(i_sflx_mu), 'XY', nohalo=.true. ) ! [IN]
892  call fileio_write_var( restart_fid, var_id(i_sflx_mv), land_sflx_mv(:,:), & ! [IN]
893  var_name(i_sflx_mv), 'XY', nohalo=.true. ) ! [IN]
894  call fileio_write_var( restart_fid, var_id(i_sflx_sh), land_sflx_sh(:,:), & ! [IN]
895  var_name(i_sflx_sh), 'XY', nohalo=.true. ) ! [IN]
896  call fileio_write_var( restart_fid, var_id(i_sflx_lh), land_sflx_lh(:,:), & ! [IN]
897  var_name(i_sflx_lh), 'XY', nohalo=.true. ) ! [IN]
898  call fileio_write_var( restart_fid, var_id(i_sflx_gh), land_sflx_gh(:,:), & ! [IN]
899  var_name(i_sflx_gh), 'XY', nohalo=.true. ) ! [IN]
900  call fileio_write_var( restart_fid, var_id(i_sflx_evap), land_sflx_evap(:,:), & ! [IN]
901  var_name(i_sflx_evap), 'XY', nohalo=.true. ) ! [IN]
902 
903  endif
904 
905  return
906  end subroutine land_vars_restart_write_var
907 
908 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]
subroutine, public land_vars_restart_close
Close restart file.
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
subroutine, public land_vars_restart_enddef
Exit netCDF define mode.
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_create
Create land restart file.
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]
subroutine, public fileio_def_var(fid, vid, varname, desc, unit, axistype, datatype, timeintv)
Define a variable to file.
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]
subroutine, public land_vars_restart_write_var
Write land variables to restart file.
character(len=h_long), public land_restart_out_basename
basename of the output file
subroutine, public fileio_create(fid, basename, title, datatype, date, subsec, append, nozcoord)
Create/open a netCDF file.
subroutine, public land_vars_restart_def_var
Define land variables in restart 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
subroutine, public fileio_enddef(fid)
Exit netCDF file define mode.
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)
subroutine, public fileio_close(fid)
Close a netCDF file.
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)