SCALE-RM
mod_land_vars.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
9 !-------------------------------------------------------------------------------
10 #include "scalelib.h"
12  !-----------------------------------------------------------------------------
13  !
14  !++ used modules
15  !
16  use scale_precision
17  use scale_io
18  use scale_prof
19  use scale_debug
21  use scale_tracer
23  !-----------------------------------------------------------------------------
24  implicit none
25  private
26  !-----------------------------------------------------------------------------
27  !
28  !++ Public procedure
29  !
30  public :: land_vars_setup
31  public :: land_vars_restart_read
32  public :: land_vars_restart_write
33  public :: land_vars_history
34  public :: land_vars_total
35 
36  public :: land_vars_restart_create
37  public :: land_vars_restart_open
39  public :: land_vars_restart_enddef
40  public :: land_vars_restart_close
41 
42  public :: convert_ws2vwc
43 
44  !-----------------------------------------------------------------------------
45  !
46  !++ Public parameters & variables
47  !
48  logical, public :: land_restart_output = .false.
49 
50  character(len=H_LONG), public :: land_restart_in_basename = ''
51  logical, public :: land_restart_in_aggregate
52  logical, public :: land_restart_in_postfix_timelabel = .false.
53  character(len=H_LONG), public :: land_restart_out_basename = ''
54  logical, public :: land_restart_out_aggregate
55  logical, public :: land_restart_out_postfix_timelabel = .true.
56  character(len=H_MID), public :: land_restart_out_title = 'LAND restart'
57  character(len=H_SHORT), 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  ! for snow model
66  real(RP), public, allocatable :: snow_sfc_temp (:,:)
67  real(RP), public, allocatable :: snow_swe (:,:)
68  real(RP), public, allocatable :: snow_depth (:,:)
69  real(RP), public, allocatable :: snow_dzero (:,:)
70  real(RP), public, allocatable :: snow_nosnowsec (:,:)
71 
72  ! tendency variables
73  real(RP), public, allocatable :: land_temp_t (:,:,:)
74  real(RP), public, allocatable :: land_water_t (:,:,:)
75 
76  ! surface variables for restart
77  real(RP), public, allocatable :: land_sflx_mw (:,:)
78  real(RP), public, allocatable :: land_sflx_mu (:,:)
79  real(RP), public, allocatable :: land_sflx_mv (:,:)
80  real(RP), public, allocatable :: land_sflx_sh (:,:)
81  real(RP), public, allocatable :: land_sflx_lh (:,:)
82  real(RP), public, allocatable :: land_sflx_qtrc (:,:,:)
83  real(RP), public, allocatable :: land_sflx_gh (:,:)
84  real(RP), public, allocatable :: land_sflx_water(:,:)
85  real(RP), public, allocatable :: land_sflx_ice (:,:)
86 
87  ! diagnostic variables
88  real(RP), public, allocatable :: land_u10 (:,:)
89  real(RP), public, allocatable :: land_v10 (:,:)
90  real(RP), public, allocatable :: land_t2 (:,:)
91  real(RP), public, allocatable :: land_q2 (:,:)
92 
93  ! recieved atmospheric variables
94  real(RP), public, allocatable :: atmos_temp (:,:)
95  real(RP), public, allocatable :: atmos_pres (:,:)
96  real(RP), public, allocatable :: atmos_w (:,:)
97  real(RP), public, allocatable :: atmos_u (:,:)
98  real(RP), public, allocatable :: atmos_v (:,:)
99  real(RP), public, allocatable :: atmos_dens (:,:)
100  real(RP), public, allocatable :: atmos_qv (:,:)
101  real(RP), public, allocatable :: atmos_pbl (:,:)
102  real(RP), public, allocatable :: atmos_sfc_dens (:,:)
103  real(RP), public, allocatable :: atmos_sfc_pres (:,:)
104  real(RP), public, allocatable :: atmos_sflx_rad_dn(:,:,:,:)
105  real(RP), public, allocatable :: atmos_cossza (:,:)
106  real(RP), public, allocatable :: atmos_sflx_rain (:,:)
107  real(RP), public, allocatable :: atmos_sflx_snow (:,:)
108 
109  real(RP), public, allocatable :: land_property(:,:,:)
110 
111  character(len=H_LONG), public :: land_property_in_filename = ''
112 
113  integer, public, parameter :: land_property_nmax = 11
114  integer, public, parameter :: i_waterlimit = 1 ! maximum soil moisture [m3/m3]
115  integer, public, parameter :: i_watercritical = 2 ! critical soil moisture [m3/m3]
116  integer, public, parameter :: i_stomataresist = 3 ! stomata resistance [1/s]
117  integer, public, parameter :: i_thermalcond = 4 ! thermal conductivity for soil [W/K/m]
118  integer, public, parameter :: i_heatcapacity = 5 ! heat capacity for soil [J/K/m3]
119  integer, public, parameter :: i_waterdiff = 6 ! moisture diffusivity in the soil [m2/s]
120  integer, public, parameter :: i_alblw = 7 ! surface albedo for long wave [1]
121  integer, public, parameter :: i_albsw = 8 ! surface albedo for short wave [1]
122  integer, public, parameter :: i_z0m = 9 ! roughness length for momemtum [m]
123  integer, public, parameter :: i_z0h = 10 ! roughness length for heat [m]
124  integer, public, parameter :: i_z0e = 11 ! roughness length for vapor [m]
125 
126  !-----------------------------------------------------------------------------
127  !
128  !++ Private procedure
129  !
130  private :: land_param_read
131 
132  !-----------------------------------------------------------------------------
133  !
134  !++ Private parameters & variables
135  !
136  logical, private :: land_vars_checkrange = .false.
137 
138  integer, private, parameter :: vmax = 19
139  integer, private, parameter :: i_temp = 1
140  integer, private, parameter :: i_water = 2
141  integer, private, parameter :: i_waterds = 3
142  integer, private, parameter :: i_sfc_temp = 4
143  integer, private, parameter :: i_sfc_alb_ir_dir = 5
144  integer, private, parameter :: i_sfc_alb_ir_dif = 6
145  integer, private, parameter :: i_sfc_alb_nir_dir = 7
146  integer, private, parameter :: i_sfc_alb_nir_dif = 8
147  integer, private, parameter :: i_sfc_alb_vis_dir = 9
148  integer, private, parameter :: i_sfc_alb_vis_dif = 10
149  integer, private, parameter :: i_sflx_mw = 11
150  integer, private, parameter :: i_sflx_mu = 12
151  integer, private, parameter :: i_sflx_mv = 13
152  integer, private, parameter :: i_sflx_sh = 14
153  integer, private, parameter :: i_sflx_lh = 15
154  integer, private, parameter :: i_sflx_evap = 16
155  integer, private, parameter :: i_sflx_gh = 17
156  integer, private, parameter :: i_sflx_water = 18
157  integer, private, parameter :: i_sflx_ice = 19
158 
159  character(len=H_SHORT), private :: var_name(vmax)
160  character(len=H_MID), private :: var_desc(vmax)
161  character(len=H_MID), private :: var_stdn(vmax)
162  character(len=H_SHORT), private :: var_unit(vmax)
163  integer, private :: var_id(vmax)
164  integer, private :: restart_fid = -1 ! file ID
165 
166  data var_name / 'LAND_TEMP', &
167  'LAND_WATER', &
168  'LAND_DSAT', &
169  'LAND_SFC_TEMP', &
170  'LAND_SFC_ALB_IR_dir', &
171  'LAND_SFC_ALB_IR_dif', &
172  'LAND_SFC_ALB_NIR_dir', &
173  'LAND_SFC_ALB_NIR_dif', &
174  'LAND_SFC_ALB_VIS_dir', &
175  'LAND_SFC_ALB_VIS_dif', &
176  'LAND_SFLX_MW', &
177  'LAND_SFLX_MU', &
178  'LAND_SFLX_MV', &
179  'LAND_SFLX_SH', &
180  'LAND_SFLX_LH', &
181  'LAND_SFLX_evap', &
182  'LAND_SFLX_GH', &
183  'LAND_SFLX_water', &
184  'LAND_SFLX_ice' /
185  data var_desc / 'temperature at each soil layer', &
186  'moisture at each soil layer', &
187  'degree of saturation at each soil layer', &
188  'land surface skin temperature', &
189  'land surface albedo for IR (direct)', &
190  'land surface albedo for IR (diffuse)', &
191  'land surface albedo for NIR (direct)', &
192  'land surface albedo for NIR (diffuse)', &
193  'land surface albedo for VIS (direct)', &
194  'land surface albedo for VIS (diffuse)', &
195  'land surface w-momentum flux (upward)', &
196  'land surface u-momentum flux (upward)', &
197  'land surface v-momentum flux (upward)', &
198  'land surface sensible heat flux (upward)', &
199  'land surface latent heat flux (upward)', &
200  'land surface water vapor flux (upward)', &
201  'land subsurface heat flux (downward)', &
202  'land surface liquid water flux (downward)', &
203  'land surface ice water flux (downward)' /
204  data var_stdn / 'soil_temperature', &
205  'volume_fraction_of_condensed_water_in_soil', &
206  'volume_fraction_of_condensed_water_in_soil_at_field_capacity', &
207  'surface_temperature_where_land', &
208  '', &
209  '', &
210  '', &
211  '', &
212  '', &
213  '', &
214  '', &
215  '', &
216  '', &
217  '', &
218  '', &
219  '', &
220  '', &
221  '', &
222  '' /
223  data var_unit / 'K', &
224  'm3/m3', &
225  '1', &
226  'K', &
227  '1', &
228  '1', &
229  '1', &
230  '1', &
231  '1', &
232  '1', &
233  'kg/m2/s', &
234  'kg/m2/s', &
235  'kg/m2/s', &
236  'J/m2/s', &
237  'J/m2/s', &
238  'kg/m2/s', &
239  'J/m2/s', &
240  'kg/m2/s', &
241  'kg/m2/s' /
242 
243  real(RP), private, allocatable :: land_property_table(:,:)
244 
245  logical, private :: land_restart_in_check_coordinates = .true.
246 
247  !-----------------------------------------------------------------------------
248 contains
249  !-----------------------------------------------------------------------------
251  subroutine land_vars_setup
252  use scale_prc, only: &
253  prc_abort
254  use scale_const, only: &
255  undef => const_undef
256  use scale_comm_cartesc, only: &
257  comm_vars8, &
258  comm_wait
259  use scale_landuse, only: &
263  implicit none
264 
265  namelist / param_land_vars / &
269  land_restart_in_check_coordinates, &
276  land_vars_checkrange
277 
278  integer :: ierr
279  integer :: i, j, iv, p
280  !---------------------------------------------------------------------------
281 
282  log_newline
283  log_info("LAND_vars_setup",*) 'Setup'
284 
285  allocate( land_temp(lkmax,lia,lja) )
286  allocate( land_water(lkmax,lia,lja) )
287  allocate( land_sfc_temp(lia,lja) )
289  land_temp(:,:,:) = undef
290  land_water(:,:,:) = undef
291  land_sfc_temp(:,:) = undef
292  land_sfc_albedo(:,:,:,:) = undef
293 
294  allocate( snow_sfc_temp(lia,lja) )
295  allocate( snow_swe(lia,lja) )
296  allocate( snow_depth(lia,lja) )
297  allocate( snow_dzero(lia,lja) )
298  allocate( snow_nosnowsec(lia,lja) )
299  snow_sfc_temp(:,:) = undef
300  snow_swe(:,:) = undef
301  snow_depth(:,:) = undef
302  snow_dzero(:,:) = undef
303  snow_nosnowsec(:,:) = undef
304 
305  allocate( land_temp_t(lkmax,lia,lja) )
306  allocate( land_water_t(lkmax,lia,lja) )
307  land_temp_t(:,:,:) = undef
308  land_water_t(:,:,:) = undef
309 
310  allocate( land_sflx_mw(lia,lja) )
311  allocate( land_sflx_mu(lia,lja) )
312  allocate( land_sflx_mv(lia,lja) )
313  allocate( land_sflx_sh(lia,lja) )
314  allocate( land_sflx_lh(lia,lja) )
315  allocate( land_sflx_gh(lia,lja) )
316  allocate( land_sflx_qtrc(lia,lja,qa) )
317  allocate( land_sflx_water(lia,lja) )
318  allocate( land_sflx_ice(lia,lja) )
319  land_sflx_mw(:,:) = undef
320  land_sflx_mu(:,:) = undef
321  land_sflx_mv(:,:) = undef
322  land_sflx_sh(:,:) = undef
323  land_sflx_lh(:,:) = undef
324  land_sflx_qtrc(:,:,:) = undef
325  land_sflx_gh(:,:) = undef
326  land_sflx_water(:,:) = undef
327  land_sflx_ice(:,:) = undef
328 
329  allocate( land_u10(lia,lja) )
330  allocate( land_v10(lia,lja) )
331  allocate( land_t2(lia,lja) )
332  allocate( land_q2(lia,lja) )
333  land_u10(:,:) = undef
334  land_v10(:,:) = undef
335  land_t2(:,:) = undef
336  land_q2(:,:) = undef
337 
338  allocate( atmos_temp(lia,lja) )
339  allocate( atmos_pres(lia,lja) )
340  allocate( atmos_w(lia,lja) )
341  allocate( atmos_u(lia,lja) )
342  allocate( atmos_v(lia,lja) )
343  allocate( atmos_dens(lia,lja) )
344  allocate( atmos_qv(lia,lja) )
345  allocate( atmos_pbl(lia,lja) )
346  allocate( atmos_sfc_dens(lia,lja) )
347  allocate( atmos_sfc_pres(lia,lja) )
349  allocate( atmos_cossza(lia,lja) )
350  allocate( atmos_sflx_rain(lia,lja) )
351  allocate( atmos_sflx_snow(lia,lja) )
352  atmos_temp(:,:) = undef
353  atmos_pres(:,:) = undef
354  atmos_w(:,:) = undef
355  atmos_u(:,:) = undef
356  atmos_v(:,:) = undef
357  atmos_dens(:,:) = undef
358  atmos_qv(:,:) = undef
359  atmos_pbl(:,:) = undef
360  atmos_sfc_dens(:,:) = undef
361  atmos_sfc_pres(:,:) = undef
362  atmos_sflx_rad_dn(:,:,:,:) = undef
363  atmos_cossza(:,:) = undef
364  atmos_sflx_rain(:,:) = undef
365  atmos_sflx_snow(:,:) = undef
366 
367  !--- read namelist
368  rewind(io_fid_conf)
369  read(io_fid_conf,nml=param_land_vars,iostat=ierr)
370  if( ierr < 0 ) then !--- missing
371  log_info("LAND_vars_setup",*) 'Not found namelist. Default used.'
372  elseif( ierr > 0 ) then !--- fatal error
373  log_error("LAND_vars_setup",*) 'Not appropriate names in namelist PARAM_LAND_VARS. Check!'
374  call prc_abort
375  endif
376  log_nml(param_land_vars)
377 
378  log_newline
379  log_info("LAND_vars_setup",*) 'List of prognostic variables (LAND) '
380  log_info_cont('(1x,A,A24,A,A48,A,A12,A)') &
381  ' |', 'VARNAME ','|', &
382  'DESCRIPTION ', '[', 'UNIT ', ']'
383  do iv = 1, vmax
384  log_info_cont('(1x,A,I3,A,A24,A,A48,A,A12,A)') &
385  'NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
386  enddo
387 
388  log_newline
389  if ( land_restart_in_basename /= '' ) then
390  log_info("LAND_vars_setup",*) 'Restart input? : YES, file = ', trim(land_restart_in_basename)
391  log_info("LAND_vars_setup",*) 'Add timelabel? : ', land_restart_in_postfix_timelabel
392  else
393  log_info("LAND_vars_setup",*) 'Restart input? : NO'
394  endif
395  if ( land_restart_output &
396  .AND. land_restart_out_basename /= '' ) then
397  log_info("LAND_vars_setup",*) 'Restart output? : YES, file = ', trim(land_restart_out_basename)
398  log_info("LAND_vars_setup",*) 'Add timelabel? : ', land_restart_out_postfix_timelabel
399  else
400  log_info("LAND_vars_setup",*) 'Restart output? : NO'
401  land_restart_output = .false.
402  endif
403 
404  ! Read land property table
405  allocate( land_property_table(landuse_pft_nmin:landuse_pft_nmax,land_property_nmax) )
406  land_property_table(:,:) = undef
407 
408  call land_param_read
409 
410  ! Apply land property to 2D map
412 
413  ! tentative, mosaic is off
414  do p = 1, land_property_nmax
415  do j = ljs, lje
416  do i = lis, lie
417  land_property(i,j,p) = land_property_table( landuse_index_pft(i,j,1), p )
418  enddo
419  enddo
420  enddo
421 
422  do p = 1, land_property_nmax
423  call comm_vars8( land_property(:,:,p), p )
424  enddo
425  do p = 1, land_property_nmax
426  call comm_wait ( land_property(:,:,p), p )
427  enddo
428 
429  return
430  end subroutine land_vars_setup
431 
432  !-----------------------------------------------------------------------------
434  subroutine land_vars_restart_open
435  use scale_time, only: &
437  use scale_file_cartesc, only: &
439  file_cartesc_check_coordinates
440  use mod_land_admin, only: &
441  land_do
442  implicit none
443 
444  character(len=19) :: timelabel
445  character(len=H_LONG) :: basename
446  !---------------------------------------------------------------------------
447 
448  log_newline
449  log_info("LAND_vars_restart_open",*) 'Open restart file (LAND) '
450 
451  if ( land_do .and. land_restart_in_basename /= '' ) then
452 
454  call time_gettimelabel( timelabel )
455  basename = trim(land_restart_in_basename)//'_'//trim(timelabel)
456  else
457  basename = trim(land_restart_in_basename)
458  endif
459 
460  log_info("LAND_vars_restart_open",*) 'basename: ', trim(basename)
461 
462  call file_cartesc_open( basename, restart_fid, aggregate=land_restart_in_aggregate )
463 
464  if ( land_restart_in_check_coordinates ) then
465  call file_cartesc_check_coordinates( restart_fid, land=.true. )
466  end if
467 
468  else
469  log_info("LAND_vars_restart_open",*) 'restart file for land is not specified.'
470  endif
471 
472  return
473  end subroutine land_vars_restart_open
474 
475  !-----------------------------------------------------------------------------
477  subroutine land_vars_restart_read
478  use scale_prc, only: &
479  prc_abort
480  use scale_file, only: &
482  use scale_file_cartesc, only: &
483  file_cartesc_read, &
485  implicit none
486  !---------------------------------------------------------------------------
487 
488  if ( restart_fid /= -1 ) then
489  log_newline
490  log_info("LAND_vars_restart_read",*) 'Read from restart file (LAND) '
491 
492  call file_cartesc_read( restart_fid, var_name(i_temp), 'LXY', & ! [IN]
493  land_temp(:,:,:) ) ! [OUT]
494  call file_cartesc_read( restart_fid, var_name(i_water), 'LXY', & ! [IN]
495  land_water(:,:,:) ) ! [OUT]
496  call file_cartesc_read( restart_fid, var_name(i_sfc_temp), 'XY', & ! [IN]
497  land_sfc_temp(:,:) ) ! [OUT]
498  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_ir_dir), 'XY', & ! [IN]
499  land_sfc_albedo(:,:,i_r_direct ,i_r_ir ) ) ! [OUT]
500  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_ir_dif), 'XY', & ! [IN]
501  land_sfc_albedo(:,:,i_r_diffuse,i_r_ir ) ) ! [OUT]
502  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_nir_dir), 'XY', & ! [IN]
503  land_sfc_albedo(:,:,i_r_direct ,i_r_nir) ) ! [OUT]
504  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_nir_dif), 'XY', & ! [IN]
505  land_sfc_albedo(:,:,i_r_diffuse,i_r_nir) ) ! [OUT]
506  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_vis_dir), 'XY', & ! [IN]
507  land_sfc_albedo(:,:,i_r_direct ,i_r_vis) ) ! [OUT]
508  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_vis_dif), 'XY', & ! [IN]
509  land_sfc_albedo(:,:,i_r_diffuse,i_r_vis) ) ! [OUT]
510 
511  !call FILE_CARTESC_read( restart_fid, 'SNOW_SFC_TEMP', 'XY', & ! [OUT]
512  ! SNOW_SFC_TEMP(:,:) ) ! [IN]
513  !call FILE_CARTESC_read( restart_fid, 'SNOW_SWE', 'XY', & ! [OUT]
514  ! SNOW_SWE(:,:) ) ! [IN]
515  !call FILE_CARTESC_read( restart_fid, 'SNOW_Depth', 'XY', & ! [OUT]
516  ! SNOW_Depth(:,:) ) ! [IN]
517  !call FILE_CARTESC_read( restart_fid, 'SNOW_Dzero', 'XY', & ! [OUT]
518  ! SNOW_Dzero(:,:) ) ! [IN]
519  !call FILE_CARTESC_read( restart_fid, 'SNOW_nosnowsec', 'XY' & ! [OUT]
520  ! SNOW_nosnowsec(:,:) ) ! [IN]
521 
522  !!!!! Tentative for snow model !!!!!
523  snow_sfc_temp = 273.15_rp
524  snow_swe = 0.0_rp
525  snow_depth = 0.0_rp
526  snow_dzero = 0.0_rp
527  snow_nosnowsec = 0.0_rp
528 
529  if( file_get_aggregate(restart_fid) ) call file_cartesc_flush( restart_fid ) ! commit all pending read requests
530 
531  call land_vars_total
532  else
533  log_error("LAND_vars_restart_read",*) 'invalid restart file ID for land.'
534  call prc_abort
535  endif
536 
537  return
538  end subroutine land_vars_restart_read
539 
540  !-----------------------------------------------------------------------------
542  subroutine land_vars_history
543  use scale_file_history, only: &
544  file_history_in
545  use scale_atmos_hydrometeor, only: &
546  i_qv
547  implicit none
548 
549  real(RP) :: LAND_WATERDS(lkmax,lia,lja)
550  integer :: k, i, j
551  !---------------------------------------------------------------------------
552 
553  call prof_rapstart('LND_History', 1)
554 
555 
556  if ( land_vars_checkrange ) then
557  call valcheck( land_temp(lks:lke,lis:lie,ljs:lje), 0.0_rp, 1000.0_rp, &
558  var_name(i_temp), __file__, __line__ )
559  call valcheck( land_water(lks:lke,lis:lie,ljs:lje), 0.0_rp, 1000.0_rp, &
560  var_name(i_water), __file__, __line__ )
561  call valcheck( land_sfc_temp(lis:lie,ljs:lje), 0.0_rp, 1000.0_rp, &
562  var_name(i_sfc_temp), __file__, __line__ )
563  call valcheck( land_sfc_albedo(lis:lie,ljs:lje,i_r_direct ,i_r_ir ), 0.0_rp, 2.0_rp, &
564  var_name(i_sfc_alb_ir_dir ), __file__, __line__ )
565  call valcheck( land_sfc_albedo(lis:lie,ljs:lje,i_r_diffuse,i_r_ir ), 0.0_rp, 2.0_rp, &
566  var_name(i_sfc_alb_ir_dif ), __file__, __line__ )
567  call valcheck( land_sfc_albedo(lis:lie,ljs:lje,i_r_direct ,i_r_nir), 0.0_rp, 2.0_rp, &
568  var_name(i_sfc_alb_nir_dir), __file__, __line__ )
569  call valcheck( land_sfc_albedo(lis:lie,ljs:lje,i_r_diffuse,i_r_nir), 0.0_rp, 2.0_rp, &
570  var_name(i_sfc_alb_nir_dif), __file__, __line__ )
571  call valcheck( land_sfc_albedo(lis:lie,ljs:lje,i_r_direct ,i_r_vis), 0.0_rp, 2.0_rp, &
572  var_name(i_sfc_alb_vis_dir), __file__, __line__ )
573  call valcheck( land_sfc_albedo(lis:lie,ljs:lje,i_r_diffuse,i_r_vis), 0.0_rp, 2.0_rp, &
574  var_name(i_sfc_alb_vis_dif), __file__, __line__ )
575 
576  !call VALCHECK( SNOW_SFC_TEMP (IS:IE,JS:JE), 0.0_RP, 1000.0_RP, 'SNOW_SFC_TEMP', &
577  ! __FILE__, __LINE__ )
578  !call VALCHECK( SNOW_SWE (IS:IE,JS:JE), 0.0_RP, 1000.0_RP, 'SNOW_SWE', &
579  ! __FILE__, __LINE__ )
580  !call VALCHECK( SNOW_Depth (IS:IE,JS:JE), 0.0_RP, 1000.0_RP, 'SNOW_Depth', &
581  ! __FILE__, __LINE__ )
582  !call VALCHECK( SNOW_Dzero (IS:IE,JS:JE), 0.0_RP, 1000.0_RP, 'SNOW_Dzero', &
583  ! __FILE__, __LINE__ )
584  endif
585 
586  call file_history_in( land_temp(:,:,:), var_name(i_temp), var_desc(i_temp), var_unit(i_temp), dim_type='LXY', standard_name=var_stdn(i_temp) )
587  call file_history_in( land_water(:,:,:), var_name(i_water), var_desc(i_water), var_unit(i_water), dim_type='LXY', standard_name=var_stdn(i_water) )
588  do j = ljs, lje
589  do i = lis, lie
590  do k = 1, lkmax
591  land_waterds(k,i,j) = land_water(k,i,j) / land_property(i,j,i_waterlimit)
592  end do
593  end do
594  end do
595  call file_history_in( land_waterds(:,:,:), var_name(i_waterds), var_desc(i_waterds), var_unit(i_waterds), dim_type='LXY', fill_halo=.true., standard_name=var_stdn(i_waterds) )
596 
597 
598  call file_history_in( land_sfc_temp(:,:), var_name(i_sfc_temp), &
599  var_desc(i_sfc_temp), var_unit(i_sfc_temp), standard_name=var_stdn(i_sfc_temp) )
600  call file_history_in( land_sfc_albedo(:,:,i_r_direct ,i_r_ir ), var_name(i_sfc_alb_ir_dir), &
601  var_desc(i_sfc_alb_ir_dir), var_unit(i_sfc_alb_ir_dir), standard_name=var_stdn(i_sfc_alb_ir_dir) )
602  call file_history_in( land_sfc_albedo(:,:,i_r_diffuse,i_r_ir ), var_name(i_sfc_alb_ir_dif), &
603  var_desc(i_sfc_alb_ir_dif), var_unit(i_sfc_alb_ir_dif), standard_name=var_stdn(i_sfc_alb_ir_dif) )
604  call file_history_in( land_sfc_albedo(:,:,i_r_direct ,i_r_nir), var_name(i_sfc_alb_nir_dir), &
605  var_desc(i_sfc_alb_nir_dir), var_unit(i_sfc_alb_nir_dir), standard_name=var_stdn(i_sfc_alb_nir_dir) )
606  call file_history_in( land_sfc_albedo(:,:,i_r_diffuse,i_r_nir), var_name(i_sfc_alb_nir_dif), &
607  var_desc(i_sfc_alb_nir_dif), var_unit(i_sfc_alb_nir_dif), standard_name=var_stdn(i_sfc_alb_nir_dif) )
608  call file_history_in( land_sfc_albedo(:,:,i_r_direct ,i_r_vis), var_name(i_sfc_alb_vis_dir), &
609  var_desc(i_sfc_alb_vis_dir), var_unit(i_sfc_alb_vis_dir), standard_name=var_stdn(i_sfc_alb_vis_dir) )
610  call file_history_in( land_sfc_albedo(:,:,i_r_diffuse,i_r_vis), var_name(i_sfc_alb_vis_dif), &
611  var_desc(i_sfc_alb_vis_dif), var_unit(i_sfc_alb_vis_dif), standard_name=var_stdn(i_sfc_alb_vis_dif) )
612 
613  call file_history_in( land_sflx_mw(:,:), var_name(i_sflx_mw), &
614  var_desc(i_sflx_mw), var_unit(i_sflx_mw), standard_name=var_stdn(i_sflx_mw) )
615  call file_history_in( land_sflx_mu(:,:), var_name(i_sflx_mu), &
616  var_desc(i_sflx_mu), var_unit(i_sflx_mu), standard_name=var_stdn(i_sflx_mu) )
617  call file_history_in( land_sflx_mv(:,:), var_name(i_sflx_mv), &
618  var_desc(i_sflx_mv), var_unit(i_sflx_mv), standard_name=var_stdn(i_sflx_mv) )
619  call file_history_in( land_sflx_sh(:,:), var_name(i_sflx_sh), &
620  var_desc(i_sflx_sh), var_unit(i_sflx_sh), standard_name=var_stdn(i_sflx_sh) )
621  call file_history_in( land_sflx_lh(:,:), var_name(i_sflx_lh), &
622  var_desc(i_sflx_lh), var_unit(i_sflx_lh), standard_name=var_stdn(i_sflx_lh) )
623  if ( i_qv > 0 ) then
624  call file_history_in( land_sflx_qtrc(:,:,i_qv), var_name(i_sflx_evap), &
625  var_desc(i_sflx_evap), var_unit(i_sflx_evap), standard_name=var_stdn(i_sflx_evap) )
626  endif
627  call file_history_in( land_sflx_gh(:,:), var_name(i_sflx_gh), &
628  var_desc(i_sflx_gh), var_unit(i_sflx_gh), standard_name=var_stdn(i_sflx_gh) )
629  call file_history_in( land_sflx_water(:,:), var_name(i_sflx_water), &
630  var_desc(i_sflx_water), var_unit(i_sflx_water), standard_name=var_stdn(i_sflx_water) )
631  call file_history_in( land_sflx_ice(:,:), var_name(i_sflx_ice), &
632  var_desc(i_sflx_ice), var_unit(i_sflx_ice), standard_name=var_stdn(i_sflx_ice) )
633 
634  ! snow model
635  call file_history_in( snow_sfc_temp(:,:), 'SNOW_SFC_TEMP', 'Snow surface temperature', 'K' )
636  call file_history_in( snow_swe(:,:), 'SNOW_SWE', 'Snow water equivalent', 'kg/m2' )
637  call file_history_in( snow_depth(:,:), 'SNOW_Depth', 'Snow depth', 'm' )
638  call file_history_in( snow_dzero(:,:), 'SNOW_Dzero', 'Snow depth at melting point', 'm' )
639  call file_history_in( snow_nosnowsec(:,:), 'SNOW_nosnowsec', 'Time duration without snow', 's' )
640 
641  call prof_rapend ('LND_History', 1)
642 
643  return
644  end subroutine land_vars_history
645 
646  !-----------------------------------------------------------------------------
648  subroutine land_vars_total
649  use scale_statistics, only: &
651  statistics_total
652  use scale_land_grid_cartesc_real, only: &
657  implicit none
658 
659  !---------------------------------------------------------------------------
660 
661  if ( statistics_checktotal ) then
662 
663  ! 3D
664  call statistics_total( lka, lks, lke, lia, lis, lie, lja, ljs, lje, &
665  land_temp(:,:,:), var_name(i_temp), & ! (in)
666  land_grid_cartesc_real_vol(:,:,:), & ! (in)
668  call statistics_total( lka, lks, lke, lia, lis, lie, lja, ljs, lje, &
669  land_water(:,:,:), var_name(i_water), & ! (in)
670  land_grid_cartesc_real_vol(:,:,:), & ! (in)
672 
673  ! 2D
674  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
675  land_sfc_temp(:,:), var_name(i_sfc_temp), & ! [IN]
676  land_grid_cartesc_real_area(:,:), & ! [IN]
678  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
679  land_sfc_albedo(:,:,i_r_direct ,i_r_ir ), var_name(i_sfc_alb_ir_dir), & ! [IN]
680  land_grid_cartesc_real_area(:,:), & ! [IN]
682  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
683  land_sfc_albedo(:,:,i_r_diffuse,i_r_ir ), var_name(i_sfc_alb_ir_dif), & ! [IN]
684  land_grid_cartesc_real_area(:,:), & ! [IN]
686  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
687  land_sfc_albedo(:,:,i_r_direct ,i_r_nir), var_name(i_sfc_alb_nir_dir), & ! [IN]
688  land_grid_cartesc_real_area(:,:), & ! [IN]
690  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
691  land_sfc_albedo(:,:,i_r_diffuse,i_r_nir), var_name(i_sfc_alb_nir_dif), & ! [IN]
692  land_grid_cartesc_real_area(:,:), & ! [IN]
694  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
695  land_sfc_albedo(:,:,i_r_direct ,i_r_vis), var_name(i_sfc_alb_vis_dir), & ! [IN]
696  land_grid_cartesc_real_area(:,:), & ! [IN]
698  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
699  land_sfc_albedo(:,:,i_r_diffuse,i_r_vis), var_name(i_sfc_alb_vis_dif), & ! [IN]
700  land_grid_cartesc_real_area(:,:), & ! [IN]
702 
703  call statistics_total( lia, lis, lie, lja, ljs, lje, &
704  snow_sfc_temp(:,:), 'SNOW_SFC_TEMP', & ! (in)
705  land_grid_cartesc_real_area(:,:), & ! (in)
707  call statistics_total( lia, lis, lie, lja, ljs, lje, &
708  snow_swe(:,:), 'SNOW_SWE', &
709  land_grid_cartesc_real_area(:,:), & ! (in)
711  call statistics_total( lia, lis, lie, lja, ljs, lje, &
712  snow_depth(:,:), 'SNOW_Depth', & ! (in)
713  land_grid_cartesc_real_area(:,:), & ! (in)
715  call statistics_total( lia, lis, lie, lja, ljs, lje, &
716  snow_dzero(:,:), 'SNOW_Dzero', & ! (in)
717  land_grid_cartesc_real_area(:,:), & ! (in)
719  endif
720 
721  return
722  end subroutine land_vars_total
723 
724  !-----------------------------------------------------------------------------
726  subroutine land_param_read
727  use scale_prc, only: &
728  prc_abort
729  use scale_landuse, only: &
732  implicit none
733 
734  integer :: index
735  character(len=H_MID) :: description
736  real(RP) :: STRGMAX
737  real(RP) :: STRGCRT
738  real(RP) :: RSTOMA
739  real(RP) :: TCS
740  real(RP) :: HCS
741  real(RP) :: DFW
742  real(RP) :: ALBLW
743  real(RP) :: ALBSW
744  real(RP) :: Z0M
745  real(RP) :: Z0H
746  real(RP) :: Z0E
747 
748  namelist / param_land_property / &
750 
751  namelist / param_land_data / &
752  index, &
753  description, &
754  strgmax, &
755  strgcrt, &
756  rstoma, &
757  tcs, &
758  hcs, &
759  dfw, &
760  alblw, &
761  albsw, &
762  z0m, &
763  z0h, &
764  z0e
765 
766  integer :: n
767  integer :: ierr
768 
769  integer :: IO_FID_LAND_PROPERTY
770  !---------------------------------------------------------------------------
771 
772  !--- read namelist
773  rewind(io_fid_conf)
774  read(io_fid_conf,nml=param_land_property,iostat=ierr)
775  if( ierr < 0 ) then !--- missing
776  log_info("LAND_param_read",*) 'Not found namelist. Default used.'
777  elseif( ierr > 0 ) then !--- fatal error
778  log_error("LAND_param_read",*) 'Not appropriate names in namelist PARAM_LAND_PROPERTY. Check!'
779  call prc_abort
780  endif
781  log_nml(param_land_property)
782 
783  if( land_property_in_filename /= '' ) then
784  !--- Open land parameter file
785  io_fid_land_property = io_get_available_fid()
786  open( io_fid_land_property, &
787  file = trim(land_property_in_filename), &
788  form = 'formatted', &
789  status = 'old', &
790  iostat = ierr )
791 
792  if ( ierr /= 0 ) then
793  log_error("LAND_param_read",*) 'Failed to open land parameter file! :', &
795  call prc_abort
796  else
797  log_newline
798  log_info("LAND_param_read",*) 'Properties for each plant functional type (PFT)'
799  log_info_cont('(12(1x,A))') ' PFT DESCRIPTION', &
800  'Max Stg', &
801  'CRT Stg', &
802  'Stm.Res', &
803  'T condu', &
804  'H capac', &
805  'DFC Wat', &
806  'LW ALB', &
807  'SW ALB', &
808  ' Z0(m)', &
809  ' Z0(h)', &
810  ' Z0(e)'
811 
812  !--- read namelist
813  rewind(io_fid_land_property)
814 
816  ! default value
817  albsw = 0.2_rp
818  strgmax = 0.2_rp
819  strgcrt = 0.1_rp
820  rstoma = 50.0_rp
821  tcs = 1.0_rp
822  hcs = 2.e+6_rp
823  dfw = 1.e-6_rp
824  alblw = 0.04_rp
825  albsw = 0.22_rp
826  z0m = 0.1_rp
827  z0h = -1.0_rp
828  z0e = -1.0_rp
829 
830  read(io_fid_land_property,nml=param_land_data,iostat=ierr)
831  if ( ierr < 0 ) then !--- no more data
832  exit
833  elseif( ierr > 0 ) then !--- fatal error
834  log_error("LAND_param_read",*) 'Not appropriate names in namelist PARAM_LAND_DATA. Check!'
835  call prc_abort
836  endif
837 
838  if( z0h < 0.0_rp ) then
839  z0h = z0m / 7.4_rp ! defined by Garratt and Francey (1978)
840  endif
841  if( z0e < 0.0_rp ) then
842  z0e = z0m / 7.4_rp ! defined by Garratt and Francey (1978)
843  endif
844 
845  land_property_table(index,i_waterlimit ) = strgmax
846  land_property_table(index,i_watercritical) = strgcrt
847  land_property_table(index,i_stomataresist) = rstoma
848  land_property_table(index,i_thermalcond ) = tcs
849  land_property_table(index,i_heatcapacity ) = hcs
850  land_property_table(index,i_waterdiff ) = dfw
851  land_property_table(index,i_alblw ) = alblw
852  land_property_table(index,i_albsw ) = albsw
853  land_property_table(index,i_z0m ) = z0m
854  land_property_table(index,i_z0h ) = z0h
855  land_property_table(index,i_z0e ) = z0e
856 
857  log_info_cont('(1x,A4,I4.3,1x,A32,4(1x,F7.3),2(1x,ES7.1),5(1x,F6.3))') &
858  'IDX=', index, &
859  trim(description), &
860  strgmax, &
861  strgcrt, &
862  rstoma, &
863  tcs, &
864  hcs, &
865  dfw, &
866  alblw, &
867  albsw, &
868  z0m, &
869  z0h, &
870  z0e
871  enddo
872 
873  end if
874 
875  close( io_fid_land_property )
876 
877  endif
878 
879  return
880  end subroutine land_param_read
881 
882  !-----------------------------------------------------------------------------
884  function convert_ws2vwc( WS, critical ) result( VWC )
885  implicit none
886 
887  real(RP), intent(in) :: WS(lia,lja) ! water saturation [fraction]
888  logical, intent(in) :: critical ! is I_WaterCritical used?
889 
890  real(RP) :: VWC(lia,lja) ! volumetric water content [m3/m3]
891 
892  ! work
893  integer :: i, j, num
894  !---------------------------------------------------------------------------
895 
896  if( critical ) then
897  num = i_watercritical
898  else
899  num = i_waterlimit
900  end if
901 
902  do j = ljs, lje
903  do i = lis, lie
904  vwc(i,j) = max( min( ws(i,j)*land_property(i,j,num), land_property(i,j,num) ), 0.0_rp )
905  end do
906  end do
907 
908  return
909  end function convert_ws2vwc
910 
911  !-----------------------------------------------------------------------------
913  subroutine land_vars_restart_create
914  use scale_time, only: &
916  use scale_file_cartesc, only: &
918  use mod_land_admin, only: &
919  land_do
920  implicit none
921 
922  character(len=19) :: timelabel
923  character(len=H_LONG) :: basename
924  !---------------------------------------------------------------------------
925 
926  if ( land_do .and. land_restart_out_basename /= '' ) then
927 
928  log_newline
929  log_info("LAND_vars_restart_create",*) 'Create restart file (LAND) '
930 
932  call time_gettimelabel( timelabel )
933  basename = trim(land_restart_out_basename)//'_'//trim(timelabel)
934  else
935  basename = trim(land_restart_out_basename)
936  endif
937 
938  log_info("LAND_vars_restart_create",*) 'basename: ', trim(basename)
939 
940  call file_cartesc_create( &
942  restart_fid, & ! [OUT]
943  aggregate=land_restart_out_aggregate ) ! [IN]
944 
945  endif
946 
947  return
948  end subroutine land_vars_restart_create
949 
950  !-----------------------------------------------------------------------------
952  subroutine land_vars_restart_enddef
953  use scale_file_cartesc, only: &
955  implicit none
956 
957  if ( restart_fid /= -1 ) then
958  call file_cartesc_enddef( restart_fid ) ! [IN]
959  endif
960 
961  return
962  end subroutine land_vars_restart_enddef
963 
964  !-----------------------------------------------------------------------------
966  subroutine land_vars_restart_close
967  use scale_file_cartesc, only: &
969  implicit none
970  !---------------------------------------------------------------------------
971 
972  if ( restart_fid /= -1 ) then
973  log_newline
974  log_info("LAND_vars_restart_close",*) 'Close restart file (LAND) '
975 
976  call file_cartesc_close( restart_fid ) ! [IN]
977 
978  restart_fid = -1
979  endif
980 
981  return
982  end subroutine land_vars_restart_close
983 
984  !-----------------------------------------------------------------------------
986  subroutine land_vars_restart_def_var
987  use scale_file_cartesc, only: &
989  implicit none
990  integer :: i
991  !---------------------------------------------------------------------------
992 
993  if ( restart_fid /= -1 ) then
994 
995  do i = i_temp, i_water
996  if ( i == i_waterds ) cycle
997  call file_cartesc_def_var( restart_fid, & ! [IN]
998  var_name(i), var_desc(i), var_unit(i), & ! [IN]
999  'LXY', land_restart_out_dtype, & ! [IN]
1000  var_id(i), & ! [OUT]
1001  standard_name=var_stdn(i) ) ! [IN]
1002  end do
1003  do i = i_sfc_temp, i_sfc_alb_vis_dif
1004  call file_cartesc_def_var( restart_fid, & ! [IN]
1005  var_name(i), var_desc(i), var_unit(i), & ! [IN]
1006  'XY', land_restart_out_dtype, & ! [IN]
1007  var_id(i), & ! [OUT]
1008  standard_name=var_stdn(i) ) ! [IN]
1009  end do
1010 
1011  !call FILE_CARTESC_def_var( restart_fid, 'SNOW_SFC_TEMP', 'Snow surface temperature', &
1012  ! 'K', 'XY', LAND_RESTART_OUT_DTYPE, ????? )
1013  !call FILE_CARTESC_def_var( restart_fid, 'SNOW_SWE', 'Snow water equivalent', &
1014  ! 'kg/m2', 'XY', LAND_RESTART_OUT_DTYPE, ????? )
1015  !call FILE_CARTESC_def_var( restart_fid, 'SNOW_Depth', 'Snow depth', &
1016  ! 'm', 'XY', LAND_RESTART_OUT_DTYPE, ????? )
1017  !call FILE_CARTESC_def_var( restart_fid, 'SNOW_Dzero', 'Snow depth at melting point', &
1018  ! 'm', 'XY', LAND_RESTART_OUT_DTYPE, ????? )
1019  !call FILE_CARTESC_def_var( restart_fid, 'SNOW_nosnowsec', 'Time duration without snow', &
1020  ! 's', 'XY', LAND_RESTART_OUT_DTYPE, ????? )
1021 
1022  endif
1023 
1024  return
1025  end subroutine land_vars_restart_def_var
1026 
1027  !-----------------------------------------------------------------------------
1029  subroutine land_vars_restart_write
1030  use scale_file_cartesc, only: &
1031  file_cartesc_write_var
1032  implicit none
1033  !---------------------------------------------------------------------------
1034 
1035  if ( restart_fid /= -1 ) then
1036 
1037  call land_vars_total
1038 
1039  call file_cartesc_write_var( restart_fid, var_id(i_temp), & ! [IN]
1040  land_temp(:,:,:), & ! [IN]
1041  var_name(i_temp), 'LXY', fill_halo=.true. ) ! [IN]
1042  call file_cartesc_write_var( restart_fid, var_id(i_water), & ! [IN]
1043  land_water(:,:,:), & ! [IN]
1044  var_name(i_water), 'LXY', fill_halo=.true. ) ! [IN]
1045  call file_cartesc_write_var( restart_fid, var_id(i_sfc_temp), & ! [IN]
1046  land_sfc_temp(:,:), & ! [IN]
1047  var_name(i_sfc_temp), 'XY', fill_halo=.true. ) ! [IN]
1048  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_ir_dir), & ! [IN]
1049  land_sfc_albedo(:,:,i_r_direct ,i_r_ir ), & ! [IN]
1050  var_name(i_sfc_alb_ir_dir), 'XY', fill_halo=.true. ) ! [IN]
1051  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_ir_dif), & ! [IN]
1052  land_sfc_albedo(:,:,i_r_diffuse,i_r_ir ), & ! [IN]
1053  var_name(i_sfc_alb_ir_dif), 'XY', fill_halo=.true. ) ! [IN]
1054  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_nir_dir), & ! [IN]
1055  land_sfc_albedo(:,:,i_r_direct ,i_r_nir), & ! [IN]
1056  var_name(i_sfc_alb_nir_dir), 'XY', fill_halo=.true. ) ! [IN]
1057  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_nir_dif), & ! [IN]
1058  land_sfc_albedo(:,:,i_r_diffuse,i_r_nir), & ! [IN]
1059  var_name(i_sfc_alb_nir_dif), 'XY', fill_halo=.true. ) ! [IN]
1060  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_vis_dir), & ! [IN]
1061  land_sfc_albedo(:,:,i_r_direct ,i_r_vis), & ! [IN]
1062  var_name(i_sfc_alb_vis_dir), 'XY', fill_halo=.true. ) ! [IN]
1063  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_vis_dif), & ! [IN]
1064  land_sfc_albedo(:,:,i_r_diffuse,i_r_vis), & ! [IN]
1065  var_name(i_sfc_alb_vis_dif), 'XY', fill_halo=.true. ) ! [IN]
1066 
1067  !call FILE_CARTESC_write_var( restart_fid, VMAX+1, SNOW_SFC_TEMP(:,:), &
1068  ! 'SNOW_SFC_TEMP', 'XY', fill_halo=.true. )
1069  !call FILE_CARTESC_write_var( restart_fid, VMAX+2, SNOW_SWE(:,:), &
1070  ! 'SNOW_SWE', 'XY', fill_halo=.true. )
1071  !call FILE_CARTESC_write_var( restart_fid, VMAX+3, SNOW_Depth(:,:), &
1072  ! 'SNOW_Depth', 'XY', fill_halo=.true. )
1073  !call FILE_CARTESC_write_var( restart_fid, VMAX+4, SNOW_Dzero(:,:), &
1074  ! 'SNOW_Dzero', 'XY', fill_halo=.true. )
1075  !call FILE_CARTESC_write_var( restart_fid, VMAX+5, SNOW_nosnowsec(:,:), &
1076  ! 'SNOW_nosnowsec', 'XY', fill_halo=.true. )
1077 
1078  endif
1079 
1080  return
1081  end subroutine land_vars_restart_write
1082 
1083 end module mod_land_vars
module Land admin
real(rp), dimension(:,:), allocatable, public snow_swe
snow water equivalent [kg/m2]
module DEBUG
Definition: scale_debug.F90:11
logical, public land_restart_out_aggregate
Switch to use aggregate file.
real(rp), dimension(:,:), allocatable, public land_sflx_water
land surface water flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public atmos_pres
subroutine, public land_vars_restart_close
Close restart file.
real(rp), dimension(:,:), allocatable, public land_sflx_ice
land surface ice flux [kg/m2/s]
logical, public land_restart_output
Output restart file?
module coupler / surface-atmospehre
integer, parameter, public i_heatcapacity
integer, parameter, public i_waterlimit
real(rp), dimension(:,:), allocatable, public atmos_dens
real(rp) function, dimension(lia, lja), public convert_ws2vwc(WS, critical)
conversion from water saturation [fraction] to volumetric water content [m3/m3]
module land / grid / cartesianC / real
real(rp), dimension(:,:,:), allocatable, public land_property
land surface property
integer, parameter, public i_r_vis
module land / grid / cartesianC / index
real(rp), dimension(:,:), allocatable, public snow_sfc_temp
snow surface temperature [K]
subroutine, public land_vars_setup
Setup.
integer, parameter, public i_watercritical
integer, public qa
real(rp), dimension(:,:), allocatable, public atmos_sfc_dens
real(rp), dimension(:,:), allocatable, public atmos_v
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:55
integer, parameter, public n_rad_dir
integer, parameter, public n_rad_rgn
real(rp), dimension(:,:), allocatable, public atmos_sflx_snow
subroutine, public land_vars_restart_enddef
Exit netCDF define mode.
real(rp), dimension(:,:), allocatable, public land_q2
land surface water vapor at 2m [kg/kg]
character(len=h_long), public land_restart_in_basename
Basename of the input file.
character(len=h_short), public land_restart_out_dtype
REAL4 or REAL8.
real(rp), dimension(:,:), allocatable, public snow_depth
snow depth [m]
integer, parameter, public i_z0h
logical, public statistics_checktotal
calc&report variable totals to logfile?
integer, parameter, public i_z0e
real(rp), dimension(:,:,:), allocatable, public land_sflx_qtrc
land surface tracer flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_sflx_mu
land surface u-momentum flux [kg/m2/s]
integer, parameter, public landuse_pft_nmin
minimum number of PFT type
real(rp), public const_undef
Definition: scale_const.F90:41
module COMMUNICATION
real(rp), dimension(:,:), allocatable, public snow_nosnowsec
sec while no snow [s]
subroutine, public land_vars_restart_create
Create land restart file.
real(rp), dimension(:,:), allocatable, public atmos_temp
subroutine, public land_vars_restart_read
Read land restart.
real(rp), dimension(:,:), allocatable, public land_sfc_temp
land surface skin temperature [K]
real(rp), dimension(:,:), allocatable, public atmos_sflx_rain
module file
Definition: scale_file.F90:15
subroutine, public file_cartesc_create(basename, title, datatype, fid, date, subsec, haszcoord, append, aggregate, single)
Create/open a netCDF file.
module TRACER
real(rp), dimension(:,:), allocatable, public land_v10
land surface velocity v at 10m [m/s]
real(rp), dimension(:,:), allocatable, public atmos_pbl
module atmosphere / hydrometeor
real(rp), dimension(:,:,:,:), allocatable, public land_sfc_albedo
land surface albedo (direct/diffuse,IR/near-IR/VIS) (0-1)
module LANDUSE
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:94
real(rp), dimension(:,:), allocatable, public land_t2
land surface temperature at 2m [K]
logical, public land_restart_in_postfix_timelabel
Add timelabel to the basename of input file?
integer function, public io_get_available_fid()
search & get available file ID
Definition: scale_io.F90:313
character(len=h_long), public land_restart_out_basename
Basename of the output file.
module PROCESS
Definition: scale_prc.F90:11
real(rp), dimension(:,:), allocatable, public land_grid_cartesc_real_area
area of grid cell
real(rp), dimension(:,:,:), allocatable, public land_water_t
tendency of LAND_WATER
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]
real(rp), dimension(:,:), allocatable, public land_sflx_lh
land surface latent heat flux [J/m2/s]
logical, public land_restart_in_aggregate
Switch to use aggregate file.
subroutine, public file_cartesc_enddef(fid)
Exit netCDF file define mode.
module TIME
Definition: scale_time.F90:16
real(rp), public land_grid_cartesc_real_totarea
total area
real(rp), dimension(:,:), allocatable, public atmos_qv
integer, parameter, public i_stomataresist
integer, dimension(:,:,:), allocatable, public landuse_index_pft
index of PFT for each mosaic
module LAND Variables
real(rp), dimension(:,:), allocatable, public land_u10
land surface velocity u at 10m [m/s]
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
module CONSTANT
Definition: scale_const.F90:11
real(rp), dimension(:,:,:), allocatable, public land_temp_t
tendency of LAND_TEMP
integer, parameter, public i_r_direct
subroutine, public file_cartesc_def_var(fid, varname, desc, unit, dim_type, datatype, vid, standard_name, timeintv, nsteps, cell_measures)
Define a variable to file.
real(rp), dimension(:,:), allocatable, public land_sflx_gh
land surface heat flux [J/m2/s]
logical function, public file_get_aggregate(fid)
real(rp), dimension(:,:), allocatable, public snow_dzero
snow depth at melting point [m]
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:157
real(rp), dimension(:,:,:), allocatable, public land_water
moisture of each soil layer [m3/m3]
logical, public land_restart_out_postfix_timelabel
Add timelabel to the basename of output file?
real(rp), dimension(:,:), allocatable, public atmos_u
subroutine, public land_vars_total
Budget monitor for land.
module profiler
Definition: scale_prof.F90:11
character(len=h_mid), public land_restart_out_title
Title of the output file.
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
real(rp), dimension(:,:), allocatable, public atmos_cossza
integer, parameter, public i_r_nir
integer, parameter, public i_z0m
real(rp), dimension(:,:,:,:), allocatable, public atmos_sflx_rad_dn
character(len=h_long), public land_property_in_filename
the file of land parameter table
module PRECISION
module file / cartesianC
real(rp), dimension(:,:), allocatable, public land_sflx_mw
land surface w-momentum flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public land_sflx_mv
land surface v-momentum flux [kg/m2/s]
subroutine, public land_vars_history
History output set for land variables.
integer, public landuse_pft_nmax
number of plant functional type(PFT)
subroutine, public land_vars_restart_open
Open land restart file for read.
module Statistics
integer, parameter, public i_alblw
integer, parameter, public i_r_ir
integer, parameter, public land_property_nmax
real(rp), dimension(:,:), allocatable, public land_sflx_sh
land surface sensible heat flux [J/m2/s]
integer, parameter, public i_albsw
module STDIO
Definition: scale_io.F90:10
real(rp), dimension(:,:), allocatable, public atmos_w
integer, parameter, public i_r_diffuse
subroutine, public file_cartesc_flush(fid)
Flush all pending requests to a netCDF file (PnetCDF only)
subroutine, public land_vars_restart_write
Write land variables to restart file.
integer, parameter, public i_thermalcond
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:210
subroutine, public file_cartesc_open(basename, fid, aggregate)
open a netCDF file for read
real(rp), public land_grid_cartesc_real_totvol
total volume
integer, parameter, public i_waterdiff
real(rp), dimension(:,:,:), allocatable, public land_grid_cartesc_real_vol
volume of grid cell
subroutine, public file_cartesc_close(fid)
Close a netCDF file.
logical, public land_do
module file_history