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_finalize
32  public :: land_vars_restart_read
33  public :: land_vars_restart_write
34  public :: land_vars_history
35  public :: land_vars_monitor
36  public :: land_vars_check
37 
38  public :: land_vars_restart_create
39  public :: land_vars_restart_open
41  public :: land_vars_restart_enddef
42  public :: land_vars_restart_close
43 
44  public :: convert_ws2vwc
45 
46  !-----------------------------------------------------------------------------
47  !
48  !++ Public parameters & variables
49  !
50  logical, public :: land_restart_output = .false.
51 
52  character(len=H_LONG), public :: land_restart_in_basename = ''
53  logical, public :: land_restart_in_aggregate
54  logical, public :: land_restart_in_postfix_timelabel = .false.
55  character(len=H_LONG), public :: land_restart_out_basename = ''
56  logical, public :: land_restart_out_aggregate
57  logical, public :: land_restart_out_postfix_timelabel = .true.
58  character(len=H_MID), public :: land_restart_out_title = 'LAND restart'
59  character(len=H_SHORT), public :: land_restart_out_dtype = 'DEFAULT'
60 
61  ! prognostic variables
62  real(rp), public, allocatable :: land_temp (:,:,:)
63  real(rp), public, allocatable :: land_water (:,:,:)
64  real(rp), public, allocatable :: land_ice (:,:,:)
65  real(rp), public, allocatable :: land_sfc_temp (:,:)
66  real(rp), public, allocatable :: land_sfc_albedo(:,:,:,:)
67 
68  ! for snow model
69  real(rp), public, allocatable :: snow_sfc_temp (:,:)
70  real(rp), public, allocatable :: snow_swe (:,:)
71  real(rp), public, allocatable :: snow_depth (:,:)
72  real(rp), public, allocatable :: snow_dzero (:,:)
73  real(rp), public, allocatable :: snow_nosnowsec(:,:)
74 
75  ! tendency variables
76  real(rp), public, allocatable :: land_temp_t (:,:,:)
77  real(rp), public, allocatable :: land_water_t(:,:,:)
78  real(rp), public, allocatable :: land_ice_t (:,:,:)
79 
80  ! surface flux for land
81  real(rp), public, allocatable :: land_sflx_gh (:,:)
82  real(rp), public, allocatable :: land_sflx_water(:,:)
83  real(rp), public, allocatable :: land_sflx_engi (:,:)
84 
85  ! surface flux for atmosphere
86  real(rp), public, allocatable :: land_sflx_mw (:,:)
87  real(rp), public, allocatable :: land_sflx_mu (:,:)
88  real(rp), public, allocatable :: land_sflx_mv (:,:)
89  real(rp), public, allocatable :: land_sflx_sh (:,:)
90  real(rp), public, allocatable :: land_sflx_lh (:,:)
91  real(rp), public, allocatable :: land_sflx_qtrc(:,:,:)
92  real(rp), public, allocatable :: land_u10 (:,:)
93  real(rp), public, allocatable :: land_v10 (:,:)
94  real(rp), public, allocatable :: land_t2 (:,:)
95  real(rp), public, allocatable :: land_q2 (:,:)
96  real(rp), public, allocatable, target :: land_ustar(:,:)
97  real(rp), public, allocatable, target :: land_tstar(:,:)
98  real(rp), public, allocatable, target :: land_qstar(:,:)
99  real(rp), public, allocatable, target :: land_wstar(:,:)
100  real(rp), public, allocatable, target :: land_rlmo (:,:)
101  real(rp), public, pointer :: soil_ustar(:,:)
102  real(rp), public, pointer :: soil_tstar(:,:)
103  real(rp), public, pointer :: soil_qstar(:,:)
104  real(rp), public, pointer :: soil_wstar(:,:)
105  real(rp), public, pointer :: soil_rlmo (:,:)
106  real(rp), public, allocatable :: snow_ustar(:,:)
107  real(rp), public, allocatable :: snow_tstar(:,:)
108  real(rp), public, allocatable :: snow_qstar(:,:)
109  real(rp), public, allocatable :: snow_wstar(:,:)
110  real(rp), public, allocatable :: snow_rlmo (:,:)
111 
112  real(rp), public, allocatable :: land_runoff (:,:)
113  real(rp), public, allocatable :: land_runoff_engi(:,:)
114 
115 
116  ! recieved atmospheric variables
117  real(rp), public, allocatable :: atmos_temp (:,:)
118  real(rp), public, allocatable :: atmos_pres (:,:)
119  real(rp), public, allocatable :: atmos_w (:,:)
120  real(rp), public, allocatable :: atmos_u (:,:)
121  real(rp), public, allocatable :: atmos_v (:,:)
122  real(rp), public, allocatable :: atmos_dens (:,:)
123  real(rp), public, allocatable :: atmos_qv (:,:)
124  real(rp), public, allocatable :: atmos_pbl (:,:)
125  real(rp), public, allocatable :: atmos_sfc_dens (:,:)
126  real(rp), public, allocatable :: atmos_sfc_pres (:,:)
127  real(rp), public, allocatable :: atmos_sflx_rad_dn(:,:,:,:)
128  real(rp), public, allocatable :: atmos_cossza (:,:)
129  real(rp), public, allocatable :: atmos_sflx_water (:,:)
130  real(rp), public, allocatable :: atmos_sflx_engi (:,:)
131 
132 
133  logical, public :: snow_flag
134 
135 
136  real(rp), public, allocatable :: land_property(:,:,:)
137 
138  character(len=H_LONG), public :: land_property_in_filename = ''
139 
140  integer, public, parameter :: land_property_nmax = 11
141  integer, public, parameter :: i_waterlimit = 1 ! maximum soil moisture [m3/m3]
142  integer, public, parameter :: i_watercritical = 2 ! critical soil moisture [m3/m3]
143  integer, public, parameter :: i_stomataresist = 3 ! stomata resistance [1/s]
144  integer, public, parameter :: i_thermalcond = 4 ! thermal conductivity for soil [W/K/m]
145  integer, public, parameter :: i_heatcapacity = 5 ! heat capacity for soil [J/K/m3]
146  integer, public, parameter :: i_waterdiff = 6 ! moisture diffusivity in the soil [m2/s]
147  integer, public, parameter :: i_alblw = 7 ! surface albedo for long wave [1]
148  integer, public, parameter :: i_albsw = 8 ! surface albedo for short wave [1]
149  integer, public, parameter :: i_z0m = 9 ! roughness length for momemtum [m]
150  integer, public, parameter :: i_z0h = 10 ! roughness length for heat [m]
151  integer, public, parameter :: i_z0e = 11 ! roughness length for vapor [m]
152 
153  !-----------------------------------------------------------------------------
154  !
155  !++ Private procedure
156  !
157  private :: land_param_read
158 
159  !-----------------------------------------------------------------------------
160  !
161  !++ Private parameters & variables
162  !
163  logical, private :: land_vars_checkrange = .false.
164 
165  ! index of the prognostic variables
166  integer, private, parameter :: vmax = 16
167  integer, private, parameter :: i_temp = 1
168  integer, private, parameter :: i_water = 2
169  integer, private, parameter :: i_ice = 3
170  integer, private, parameter :: i_waterds = 4
171  integer, private, parameter :: i_sfc_temp = 5
172  integer, private, parameter :: i_sfc_alb_ir_dir = 6
173  integer, private, parameter :: i_sfc_alb_ir_dif = 7
174  integer, private, parameter :: i_sfc_alb_nir_dir = 8
175  integer, private, parameter :: i_sfc_alb_nir_dif = 9
176  integer, private, parameter :: i_sfc_alb_vis_dir = 10
177  integer, private, parameter :: i_sfc_alb_vis_dif = 11
178  integer, private, parameter :: i_snow_sfc_temp = 12
179  integer, private, parameter :: i_snow_swe = 13
180  integer, private, parameter :: i_snow_depth = 14
181  integer, private, parameter :: i_snow_dzero = 15
182  integer, private, parameter :: i_snow_nosnowsec = 16
183 
184  character(len=H_SHORT), private :: var_name(vmax)
185  character(len=H_MID), private :: var_desc(vmax)
186  character(len=H_MID), private :: var_stdn(vmax)
187  character(len=H_SHORT), private :: var_unit(vmax)
188  integer, private :: var_id(vmax)
189  integer, private :: restart_fid = -1 ! file ID
190 
191  data var_name / 'LAND_TEMP', &
192  'LAND_WATER', &
193  'LAND_ICE', &
194  'LAND_DSAT', &
195  'LAND_SFC_TEMP', &
196  'LAND_SFC_ALB_IR_dir', &
197  'LAND_SFC_ALB_IR_dif', &
198  'LAND_SFC_ALB_NIR_dir', &
199  'LAND_SFC_ALB_NIR_dif', &
200  'LAND_SFC_ALB_VIS_dir', &
201  'LAND_SFC_ALB_VIS_dif', &
202  'LAND_SNOW_SFC_TEMP', &
203  'LAND_SNOW_SWE', &
204  'LAND_SNOW_Depth', &
205  'LAND_SNOW_Dzero', &
206  'LAND_SNOW_nosnowsec' /
207 
208  data var_desc / 'temperature at each soil layer', &
209  'moisture at each soil layer', &
210  'ice at each soil layer', &
211  'degree of saturation at each soil layer', &
212  'land surface skin temperature', &
213  'land surface albedo for IR (direct)', &
214  'land surface albedo for IR (diffuse)', &
215  'land surface albedo for NIR (direct)', &
216  'land surface albedo for NIR (diffuse)', &
217  'land surface albedo for VIS (direct)', &
218  'land surface albedo for VIS (diffuse)', &
219  'Snow surface temperature', &
220  'Snow water equivalent', &
221  'Snow depth', &
222  'Snow depth at melting point', &
223  'Time duration without snow' /
224 
225  data var_stdn / 'soil_temperature', &
226  'volume_fraction_of_condensed_water_in_soil', &
227  '', &
228  'volume_fraction_of_condensed_water_in_soil_at_field_capacity', &
229  'surface_temperature_where_land', &
230  '', &
231  '', &
232  '', &
233  '', &
234  '', &
235  '', &
236  '', &
237  '', &
238  '', &
239  '', &
240  '' /
241 
242  data var_unit / 'K', &
243  'm3/m3', &
244  'm3/m3', &
245  '1', &
246  'K', &
247  '1', &
248  '1', &
249  '1', &
250  '1', &
251  '1', &
252  '1', &
253  'K', &
254  'kg/m2', &
255  'm', &
256  'm', &
257  's' /
258 
259  logical, private :: land_restart_in_check_coordinates = .true.
260 
261  ! for monitor
262  integer, parameter :: im_temp = 1
263  integer, parameter :: im_water = 2
264  integer, parameter :: im_ice = 3
265  integer, parameter :: im_sfc = 4
266  integer, parameter :: im_roff = 5
267  integer, parameter :: im_masflx = 6
268  integer, parameter :: im_engi = 7
269  integer, parameter :: im_w_engi = 8
270  integer, parameter :: im_i_engi = 9
271  integer, parameter :: im_engsfc_gh = 10
272  integer, parameter :: im_engsfc_ei = 11
273  integer, parameter :: im_roff_ei = 12
274  integer, parameter :: im_engflx = 13
275  integer, parameter :: im_max = 13
276  integer, private :: monit_id(im_max)
277 
278  !-----------------------------------------------------------------------------
279 contains
280  !-----------------------------------------------------------------------------
282  subroutine land_vars_setup
283  use scale_prc, only: &
284  prc_abort
285  use scale_const, only: &
286  undef => const_undef
287  use scale_comm_cartesc, only: &
288  comm_vars8, &
289  comm_wait
290  use scale_landuse, only: &
294  use mod_land_admin, only: &
295  snow_type
296  use scale_monitor, only: &
298  implicit none
299 
300  namelist / param_land_vars / &
304  land_restart_in_check_coordinates, &
311  land_vars_checkrange
312 
313  real(rp), allocatable :: land_property_table(:,:)
314 
315 
316  integer :: ierr
317  integer :: i, j, iv, p
318  !---------------------------------------------------------------------------
319 
320  log_newline
321  log_info("LAND_vars_setup",*) 'Setup'
322 
323  select case ( snow_type )
324  case ( 'NONE', 'OFF' )
325  snow_flag = .false.
326  case default
327  snow_flag = .true.
328  end select
329 
330  allocate( land_temp(lkmax,lia,lja) )
331  allocate( land_water(lkmax,lia,lja) )
332  allocate( land_ice(lkmax,lia,lja) )
333  allocate( land_sfc_temp(lia,lja) )
335  land_temp(:,:,:) = undef
336  land_water(:,:,:) = undef
337  land_ice(:,:,:) = undef
338  land_sfc_temp(:,:) = undef
339  land_sfc_albedo(:,:,:,:) = undef
340  !$acc enter data create(LAND_TEMP,LAND_WATER,LAND_ICE,LAND_SFC_TEMP,LAND_SFC_albedo)
341 
342  if ( snow_flag ) then
343  allocate( snow_sfc_temp(lia,lja) )
344  allocate( snow_swe(lia,lja) )
345  allocate( snow_depth(lia,lja) )
346  allocate( snow_dzero(lia,lja) )
347  allocate( snow_nosnowsec(lia,lja) )
348  snow_sfc_temp(:,:) = undef
349  snow_swe(:,:) = undef
350  snow_depth(:,:) = undef
351  snow_dzero(:,:) = undef
352  snow_nosnowsec(:,:) = undef
353  end if
354 
355  allocate( land_temp_t(lkmax,lia,lja) )
356  allocate( land_water_t(lkmax,lia,lja) )
357  allocate( land_ice_t(lkmax,lia,lja) )
358  land_temp_t(:,:,:) = undef
359  land_water_t(:,:,:) = undef
360  land_ice_t(:,:,:) = undef
361  !$acc enter data create(LAND_TEMP_t,LAND_WATER_t,LAND_ICE_t)
362 
363  allocate( land_sflx_gh(lia,lja) )
364  allocate( land_sflx_water(lia,lja) )
365  allocate( land_sflx_engi(lia,lja) )
366  land_sflx_gh(:,:) = undef
367  land_sflx_water(:,:) = undef
368  land_sflx_engi(:,:) = undef
369  !$acc enter data create(LAND_SFLX_GH,LAND_SFLX_water,LAND_SFLX_ENGI)
370 
371  allocate( land_runoff(lia,lja) )
372  allocate( land_runoff_engi(lia,lja) )
373  land_runoff(:,:) = undef
374  land_runoff_engi(:,:) = undef
375  !$acc enter data create(LAND_RUNOFF,LAND_RUNOFF_ENGI)
376 
377  allocate( land_sflx_mw(lia,lja) )
378  allocate( land_sflx_mu(lia,lja) )
379  allocate( land_sflx_mv(lia,lja) )
380  allocate( land_sflx_sh(lia,lja) )
381  allocate( land_sflx_lh(lia,lja) )
382  allocate( land_sflx_qtrc(lia,lja,max(qa,1)) )
383  land_sflx_mw(:,:) = undef
384  land_sflx_mu(:,:) = undef
385  land_sflx_mv(:,:) = undef
386  land_sflx_sh(:,:) = undef
387  land_sflx_lh(:,:) = undef
388  land_sflx_qtrc(:,:,:) = undef
389  !$acc enter data create(LAND_SFLX_MW,LAND_SFLX_MU,LAND_SFLX_MV,LAND_SFLX_SH,LAND_SFLX_LH,LAND_SFLX_QTRC)
390 
391  allocate( land_u10(lia,lja) )
392  allocate( land_v10(lia,lja) )
393  allocate( land_t2(lia,lja) )
394  allocate( land_q2(lia,lja) )
395  land_u10(:,:) = undef
396  land_v10(:,:) = undef
397  land_t2(:,:) = undef
398  land_q2(:,:) = undef
399  !$acc enter data create(LAND_U10,LAND_V10,LAND_T2,LAND_Q2)
400 
401  allocate( land_ustar(lia,lja) )
402  allocate( land_tstar(lia,lja) )
403  allocate( land_qstar(lia,lja) )
404  allocate( land_wstar(lia,lja) )
405  allocate( land_rlmo(lia,lja) )
406  land_ustar(:,:) = undef
407  land_tstar(:,:) = undef
408  land_qstar(:,:) = undef
409  land_wstar(:,:) = undef
410  land_rlmo(:,:) = undef
411  !$acc enter data create(LAND_Ustar,LAND_Tstar,LAND_Qstar,LAND_Wstar,LAND_RLmo)
412 
413  if ( snow_flag ) then
414  allocate( soil_ustar(lia,lja) )
415  allocate( soil_tstar(lia,lja) )
416  allocate( soil_qstar(lia,lja) )
417  allocate( soil_wstar(lia,lja) )
418  allocate( soil_rlmo(lia,lja) )
419  soil_ustar(:,:) = undef
420  soil_tstar(:,:) = undef
421  soil_qstar(:,:) = undef
422  soil_wstar(:,:) = undef
423  soil_rlmo(:,:) = undef
424  !$acc enter data create(SOIL_Ustar,SOIL_Tstar,SOIL_Qstar,SOIL_Wstar,SOIL_RLmo)
425  else
431  end if
432  if ( snow_flag ) then
433  allocate( snow_ustar(lia,lja) )
434  allocate( snow_tstar(lia,lja) )
435  allocate( snow_qstar(lia,lja) )
436  allocate( snow_wstar(lia,lja) )
437  allocate( snow_rlmo(lia,lja) )
438  snow_ustar(:,:) = undef
439  snow_tstar(:,:) = undef
440  snow_qstar(:,:) = undef
441  snow_wstar(:,:) = undef
442  snow_rlmo(:,:) = undef
443  end if
444 
445  allocate( atmos_temp(lia,lja) )
446  allocate( atmos_pres(lia,lja) )
447  allocate( atmos_w(lia,lja) )
448  allocate( atmos_u(lia,lja) )
449  allocate( atmos_v(lia,lja) )
450  allocate( atmos_dens(lia,lja) )
451  allocate( atmos_qv(lia,lja) )
452  allocate( atmos_pbl(lia,lja) )
453  allocate( atmos_sfc_dens(lia,lja) )
454  allocate( atmos_sfc_pres(lia,lja) )
456  allocate( atmos_cossza(lia,lja) )
457  allocate( atmos_sflx_water(lia,lja) )
458  allocate( atmos_sflx_engi(lia,lja) )
459  atmos_temp(:,:) = undef
460  atmos_pres(:,:) = undef
461  atmos_w(:,:) = undef
462  atmos_u(:,:) = undef
463  atmos_v(:,:) = undef
464  atmos_dens(:,:) = undef
465  atmos_qv(:,:) = undef
466  atmos_pbl(:,:) = undef
467  atmos_sfc_dens(:,:) = undef
468  atmos_sfc_pres(:,:) = undef
469  atmos_sflx_rad_dn(:,:,:,:) = undef
470  atmos_cossza(:,:) = undef
471  atmos_sflx_water(:,:) = undef
472  atmos_sflx_engi(:,:) = undef
473  !$acc enter data create(ATMOS_TEMP,ATMOS_PRES,ATMOS_W,ATMOS_U,ATMOS_V,ATMOS_DENS,ATMOS_QV,ATMOS_PBL,ATMOS_SFC_DENS,ATMOS_SFC_PRES,ATMOS_SFLX_rad_dn,ATMOS_cosSZA,ATMOS_SFLX_water,ATMOS_SFLX_ENGI)
474 
475  !--- read namelist
476  rewind(io_fid_conf)
477  read(io_fid_conf,nml=param_land_vars,iostat=ierr)
478  if( ierr < 0 ) then !--- missing
479  log_info("LAND_vars_setup",*) 'Not found namelist. Default used.'
480  elseif( ierr > 0 ) then !--- fatal error
481  log_error("LAND_vars_setup",*) 'Not appropriate names in namelist PARAM_LAND_VARS. Check!'
482  call prc_abort
483  endif
484  log_nml(param_land_vars)
485 
486  log_newline
487  log_info("LAND_vars_setup",*) 'List of prognostic variables (LAND) '
488  log_info_cont('(1x,A,A24,A,A48,A,A12,A)') &
489  ' |', 'VARNAME ','|', &
490  'DESCRIPTION ', '[', 'UNIT ', ']'
491  do iv = 1, vmax
492  log_info_cont('(1x,A,I3,A,A24,A,A48,A,A12,A)') &
493  'NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
494  enddo
495 
496  log_newline
497  if ( land_restart_in_basename /= '' ) then
498  log_info("LAND_vars_setup",*) 'Restart input? : YES, file = ', trim(land_restart_in_basename)
499  log_info("LAND_vars_setup",*) 'Add timelabel? : ', land_restart_in_postfix_timelabel
500  else
501  log_info("LAND_vars_setup",*) 'Restart input? : NO'
502  endif
503  if ( land_restart_output &
504  .AND. land_restart_out_basename /= '' ) then
505  log_info("LAND_vars_setup",*) 'Restart output? : YES, file = ', trim(land_restart_out_basename)
506  log_info("LAND_vars_setup",*) 'Add timelabel? : ', land_restart_out_postfix_timelabel
507  else
508  log_info("LAND_vars_setup",*) 'Restart output? : NO'
509  land_restart_output = .false.
510  endif
511 
512  ! Read land property table
513  allocate( land_property_table(landuse_pft_nmin:landuse_pft_nmax,land_property_nmax) )
514  land_property_table(:,:) = undef
515 
516  call land_param_read( landuse_pft_nmin, landuse_pft_nmax, land_property_nmax, &
517  land_property_table(:,:) )
518 
519  ! Apply land property to 2D map
521  !$acc enter data create(LAND_PROPERTY)
522 
523  ! tentative, mosaic is off
524  !$omp parallel do collapse(2)
525  do p = 1, land_property_nmax
526  do j = ljs, lje
527  do i = lis, lie
528  land_property(i,j,p) = land_property_table( landuse_index_pft(i,j,1), p )
529  enddo
530  enddo
531  enddo
532 
533  deallocate( land_property_table )
534 
535 #ifdef QUICKDEBUG
536  land_property(:lis-1,:,:) = undef
537  land_property(lie+1:,:,:) = undef
538  land_property(:,:ljs-1,:) = undef
539  land_property(:,lje+1:,:) = undef
540 #endif
541  do p = 1, land_property_nmax
542  call comm_vars8( land_property(:,:,p), p )
543  enddo
544  do p = 1, land_property_nmax
545  call comm_wait ( land_property(:,:,p), p )
546  enddo
547  !$acc update device(LAND_PROPERTY)
548 
549  ! monitor
550  call monitor_reg( 'LND_TEMP', 'land temperature', 'K m3', & ! (in)
551  monit_id(im_temp), & ! (out)
552  dim_type='LXY', is_tendency=.false. ) ! (in)
553  call monitor_reg( 'LND_WATER', 'land water', 'kg', & ! (in)
554  monit_id(im_water), & ! (out)
555  dim_type='LXY', is_tendency=.false. ) ! (in)
556  call monitor_reg( 'LND_ICE', 'land ice', 'kg', & ! (in)
557  monit_id(im_ice), & ! (out)
558  dim_type='LXY', is_tendency=.false. ) ! (in)
559  call monitor_reg( 'LND_MASSFC', 'SFC water flux', 'kg', & ! (in)
560  monit_id(im_sfc), & ! (out)
561  dim_type='XY', is_tendency=.true. ) ! (in)
562  call monitor_reg( 'LND_ROFF', 'runoff water', 'kg', & ! (in)
563  monit_id(im_roff), & ! (out)
564  dim_type='XY', is_tendency=.true. ) ! (in)
565  call monitor_reg( 'LND_MASFLX', 'total mass change', 'kg', & ! (in)
566  monit_id(im_masflx), & ! (out)
567  dim_type='XY', is_tendency=.true. ) ! (in)
568  call monitor_reg( 'LND_ENGI', 'total internal energy', 'J', & ! (in)
569  monit_id(im_engi), & ! (out)
570  dim_type='LXY', is_tendency=.false. ) ! (in)
571  call monitor_reg( 'LND_WTR_ENGI', 'water internal energy', 'J', & ! (in)
572  monit_id(im_w_engi), & ! (out)
573  dim_type='LXY', is_tendency=.false. ) ! (in)
574  call monitor_reg( 'LND_ICE_ENGI', 'ice internal energy', 'J', & ! (in)
575  monit_id(im_i_engi), & ! (out)
576  dim_type='LXY', is_tendency=.false. ) ! (in)
577  call monitor_reg( 'LND_ENGSFC_GH', 'SFC ground heat flux', 'J', & ! (in)
578  monit_id(im_engsfc_gh), & ! (out)
579  dim_type='XY', is_tendency=.true. ) ! (in)
580  call monitor_reg( 'LND_ENGSFC_EI', 'SFC internal energy flux', 'J', & ! (in)
581  monit_id(im_engsfc_ei), & ! (out)
582  dim_type='XY', is_tendency=.true. ) ! (in)
583  call monitor_reg( 'LND_ROFF_EI', 'internal energy of runoff water', 'J', & ! (in)
584  monit_id(im_roff_ei), & ! (out)
585  dim_type='XY', is_tendency=.true. ) ! (in)
586  call monitor_reg( 'LND_ENGFLX', 'total internal energy change', 'J', & ! (in)
587  monit_id(im_engflx), & ! (out)
588  dim_type='XY', is_tendency=.true. ) ! (in)
589 
590  return
591  end subroutine land_vars_setup
592 
593  !-----------------------------------------------------------------------------
595  subroutine land_vars_finalize
596  use scale_landuse, only: &
600  use mod_land_admin, only: &
601  snow_type
602  implicit none
603  !---------------------------------------------------------------------------
604 
605  log_newline
606  log_info("LAND_vars_finalize",*) 'Finalize'
607 
608  select case ( snow_type )
609  case ( 'NONE', 'OFF' )
610  snow_flag = .false.
611  case default
612  snow_flag = .true.
613  end select
614 
615  !$acc exit data delete(LAND_TEMP,LAND_WATER,LAND_ICE,LAND_SFC_TEMP,LAND_SFC_albedo)
616  deallocate( land_temp )
617  deallocate( land_water )
618  deallocate( land_ice )
619  deallocate( land_sfc_temp )
620  deallocate( land_sfc_albedo )
621 
622  if ( snow_flag ) then
623  deallocate( snow_sfc_temp )
624  deallocate( snow_swe )
625  deallocate( snow_depth )
626  deallocate( snow_dzero )
627  deallocate( snow_nosnowsec )
628  end if
629 
630  !$acc exit data delete(LAND_TEMP_t,LAND_WATER_t,LAND_ICE_t)
631  deallocate( land_temp_t )
632  deallocate( land_water_t )
633  deallocate( land_ice_t )
634 
635  !$acc exit data delete(LAND_SFLX_GH,LAND_SFLX_water,LAND_SFLX_ENGI)
636  deallocate( land_sflx_gh )
637  deallocate( land_sflx_water )
638  deallocate( land_sflx_engi )
639 
640  !$acc exit data delete(LAND_RUNOFF,LAND_RUNOFF_ENGI)
641  deallocate( land_runoff )
642  deallocate( land_runoff_engi )
643 
644  !$acc exit data delete(LAND_SFLX_MW,LAND_SFLX_MU,LAND_SFLX_MV,LAND_SFLX_SH,LAND_SFLX_LH,LAND_SFLX_QTRC)
645  deallocate( land_sflx_mw )
646  deallocate( land_sflx_mu )
647  deallocate( land_sflx_mv )
648  deallocate( land_sflx_sh )
649  deallocate( land_sflx_lh )
650  deallocate( land_sflx_qtrc )
651 
652  !$acc exit data delete(LAND_U10,LAND_V10,LAND_T2,LAND_Q2)
653  deallocate( land_u10 )
654  deallocate( land_v10 )
655  deallocate( land_t2 )
656  deallocate( land_q2 )
657 
658  !$acc exit data delete(LAND_Ustar,LAND_Tstar,LAND_Qstar,LAND_Wstar,LAND_RLmo)
659  deallocate( land_ustar )
660  deallocate( land_tstar )
661  deallocate( land_qstar )
662  deallocate( land_wstar )
663  deallocate( land_rlmo )
664  if ( snow_flag ) then
665  !$acc exit data delete(SOIL_Ustar,SOIL_Tstar,SOIL_Qstar,SOIL_Wstar,SOIL_RLmo)
666  deallocate( soil_ustar )
667  deallocate( soil_tstar )
668  deallocate( soil_qstar )
669  deallocate( soil_wstar )
670  deallocate( soil_rlmo )
671  end if
672  if ( snow_flag ) then
673  deallocate( snow_ustar )
674  deallocate( snow_tstar )
675  deallocate( snow_qstar )
676  deallocate( snow_wstar )
677  deallocate( snow_rlmo )
678  end if
679 
680  !$acc exit data delete(ATMOS_TEMP,ATMOS_PRES,ATMOS_W,ATMOS_U,ATMOS_V,ATMOS_DENS,ATMOS_QV,ATMOS_PBL,ATMOS_SFC_DENS,ATMOS_SFC_PRES,ATMOS_SFLX_rad_dn,ATMOS_cosSZA,ATMOS_SFLX_water,ATMOS_SFLX_ENGI)
681  deallocate( atmos_temp )
682  deallocate( atmos_pres )
683  deallocate( atmos_w )
684  deallocate( atmos_u )
685  deallocate( atmos_v )
686  deallocate( atmos_dens )
687  deallocate( atmos_qv )
688  deallocate( atmos_pbl )
689  deallocate( atmos_sfc_dens )
690  deallocate( atmos_sfc_pres )
691  deallocate( atmos_sflx_rad_dn )
692  deallocate( atmos_cossza )
693  deallocate( atmos_sflx_water )
694  deallocate( atmos_sflx_engi )
695 
696  !$acc exit data delete(LAND_PROPERTY)
697  deallocate( land_property )
698 
699  return
700  end subroutine land_vars_finalize
701 
702  !-----------------------------------------------------------------------------
704  subroutine land_vars_restart_open
705  use scale_time, only: &
707  use scale_file_cartesc, only: &
709  file_cartesc_check_coordinates
710  use mod_land_admin, only: &
711  land_do
712  implicit none
713 
714  character(len=19) :: timelabel
715  character(len=H_LONG) :: basename
716  !---------------------------------------------------------------------------
717 
718  call prof_rapstart('LND_Restart', 1)
719 
720  log_newline
721  log_info("LAND_vars_restart_open",*) 'Open restart file (LAND) '
722 
723  if ( land_do .and. land_restart_in_basename /= '' ) then
724 
726  call time_gettimelabel( timelabel )
727  basename = trim(land_restart_in_basename)//'_'//trim(timelabel)
728  else
729  basename = trim(land_restart_in_basename)
730  endif
731 
732  log_info("LAND_vars_restart_open",*) 'basename: ', trim(basename)
733 
734  call file_cartesc_open( basename, restart_fid, aggregate=land_restart_in_aggregate )
735 
736  if ( land_restart_in_check_coordinates ) then
737  call file_cartesc_check_coordinates( restart_fid, land=.true. )
738  end if
739 
740  else
741  log_info("LAND_vars_restart_open",*) 'restart file for land is not specified.'
742  endif
743 
744  call prof_rapend('LND_Restart', 1)
745 
746  return
747  end subroutine land_vars_restart_open
748 
749  !-----------------------------------------------------------------------------
751  subroutine land_vars_restart_read
752  use scale_prc, only: &
753  prc_abort
754  use scale_file, only: &
756  use scale_file_cartesc, only: &
757  file_cartesc_read, &
759  implicit none
760  !---------------------------------------------------------------------------
761 
762  call prof_rapstart('LND_Restart', 1)
763 
764  if ( restart_fid /= -1 ) then
765  log_newline
766  log_info("LAND_vars_restart_read",*) 'Read from restart file (LAND) '
767 
768  call file_cartesc_read( restart_fid, var_name(i_temp), 'LXY', & ! [IN]
769  land_temp(:,:,:) ) ! [OUT]
770  call file_cartesc_read( restart_fid, var_name(i_water), 'LXY', & ! [IN]
771  land_water(:,:,:) ) ! [OUT]
772  call file_cartesc_read( restart_fid, var_name(i_ice), 'LXY', & ! [IN]
773  land_ice(:,:,:), & ! [OUT]
774  allow_missing = .true. ) ! [IN]
775  call file_cartesc_read( restart_fid, var_name(i_sfc_temp), 'XY', & ! [IN]
776  land_sfc_temp(:,:) ) ! [OUT]
777  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_ir_dir), 'XY', & ! [IN]
778  land_sfc_albedo(:,:,i_r_direct ,i_r_ir ) ) ! [OUT]
779  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_ir_dif), 'XY', & ! [IN]
780  land_sfc_albedo(:,:,i_r_diffuse,i_r_ir ) ) ! [OUT]
781  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_nir_dir), 'XY', & ! [IN]
782  land_sfc_albedo(:,:,i_r_direct ,i_r_nir) ) ! [OUT]
783  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_nir_dif), 'XY', & ! [IN]
784  land_sfc_albedo(:,:,i_r_diffuse,i_r_nir) ) ! [OUT]
785  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_vis_dir), 'XY', & ! [IN]
786  land_sfc_albedo(:,:,i_r_direct ,i_r_vis) ) ! [OUT]
787  call file_cartesc_read( restart_fid, var_name(i_sfc_alb_vis_dif), 'XY', & ! [IN]
788  land_sfc_albedo(:,:,i_r_diffuse,i_r_vis) ) ! [OUT]
789 
790  if ( snow_flag ) then
791  call file_cartesc_read( restart_fid, var_name(i_snow_sfc_temp), 'XY', & ! [OUT]
792  snow_sfc_temp(:,:) ) ! [IN]
793  call file_cartesc_read( restart_fid, var_name(i_snow_swe), 'XY', & ! [OUT]
794  snow_swe(:,:) ) ! [IN]
795  call file_cartesc_read( restart_fid, var_name(i_snow_depth), 'XY', & ! [OUT]
796  snow_depth(:,:) ) ! [IN]
797  call file_cartesc_read( restart_fid, var_name(i_snow_dzero), 'XY', & ! [OUT]
798  snow_dzero(:,:) ) ! [IN]
799  call file_cartesc_read( restart_fid, var_name(i_snow_nosnowsec), 'XY', & ! [OUT]
800  snow_nosnowsec(:,:) ) ! [IN]
801  end if
802 
803  if( file_get_aggregate(restart_fid) ) call file_cartesc_flush( restart_fid ) ! commit all pending read requests
804 
805  !$acc update device(LAND_TEMP,LAND_WATER,LAND_ICE,LAND_SFC_TEMP,LAND_SFC_albedo)
806 
807  call land_vars_check( force = .true. )
808  else
809  log_error("LAND_vars_restart_read",*) 'invalid restart file ID for land.'
810  call prc_abort
811  endif
812 
813  call prof_rapend('LND_Restart', 1)
814 
815  return
816  end subroutine land_vars_restart_read
817 
818  !-----------------------------------------------------------------------------
820  subroutine land_vars_history
821  use scale_file_history, only: &
822  file_history_in
823  use scale_atmos_hydrometeor, only: &
824  i_qv
825  implicit none
826 
827  real(rp) :: land_waterds(lkmax,lia,lja)
828  integer :: k, i, j
829  !---------------------------------------------------------------------------
830 
831  call prof_rapstart('LND_History', 1)
832 
833 
834  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) )
835  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) )
836  call file_history_in( land_ice(:,:,:), var_name(i_ice), var_desc(i_ice), var_unit(i_ice), dim_type='LXY', standard_name=var_stdn(i_ice) )
837  !$acc data create(LAND_WATERDS)
838  !$acc kernels
839  do j = ljs, lje
840  do i = lis, lie
841  do k = 1, lkmax
842  land_waterds(k,i,j) = land_water(k,i,j) / land_property(i,j,i_waterlimit)
843  end do
844  end do
845  end do
846  !$acc end kernels
847  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) )
848  !$acc end data
849 
850  call file_history_in( land_sfc_temp(:,:), var_name(i_sfc_temp), &
851  var_desc(i_sfc_temp), var_unit(i_sfc_temp), standard_name=var_stdn(i_sfc_temp) )
852  call file_history_in( land_sfc_albedo(:,:,i_r_direct ,i_r_ir ), var_name(i_sfc_alb_ir_dir), &
853  var_desc(i_sfc_alb_ir_dir), var_unit(i_sfc_alb_ir_dir), standard_name=var_stdn(i_sfc_alb_ir_dir) )
854  call file_history_in( land_sfc_albedo(:,:,i_r_diffuse,i_r_ir ), var_name(i_sfc_alb_ir_dif), &
855  var_desc(i_sfc_alb_ir_dif), var_unit(i_sfc_alb_ir_dif), standard_name=var_stdn(i_sfc_alb_ir_dif) )
856  call file_history_in( land_sfc_albedo(:,:,i_r_direct ,i_r_nir), var_name(i_sfc_alb_nir_dir), &
857  var_desc(i_sfc_alb_nir_dir), var_unit(i_sfc_alb_nir_dir), standard_name=var_stdn(i_sfc_alb_nir_dir) )
858  call file_history_in( land_sfc_albedo(:,:,i_r_diffuse,i_r_nir), var_name(i_sfc_alb_nir_dif), &
859  var_desc(i_sfc_alb_nir_dif), var_unit(i_sfc_alb_nir_dif), standard_name=var_stdn(i_sfc_alb_nir_dif) )
860  call file_history_in( land_sfc_albedo(:,:,i_r_direct ,i_r_vis), var_name(i_sfc_alb_vis_dir), &
861  var_desc(i_sfc_alb_vis_dir), var_unit(i_sfc_alb_vis_dir), standard_name=var_stdn(i_sfc_alb_vis_dir) )
862  call file_history_in( land_sfc_albedo(:,:,i_r_diffuse,i_r_vis), var_name(i_sfc_alb_vis_dif), &
863  var_desc(i_sfc_alb_vis_dif), var_unit(i_sfc_alb_vis_dif), standard_name=var_stdn(i_sfc_alb_vis_dif) )
864  if ( snow_flag ) then
865  ! snow model
866  call file_history_in( snow_sfc_temp(:,:), var_name(i_snow_sfc_temp), &
867  var_desc(i_snow_sfc_temp), var_unit(i_snow_sfc_temp), standard_name=var_stdn(i_snow_sfc_temp) )
868  call file_history_in( snow_swe(:,:), var_name(i_snow_swe), &
869  var_desc(i_snow_swe), var_unit(i_snow_swe), standard_name=var_stdn(i_snow_swe) )
870  call file_history_in( snow_depth(:,:), var_name(i_snow_depth), &
871  var_desc(i_snow_depth), var_unit(i_snow_depth), standard_name=var_stdn(i_snow_depth) )
872  call file_history_in( snow_dzero(:,:), var_name(i_snow_dzero), &
873  var_desc(i_snow_dzero), var_unit(i_snow_dzero), standard_name=var_stdn(i_snow_dzero) )
874  call file_history_in( snow_nosnowsec(:,:), var_name(i_snow_nosnowsec), &
875  var_desc(i_snow_nosnowsec), var_unit(i_snow_nosnowsec), standard_name=var_stdn(i_snow_nosnowsec) )
876  end if
877 
878  call file_history_in( land_sflx_gh(:,:), 'LAND_SFLX_GH', &
879  'land subsurface heat flux (downward)', 'J/m2/s' )
880  call file_history_in( land_sflx_water(:,:), 'LAND_SFLX_water', &
881  'land surface water mass flux (downward)', 'kg/m2/s' )
882  call file_history_in( land_sflx_engi(:,:), 'LAND_SFLX_ENGI', &
883  'land surface internal energy flux (downward)', 'kg/m2/s' )
884 
885  call file_history_in( land_runoff(:,:), 'LAND_RUNOFF', &
886  'runoff water', 'kg/m2/s' )
887  call file_history_in( land_runoff_engi(:,:), 'LAND_RUNOFF_ENGI', &
888  'internal energy of runoff water', 'J/m2/s' )
889 
890  call file_history_in( land_sflx_mw(:,:), 'LAND_SFLX_MW', &
891  'land surface w-momentum flux (upward)', 'kg/m2/s' )
892  call file_history_in( land_sflx_mu(:,:), 'LAND_SFLX_MU', &
893  'land surface u-momentum flux (upward)', 'kg/m2/s' )
894  call file_history_in( land_sflx_mv(:,:), 'LAND_SFLX_MV', &
895  'land surface v-momentum flux (upward)', 'kg/m2/s' )
896  call file_history_in( land_sflx_sh(:,:), 'LAND_SFLX_SH', &
897  'land surface sensible heat flux (upward)', 'J/m2/s' )
898  call file_history_in( land_sflx_lh(:,:), 'LAND_SFLX_LH', &
899  'land surface latent heat flux (upward)', 'J/m2/s' )
900  if ( i_qv > 0 ) &
901  call file_history_in( land_sflx_qtrc(:,:,i_qv), 'LAND_SFLX_evap', &
902  'land surface water vapor flux (upward)', 'kg/m2/s' )
903 
904  call file_history_in( land_u10(:,:), 'LAND_U10', &
905  'land 10m x-wind', 'm/s' )
906  call file_history_in( land_v10(:,:), 'LAND_V10', &
907  'land 10m y-wind', 'm/s' )
908  call file_history_in( land_t2(:,:), 'LAND_T2', &
909  'land 2m temperature', 'K' )
910  call file_history_in( land_q2(:,:), 'LAND_Q2', &
911  'land 2m specific humidity', 'kg/kg' )
912 
913  call file_history_in( land_ustar(:,:), 'LAND_Ustar', &
914  'land friction velocity', 'm/s' )
915  call file_history_in( land_tstar(:,:), 'LAND_Tstar', &
916  'land temperature scale', 'K' )
917  call file_history_in( land_qstar(:,:), 'LAND_Qstar', &
918  'land moisture scale', 'kg/kg' )
919  call file_history_in( land_wstar(:,:), 'LAND_Wstar', &
920  'land convective velocity scale', 'm/s' )
921  call file_history_in( land_rlmo(:,:), 'LAND_RLmo', &
922  'land inversed Obukhov length', '1/m' )
923  if ( snow_flag ) then
924  ! soil
925  call file_history_in( soil_ustar(:,:), 'SOIL_Ustar', &
926  'soil friction velocity', 'm/s' )
927  call file_history_in( soil_tstar(:,:), 'SOIL_Tstar', &
928  'soil temperature scale', 'K' )
929  call file_history_in( soil_qstar(:,:), 'SOIL_Qstar', &
930  'soil moisture scale', 'kg/kg' )
931  call file_history_in( soil_wstar(:,:), 'SOIL_Wstar', &
932  'soil convective velocity scale', 'm/s' )
933  call file_history_in( soil_rlmo(:,:), 'SOIL_RLmo', &
934  'soil inversed Obukhov length', '1/m' )
935  ! snow pack
936  call file_history_in( snow_ustar(:,:), 'SNOW_Ustar', &
937  'snow friction velocity', 'm/s' )
938  call file_history_in( snow_tstar(:,:), 'SNOW_Tstar', &
939  'snow temperature scale', 'K' )
940  call file_history_in( snow_qstar(:,:), 'SNOW_Qstar', &
941  'snow moisture scale', 'kg/kg' )
942  call file_history_in( snow_wstar(:,:), 'SNOW_Wstar', &
943  'snow convective velocity scale', 'm/s' )
944  call file_history_in( snow_rlmo(:,:), 'SNOW_RLmo', &
945  'snow inversed Obukhov length', '1/m' )
946  end if
947 
948  call prof_rapend ('LND_History', 1)
949 
950  return
951  end subroutine land_vars_history
952 
953  !-----------------------------------------------------------------------------
955  subroutine land_vars_monitor
956  use scale_const, only: &
957  dwatr => const_dwatr, &
958  dice => const_dice
959  use scale_atmos_hydrometeor, only: &
960  cv_water, &
961  cv_ice, &
962  lhf
963  use scale_monitor, only: &
964  monitor_put
965  implicit none
966 
967  real(rp) :: work3d(lka,lia,lja)
968  real(rp) :: work2d(lia,lja)
969 
970  integer :: k, i, j
971  !---------------------------------------------------------------------------
972 
973  !$acc data create(WORK3D,WORK2D)
974 
975  call monitor_put( monit_id(im_temp), land_temp(:,:,:) )
976  if ( monit_id(im_water) > 0 ) then
977  !$omp parallel do
978  !$acc kernels
979  do j = ljs, lje
980  do i = lis, lie
981  do k = lks, lke
982  work3d(k,i,j) = land_water(k,i,j) * dwatr
983  end do
984  end do
985  end do
986  !$acc end kernels
987  call monitor_put( monit_id(im_water), work3d(:,:,:) )
988  end if
989  if ( monit_id(im_ice) > 0 ) then
990  !$omp parallel do
991  !$acc kernels
992  do j = ljs, lje
993  do i = lis, lie
994  do k = lks, lke
995  work3d(k,i,j) = land_ice(k,i,j) * dice
996  end do
997  end do
998  end do
999  !$acc end kernels
1000  call monitor_put( monit_id(im_ice), work3d(:,:,:) )
1001  end if
1002 
1003 
1004  ! mass budget
1005  call monitor_put( monit_id(im_sfc), land_sflx_water(:,:) )
1006  call monitor_put( monit_id(im_roff), land_runoff(:,:) )
1007  if ( monit_id(im_masflx) > 0 ) then
1008  !$omp parallel do
1009  !$acc kernels
1010  do j = ljs, lje
1011  do i = lis, lie
1012  work2d(i,j) = land_sflx_water(i,j) - land_runoff(i,j)
1013  end do
1014  end do
1015  !$acc end kernels
1016  call monitor_put( monit_id(im_masflx), work2d(:,:) )
1017  end if
1018 
1019  ! energy budget
1020  if ( monit_id(im_engi) > 0 ) then
1021  !$omp parallel do
1022  !$acc kernels
1023  do j = ljs, lje
1024  do i = lis, lie
1025  do k = lks, lke
1026  work3d(k,i,j) = ( land_property(i,j,i_heatcapacity) * ( 1.0_rp - land_property(i,j,i_waterlimit) ) & ! soil particles
1027  + cv_water * dwatr * land_water(k,i,j) & ! land water
1028  + cv_ice * dice * land_ice(k,i,j) & ! land ice
1029  ) * land_temp(k,i,j) &
1030  - lhf * dice * land_ice(k,i,j)
1031  end do
1032  end do
1033  end do
1034  !$acc end kernels
1035  call monitor_put( monit_id(im_engi), work3d(:,:,:) )
1036  end if
1037  if ( monit_id(im_w_engi) > 0 ) then
1038  !$omp parallel do
1039  !$acc kernels
1040  do j = ljs, lje
1041  do i = lis, lie
1042  do k = lks, lke
1043  work3d(k,i,j) = cv_water * dwatr * land_water(k,i,j) * land_temp(k,i,j)
1044  end do
1045  end do
1046  end do
1047  !$acc end kernels
1048  call monitor_put( monit_id(im_w_engi), work3d(:,:,:) )
1049  end if
1050  if ( monit_id(im_i_engi) > 0 ) then
1051  !$omp parallel do
1052  !$acc kernels
1053  do j = ljs, lje
1054  do i = lis, lie
1055  do k = lks, lke
1056  work3d(k,i,j) = ( cv_ice * land_temp(k,i,j) - lhf ) * dice * land_ice(k,i,j)
1057  end do
1058  end do
1059  end do
1060  !$acc end kernels
1061  call monitor_put( monit_id(im_i_engi), work3d(:,:,:) )
1062  end if
1063 
1064 
1065  call monitor_put( monit_id(im_engsfc_gh), land_sflx_gh(:,:) )
1066  call monitor_put( monit_id(im_engsfc_ei), land_sflx_engi(:,:) )
1067  call monitor_put( monit_id(im_roff_ei), land_runoff_engi(:,:) )
1068  if ( monit_id(im_engflx) > 0 ) then
1069  !$omp parallel do
1070  !$acc kernels
1071  do j = ljs, lje
1072  do i = lis, lie
1073  work2d(i,j) = land_sflx_gh(i,j) + land_sflx_engi(i,j) &
1074  - land_runoff_engi(i,j)
1075  end do
1076  end do
1077  !$acc end kernels
1078  call monitor_put( monit_id(im_engflx), work2d(:,:) )
1079  end if
1080 
1081  !$acc end data
1082 
1083  return
1084  end subroutine land_vars_monitor
1085 
1086  !-----------------------------------------------------------------------------
1088  subroutine land_vars_check( force )
1089  use scale_statistics, only: &
1091  statistics_total
1092  use scale_land_grid_cartesc_real, only: &
1097  use scale_landuse, only: &
1099  implicit none
1100  logical, intent(in), optional :: force
1101  logical :: check
1102  !---------------------------------------------------------------------------
1103 
1104  if ( present(force) ) then
1105  check = force
1106  else
1107  check = land_vars_checkrange
1108  end if
1109 
1110  if ( check ) then
1111  call valcheck( lka, lks, lke, lia, lis, lie, lja, ljs, lje, &
1112  land_temp(:,:,:), 0.0_rp, 1000.0_rp, &
1113  var_name(i_temp), __file__, __line__, &
1114  mask = landuse_exists_land(:,:) )
1115  call valcheck( lka, lks, lke, lia, lis, lie, lja, ljs, lje, &
1116  land_water(:,:,:), 0.0_rp, 1.0_rp, &
1117  var_name(i_water), __file__, __line__, &
1118  mask = landuse_exists_land(:,:) )
1119  call valcheck( lka, lks, lke, lia, lis, lie, lja, ljs, lje, &
1120  land_ice(:,:,:), 0.0_rp, 1.0_rp, &
1121  var_name(i_ice), __file__, __line__, &
1122  mask = landuse_exists_land(:,:) )
1123  call valcheck( lia, lis, lie, lja, ljs, lje, &
1124  land_sfc_temp(:,:), 0.0_rp, 1000.0_rp, &
1125  var_name(i_sfc_temp), __file__, __line__, &
1126  mask = landuse_exists_land(:,:) )
1127  call valcheck( lia, lis, lie, lja, ljs, lje, &
1128  land_sfc_albedo(:,:,i_r_direct ,i_r_ir ), 0.0_rp, 2.0_rp, &
1129  var_name(i_sfc_alb_ir_dir ), __file__, __line__, &
1130  mask = landuse_exists_land(:,:) )
1131  call valcheck( lia, lis, lie, lja, ljs, lje, &
1132  land_sfc_albedo(:,:,i_r_diffuse,i_r_ir ), 0.0_rp, 2.0_rp, &
1133  var_name(i_sfc_alb_ir_dif ), __file__, __line__, &
1134  mask = landuse_exists_land(:,:) )
1135  call valcheck( lia, lis, lie, lja, ljs, lje, &
1136  land_sfc_albedo(:,:,i_r_direct ,i_r_nir), 0.0_rp, 2.0_rp, &
1137  var_name(i_sfc_alb_nir_dir), __file__, __line__, &
1138  mask = landuse_exists_land(:,:) )
1139  call valcheck( lia, lis, lie, lja, ljs, lje, &
1140  land_sfc_albedo(:,:,i_r_diffuse,i_r_nir), 0.0_rp, 2.0_rp, &
1141  var_name(i_sfc_alb_nir_dif), __file__, __line__, &
1142  mask = landuse_exists_land(:,:) )
1143  call valcheck( lia, lis, lie, lja, ljs, lje, &
1144  land_sfc_albedo(:,:,i_r_direct ,i_r_vis), 0.0_rp, 2.0_rp, &
1145  var_name(i_sfc_alb_vis_dir), __file__, __line__, &
1146  mask = landuse_exists_land(:,:) )
1147  call valcheck( lia, lis, lie, lja, ljs, lje, &
1148  land_sfc_albedo(:,:,i_r_diffuse,i_r_vis), 0.0_rp, 2.0_rp, &
1149  var_name(i_sfc_alb_vis_dif), __file__, __line__, &
1150  mask = landuse_exists_land(:,:) )
1151 
1152  if ( snow_flag ) then
1153  call valcheck( lia, lis, lie, lja, ljs, lje, &
1154  snow_sfc_temp(:,:), 0.0_rp, 1000.0_rp, &
1155  var_name(i_snow_sfc_temp), __file__, __line__, &
1156  mask = landuse_exists_land(:,:) )
1157  call valcheck( lia, lis, lie, lja, ljs, lje, &
1158  snow_swe(:,:), 0.0_rp, 1000.0_rp, &
1159  var_name(i_snow_swe), __file__, __line__, &
1160  mask = landuse_exists_land(:,:) )
1161  call valcheck( lia, lis, lie, lja, ljs, lje, &
1162  snow_depth(:,:), 0.0_rp, 1000.0_rp, &
1163  var_name(i_snow_depth), __file__, __line__, &
1164  mask = landuse_exists_land(:,:) )
1165 
1166  call valcheck( lia, lis, lie, lja, ljs, lje, &
1167  snow_dzero(:,:), 0.0_rp, 1000.0_rp, &
1168  var_name(i_snow_dzero), __file__, __line__, &
1169  mask = landuse_exists_land(:,:) )
1170  endif
1171 
1172  end if
1173 
1174  if ( present(force) ) then
1175  check = force
1176  else
1178  end if
1179 
1180  if ( check ) then
1181 
1182  ! 3D
1183  call statistics_total( lka, lks, lke, lia, lis, lie, lja, ljs, lje, &
1184  land_temp(:,:,:), var_name(i_temp), & ! (in)
1185  land_grid_cartesc_real_vol(:,:,:), & ! (in)
1187  call statistics_total( lka, lks, lke, lia, lis, lie, lja, ljs, lje, &
1188  land_water(:,:,:), var_name(i_water), & ! (in)
1189  land_grid_cartesc_real_vol(:,:,:), & ! (in)
1191  call statistics_total( lka, lks, lke, lia, lis, lie, lja, ljs, lje, &
1192  land_ice(:,:,:), var_name(i_ice), & ! (in)
1193  land_grid_cartesc_real_vol(:,:,:), & ! (in)
1195 
1196  ! 2D
1197  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
1198  land_sfc_temp(:,:), var_name(i_sfc_temp), & ! [IN]
1199  land_grid_cartesc_real_area(:,:), & ! [IN]
1201  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
1202  land_sfc_albedo(:,:,i_r_direct ,i_r_ir ), var_name(i_sfc_alb_ir_dir), & ! [IN]
1203  land_grid_cartesc_real_area(:,:), & ! [IN]
1205  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
1206  land_sfc_albedo(:,:,i_r_diffuse,i_r_ir ), var_name(i_sfc_alb_ir_dif), & ! [IN]
1207  land_grid_cartesc_real_area(:,:), & ! [IN]
1209  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
1210  land_sfc_albedo(:,:,i_r_direct ,i_r_nir), var_name(i_sfc_alb_nir_dir), & ! [IN]
1211  land_grid_cartesc_real_area(:,:), & ! [IN]
1213  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
1214  land_sfc_albedo(:,:,i_r_diffuse,i_r_nir), var_name(i_sfc_alb_nir_dif), & ! [IN]
1215  land_grid_cartesc_real_area(:,:), & ! [IN]
1217  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
1218  land_sfc_albedo(:,:,i_r_direct ,i_r_vis), var_name(i_sfc_alb_vis_dir), & ! [IN]
1219  land_grid_cartesc_real_area(:,:), & ! [IN]
1221  call statistics_total( lia, lis, lie, lja, ljs, lje, & ! [IN]
1222  land_sfc_albedo(:,:,i_r_diffuse,i_r_vis), var_name(i_sfc_alb_vis_dif), & ! [IN]
1223  land_grid_cartesc_real_area(:,:), & ! [IN]
1225 
1226  if ( snow_flag ) then
1227  call statistics_total( lia, lis, lie, lja, ljs, lje, &
1228  snow_sfc_temp(:,:), var_name(i_snow_sfc_temp), & ! (in)
1229  land_grid_cartesc_real_area(:,:), & ! (in)
1231  call statistics_total( lia, lis, lie, lja, ljs, lje, &
1232  snow_swe(:,:), var_name(i_snow_swe), & ! (in)
1233  land_grid_cartesc_real_area(:,:), & ! (in)
1235  call statistics_total( lia, lis, lie, lja, ljs, lje, &
1236  snow_depth(:,:), var_name(i_snow_depth), & ! (in)
1237  land_grid_cartesc_real_area(:,:), & ! (in)
1239  call statistics_total( lia, lis, lie, lja, ljs, lje, &
1240  snow_dzero(:,:), var_name(i_snow_dzero), & ! (in)
1241  land_grid_cartesc_real_area(:,:), & ! (in)
1243  call statistics_total( lia, lis, lie, lja, ljs, lje, &
1244  snow_nosnowsec(:,:), var_name(i_snow_nosnowsec), & ! (in)
1245  land_grid_cartesc_real_area(:,:), & ! (in)
1247  end if
1248 
1249  endif
1250 
1251  return
1252  end subroutine land_vars_check
1253 
1254  !-----------------------------------------------------------------------------
1256  subroutine land_param_read( &
1257  LANDUSE_PFT_nmin, &
1258  LANDUSE_PFT_nmax, &
1259  LAND_PROPERTY_nmax, &
1260  LAND_PROPERTY_table )
1261  use scale_prc, only: &
1262  prc_abort
1263  implicit none
1264  integer, intent(in) :: landuse_pft_nmin
1265  integer, intent(in) :: landuse_pft_nmax
1266  integer, intent(in) :: land_property_nmax
1267  real(rp), intent(out) :: land_property_table(landuse_pft_nmin:landuse_pft_nmax,land_property_nmax)
1268 
1269  integer :: index
1270  character(len=H_MID) :: description
1271  real(rp) :: strgmax ! Water Limit [0-1]
1272  real(rp) :: strgcrt ! Water Critical [0-1]
1273  real(rp) :: rstoma ! Stomata Resistance [0-1]
1274  real(rp) :: tcs ! Thermal Conductivity [W m-1 K-1]
1275  real(rp) :: hcs ! Dencity x Heat Capacity [J m-3 K-1]
1276  real(rp) :: dfw ! Water Diffusivity [m2 s-1]
1277  real(rp) :: alblw ! Albedo Long Wave [0-1]
1278  real(rp) :: albsw ! Albedo Short Wave [0-1]
1279  real(rp) :: z0m ! Z0 for momentum [m]
1280  real(rp) :: z0h ! Z0 for heat [m]
1281  real(rp) :: z0e ! Z0 for vapor [m]
1282 
1283  namelist / param_land_property / &
1285 
1286  namelist / param_land_data / &
1287  index, &
1288  description, &
1289  strgmax, &
1290  strgcrt, &
1291  rstoma, &
1292  tcs, &
1293  hcs, &
1294  dfw, &
1295  alblw, &
1296  albsw, &
1297  z0m, &
1298  z0h, &
1299  z0e
1300 
1301  integer :: n
1302  integer :: ierr
1303 
1304  character(len=H_LONG) :: fname
1305 
1306  integer :: io_fid_land_property
1307  !---------------------------------------------------------------------------
1308 
1309  !--- read namelist
1310  rewind(io_fid_conf)
1311  read(io_fid_conf,nml=param_land_property,iostat=ierr)
1312  if( ierr < 0 ) then !--- missing
1313  log_info("LAND_param_read",*) 'Not found namelist. Default used.'
1314  elseif( ierr > 0 ) then !--- fatal error
1315  log_error("LAND_param_read",*) 'Not appropriate names in namelist PARAM_LAND_PROPERTY. Check!'
1316  call prc_abort
1317  endif
1318  log_nml(param_land_property)
1319 
1320  if( land_property_in_filename /= '' ) then
1321  !--- Open land parameter file
1322  io_fid_land_property = io_get_available_fid()
1324  open( io_fid_land_property, &
1325  file = fname, &
1326  form = 'formatted', &
1327  status = 'old', &
1328  iostat = ierr )
1329 
1330  if ( ierr /= 0 ) then
1331  log_error("LAND_param_read",*) 'Failed to open land parameter file! :', trim(fname)
1332  call prc_abort
1333  else
1334  log_newline
1335  log_info("LAND_param_read",*) 'Properties for each plant functional type (PFT)'
1336  log_info_cont('(12(1x,A))') ' PFT DESCRIPTION', &
1337  'Max Stg', &
1338  'CRT Stg', &
1339  'Stm.Res', &
1340  'T condu', &
1341  'H capac', &
1342  'DFC Wat', &
1343  'LW ALB', &
1344  'SW ALB', &
1345  ' Z0(m)', &
1346  ' Z0(h)', &
1347  ' Z0(e)'
1348 
1349  !--- read namelist
1350  rewind(io_fid_land_property)
1351 
1352  do n = landuse_pft_nmin, landuse_pft_nmax
1353  ! default value
1354  albsw = 0.2_rp
1355  strgmax = 0.2_rp
1356  strgcrt = 0.1_rp
1357  rstoma = 50.0_rp
1358  tcs = 1.0_rp
1359  hcs = 2.e+6_rp
1360  dfw = 1.e-6_rp
1361  alblw = 0.04_rp
1362  albsw = 0.22_rp
1363  z0m = 0.1_rp
1364  z0h = -1.0_rp
1365  z0e = -1.0_rp
1366 
1367  read(io_fid_land_property,nml=param_land_data,iostat=ierr)
1368  if ( ierr < 0 ) then !--- no more data
1369  exit
1370  elseif( ierr > 0 ) then !--- fatal error
1371  log_error("LAND_param_read",*) 'Not appropriate names in namelist PARAM_LAND_DATA. Check!'
1372  call prc_abort
1373  endif
1374 
1375  if( z0h < 0.0_rp ) then
1376  z0h = z0m / 7.4_rp ! defined by Garratt and Francey (1978)
1377  endif
1378  if( z0e < 0.0_rp ) then
1379  z0e = z0m / 7.4_rp ! defined by Garratt and Francey (1978)
1380  endif
1381 
1382  land_property_table(index,i_waterlimit ) = strgmax
1383  land_property_table(index,i_watercritical) = strgcrt
1384  land_property_table(index,i_stomataresist) = rstoma
1385  land_property_table(index,i_thermalcond ) = tcs
1386  land_property_table(index,i_heatcapacity ) = hcs
1387  land_property_table(index,i_waterdiff ) = dfw
1388  land_property_table(index,i_alblw ) = alblw
1389  land_property_table(index,i_albsw ) = albsw
1390  land_property_table(index,i_z0m ) = z0m
1391  land_property_table(index,i_z0h ) = z0h
1392  land_property_table(index,i_z0e ) = z0e
1393 
1394  log_info_cont('(1x,A4,I4.3,1x,A32,4(1x,F7.3),2(1x,ES7.1),5(1x,F6.3))') &
1395  'IDX=', index, &
1396  trim(description), &
1397  strgmax, &
1398  strgcrt, &
1399  rstoma, &
1400  tcs, &
1401  hcs, &
1402  dfw, &
1403  alblw, &
1404  albsw, &
1405  z0m, &
1406  z0h, &
1407  z0e
1408  enddo
1409 
1410  end if
1411 
1412  close( io_fid_land_property )
1413 
1414  endif
1415 
1416  return
1417  end subroutine land_param_read
1418 
1419  !-----------------------------------------------------------------------------
1421  function convert_ws2vwc( WS, critical ) result( VWC )
1422  implicit none
1423 
1424  real(rp), intent(in) :: ws(lia,lja) ! water saturation [fraction]
1425  logical, intent(in) :: critical ! is I_WaterCritical used?
1426 
1427  real(rp) :: vwc(lia,lja) ! volumetric water content [m3/m3]
1428 
1429  ! work
1430  integer :: i, j, num
1431  !---------------------------------------------------------------------------
1432 
1433  if( critical ) then
1434  num = i_watercritical
1435  else
1436  num = i_waterlimit
1437  end if
1438 
1439  !$acc kernels
1440  do j = ljs, lje
1441  do i = lis, lie
1442  vwc(i,j) = max( min( ws(i,j)*land_property(i,j,num), land_property(i,j,num) ), 0.0_rp )
1443  end do
1444  end do
1445  !$acc end kernels
1446 
1447  return
1448  end function convert_ws2vwc
1449 
1450  !-----------------------------------------------------------------------------
1452  subroutine land_vars_restart_create
1453  use scale_time, only: &
1455  use scale_file_cartesc, only: &
1457  use mod_land_admin, only: &
1458  land_do
1459  implicit none
1460 
1461  character(len=19) :: timelabel
1462  character(len=H_LONG) :: basename
1463  !---------------------------------------------------------------------------
1464 
1465  call prof_rapstart('LND_Restart', 1)
1466 
1467  if ( land_do .and. land_restart_out_basename /= '' ) then
1468 
1469  log_newline
1470  log_info("LAND_vars_restart_create",*) 'Create restart file (LAND) '
1471 
1473  call time_gettimelabel( timelabel )
1474  basename = trim(land_restart_out_basename)//'_'//trim(timelabel)
1475  else
1476  basename = trim(land_restart_out_basename)
1477  endif
1478 
1479  log_info("LAND_vars_restart_create",*) 'basename: ', trim(basename)
1480 
1481  call file_cartesc_create( &
1482  basename, land_restart_out_title, land_restart_out_dtype, & ! [IN]
1483  restart_fid, & ! [OUT]
1484  aggregate=land_restart_out_aggregate ) ! [IN]
1485 
1486  endif
1487 
1488  call prof_rapend('LND_Restart', 1)
1489 
1490  return
1491  end subroutine land_vars_restart_create
1492 
1493  !-----------------------------------------------------------------------------
1495  subroutine land_vars_restart_enddef
1496  use scale_file_cartesc, only: &
1498  implicit none
1499 
1500  call prof_rapstart('LND_Restart', 1)
1501 
1502  if ( restart_fid /= -1 ) then
1503  call file_cartesc_enddef( restart_fid ) ! [IN]
1504  endif
1505 
1506  call prof_rapend('LND_Restart', 1)
1507 
1508  return
1509  end subroutine land_vars_restart_enddef
1510 
1511  !-----------------------------------------------------------------------------
1513  subroutine land_vars_restart_close
1514  use scale_file_cartesc, only: &
1516  implicit none
1517  !---------------------------------------------------------------------------
1518 
1519  call prof_rapstart('LND_Restart', 1)
1520 
1521  if ( restart_fid /= -1 ) then
1522  log_newline
1523  log_info("LAND_vars_restart_close",*) 'Close restart file (LAND) '
1524 
1525  call file_cartesc_close( restart_fid ) ! [IN]
1526 
1527  restart_fid = -1
1528  endif
1529 
1530  call prof_rapend('LND_Restart', 1)
1531 
1532  return
1533  end subroutine land_vars_restart_close
1534 
1535  !-----------------------------------------------------------------------------
1537  subroutine land_vars_restart_def_var
1538  use scale_file_cartesc, only: &
1540  implicit none
1541  integer :: i
1542  !---------------------------------------------------------------------------
1543 
1544  call prof_rapstart('LND_Restart', 1)
1545 
1546  if ( restart_fid /= -1 ) then
1547 
1548  do i = i_temp, i_ice
1549  call file_cartesc_def_var( restart_fid, & ! [IN]
1550  var_name(i), var_desc(i), var_unit(i), & ! [IN]
1551  'LXY', land_restart_out_dtype, & ! [IN]
1552  var_id(i), & ! [OUT]
1553  standard_name=var_stdn(i) ) ! [IN]
1554  end do
1555  do i = i_sfc_temp, i_sfc_alb_vis_dif
1556  call file_cartesc_def_var( restart_fid, & ! [IN]
1557  var_name(i), var_desc(i), var_unit(i), & ! [IN]
1558  'XY', land_restart_out_dtype, & ! [IN]
1559  var_id(i), & ! [OUT]
1560  standard_name=var_stdn(i) ) ! [IN]
1561  end do
1562 
1563  if ( snow_flag ) then
1564  do i = i_snow_sfc_temp, i_snow_nosnowsec
1565  call file_cartesc_def_var( restart_fid, & ! [IN]
1566  var_name(i), var_desc(i), var_unit(i), & ! [IN]
1567  'XY', land_restart_out_dtype, & ! [IN]
1568  var_id(i), & ! [OUT]
1569  standard_name=var_stdn(i) ) ! [IN]
1570  end do
1571  end if
1572 
1573  endif
1574 
1575  call prof_rapend('LND_Restart', 1)
1576 
1577  return
1578  end subroutine land_vars_restart_def_var
1579 
1580  !-----------------------------------------------------------------------------
1582  subroutine land_vars_restart_write
1583  use scale_file_cartesc, only: &
1584  file_cartesc_write_var
1585  implicit none
1586  !---------------------------------------------------------------------------
1587 
1588  call prof_rapstart('LND_Restart', 1)
1589 
1590  if ( restart_fid /= -1 ) then
1591 
1592  call land_vars_check( force = .true. )
1593 
1594  call file_cartesc_write_var( restart_fid, var_id(i_temp), & ! [IN]
1595  land_temp(:,:,:), & ! [IN]
1596  var_name(i_temp), 'LXY', fill_halo=.true. ) ! [IN]
1597  call file_cartesc_write_var( restart_fid, var_id(i_water), & ! [IN]
1598  land_water(:,:,:), & ! [IN]
1599  var_name(i_water), 'LXY', fill_halo=.true. ) ! [IN]
1600  call file_cartesc_write_var( restart_fid, var_id(i_ice), & ! [IN]
1601  land_ice(:,:,:), & ! [IN]
1602  var_name(i_ice), 'LXY', fill_halo=.true. ) ! [IN]
1603  call file_cartesc_write_var( restart_fid, var_id(i_sfc_temp), & ! [IN]
1604  land_sfc_temp(:,:), & ! [IN]
1605  var_name(i_sfc_temp), 'XY', fill_halo=.true. ) ! [IN]
1606  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_ir_dir), & ! [IN]
1607  land_sfc_albedo(:,:,i_r_direct ,i_r_ir ), & ! [IN]
1608  var_name(i_sfc_alb_ir_dir), 'XY', fill_halo=.true. ) ! [IN]
1609  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_ir_dif), & ! [IN]
1610  land_sfc_albedo(:,:,i_r_diffuse,i_r_ir ), & ! [IN]
1611  var_name(i_sfc_alb_ir_dif), 'XY', fill_halo=.true. ) ! [IN]
1612  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_nir_dir), & ! [IN]
1613  land_sfc_albedo(:,:,i_r_direct ,i_r_nir), & ! [IN]
1614  var_name(i_sfc_alb_nir_dir), 'XY', fill_halo=.true. ) ! [IN]
1615  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_nir_dif), & ! [IN]
1616  land_sfc_albedo(:,:,i_r_diffuse,i_r_nir), & ! [IN]
1617  var_name(i_sfc_alb_nir_dif), 'XY', fill_halo=.true. ) ! [IN]
1618  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_vis_dir), & ! [IN]
1619  land_sfc_albedo(:,:,i_r_direct ,i_r_vis), & ! [IN]
1620  var_name(i_sfc_alb_vis_dir), 'XY', fill_halo=.true. ) ! [IN]
1621  call file_cartesc_write_var( restart_fid, var_id(i_sfc_alb_vis_dif), & ! [IN]
1622  land_sfc_albedo(:,:,i_r_diffuse,i_r_vis), & ! [IN]
1623  var_name(i_sfc_alb_vis_dif), 'XY', fill_halo=.true. ) ! [IN]
1624 
1625  if ( snow_flag ) then
1626  call file_cartesc_write_var( restart_fid, var_id(i_snow_sfc_temp), snow_sfc_temp(:,:), &
1627  var_name(i_snow_sfc_temp), 'XY', fill_halo=.true. )
1628  call file_cartesc_write_var( restart_fid, var_id(i_snow_swe), snow_swe(:,:), &
1629  var_name(i_snow_swe), 'XY', fill_halo=.true. )
1630  call file_cartesc_write_var( restart_fid, var_id(i_snow_depth), snow_depth(:,:), &
1631  var_name(i_snow_depth), 'XY', fill_halo=.true. )
1632  call file_cartesc_write_var( restart_fid, var_id(i_snow_dzero), snow_dzero(:,:), &
1633  var_name(i_snow_dzero), 'XY', fill_halo=.true. )
1634  call file_cartesc_write_var( restart_fid, var_id(i_snow_nosnowsec), snow_nosnowsec(:,:), &
1635  var_name(i_snow_nosnowsec), 'XY', fill_halo=.true. )
1636  end if
1637 
1638  endif
1639 
1640  call prof_rapend('LND_Restart', 1)
1641 
1642  return
1643  end subroutine land_vars_restart_write
1644 
1645 end module mod_land_vars
mod_land_vars::land_restart_out_basename
character(len=h_long), public land_restart_out_basename
Basename of the output file.
Definition: mod_land_vars.F90:55
scale_cpl_sfc_index::n_rad_dir
integer, parameter, public n_rad_dir
Definition: scale_cpl_sfc_index.F90:36
scale_statistics
module Statistics
Definition: scale_statistics.F90:11
mod_land_vars::land_temp
real(rp), dimension(:,:,:), allocatable, public land_temp
temperature of each soil layer [K]
Definition: mod_land_vars.F90:62
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
scale_cpl_sfc_index::i_r_direct
integer, parameter, public i_r_direct
Definition: scale_cpl_sfc_index.F90:37
mod_land_vars::atmos_sfc_pres
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
Definition: mod_land_vars.F90:126
mod_land_vars::atmos_temp
real(rp), dimension(:,:), allocatable, public atmos_temp
Definition: mod_land_vars.F90:117
mod_land_vars::snow_sfc_temp
real(rp), dimension(:,:), allocatable, public snow_sfc_temp
snow surface temperature [K]
Definition: mod_land_vars.F90:69
scale_land_grid_cartesc_index::ljs
integer, public ljs
Definition: scale_land_grid_cartesC_index.F90:46
mod_land_vars::atmos_qv
real(rp), dimension(:,:), allocatable, public atmos_qv
Definition: mod_land_vars.F90:123
scale_tracer::qa
integer, public qa
Definition: scale_tracer.F90:35
mod_land_vars::i_stomataresist
integer, parameter, public i_stomataresist
Definition: mod_land_vars.F90:143
scale_land_grid_cartesc_index::lia
integer, public lia
Definition: scale_land_grid_cartesC_index.F90:41
mod_land_vars::land_sflx_mu
real(rp), dimension(:,:), allocatable, public land_sflx_mu
land surface u-momentum flux [kg/m2/s]
Definition: mod_land_vars.F90:87
scale_land_grid_cartesc_index::lja
integer, public lja
Definition: scale_land_grid_cartesC_index.F90:45
scale_file_cartesc::file_cartesc_enddef
subroutine, public file_cartesc_enddef(fid)
Exit netCDF file define mode.
Definition: scale_file_cartesC.F90:964
mod_land_vars::land_tstar
real(rp), dimension(:,:), allocatable, target, public land_tstar
temperature scale [K]
Definition: mod_land_vars.F90:97
scale_file_cartesc::file_cartesc_def_var
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.
Definition: scale_file_cartesC.F90:3360
mod_land_vars::land_sfc_albedo
real(rp), dimension(:,:,:,:), allocatable, public land_sfc_albedo
land surface albedo (direct/diffuse,IR/near-IR/VIS) (0-1)
Definition: mod_land_vars.F90:66
scale_cpl_sfc_index::i_r_diffuse
integer, parameter, public i_r_diffuse
Definition: scale_cpl_sfc_index.F90:38
mod_land_vars::land_sflx_engi
real(rp), dimension(:,:), allocatable, public land_sflx_engi
land surface internal energy flux [J/m2/s]
Definition: mod_land_vars.F90:83
mod_land_vars::land_vars_history
subroutine, public land_vars_history
History output set for land variables.
Definition: mod_land_vars.F90:821
scale_precision
module PRECISION
Definition: scale_precision.F90:14
mod_land_vars::i_alblw
integer, parameter, public i_alblw
Definition: mod_land_vars.F90:147
mod_land_vars::i_albsw
integer, parameter, public i_albsw
Definition: mod_land_vars.F90:148
mod_land_vars::atmos_w
real(rp), dimension(:,:), allocatable, public atmos_w
Definition: mod_land_vars.F90:119
mod_land_vars::soil_ustar
real(rp), dimension(:,:), pointer, public soil_ustar
Definition: mod_land_vars.F90:101
mod_land_vars::land_water_t
real(rp), dimension(:,:,:), allocatable, public land_water_t
tendency of LAND_WATER
Definition: mod_land_vars.F90:77
scale_land_grid_cartesc_index::lkmax
integer, public lkmax
Definition: scale_land_grid_cartesC_index.F90:32
mod_land_vars::land_water
real(rp), dimension(:,:,:), allocatable, public land_water
moisture of each soil layer [m3/m3]
Definition: mod_land_vars.F90:63
mod_land_vars::land_runoff
real(rp), dimension(:,:), allocatable, public land_runoff
runoff of the land water [kg/m2/s]
Definition: mod_land_vars.F90:112
scale_cpl_sfc_index::i_r_ir
integer, parameter, public i_r_ir
Definition: scale_cpl_sfc_index.F90:29
mod_land_vars::atmos_u
real(rp), dimension(:,:), allocatable, public atmos_u
Definition: mod_land_vars.F90:120
scale_land_grid_cartesc_index::lje
integer, public lje
Definition: scale_land_grid_cartesC_index.F90:47
scale_prof::prof_rapstart
subroutine, public prof_rapstart(rapname_base, level, disable_barrier)
Start raptime.
Definition: scale_prof.F90:174
mod_land_vars::land_vars_restart_def_var
subroutine, public land_vars_restart_def_var
Define land variables in restart file.
Definition: mod_land_vars.F90:1538
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
mod_land_vars::land_restart_out_title
character(len=h_mid), public land_restart_out_title
Title of the output file.
Definition: mod_land_vars.F90:58
mod_land_vars::land_restart_in_aggregate
logical, public land_restart_in_aggregate
Switch to use aggregate file.
Definition: mod_land_vars.F90:53
mod_land_vars::land_sflx_mv
real(rp), dimension(:,:), allocatable, public land_sflx_mv
land surface v-momentum flux [kg/m2/s]
Definition: mod_land_vars.F90:88
mod_land_vars::i_waterdiff
integer, parameter, public i_waterdiff
Definition: mod_land_vars.F90:146
mod_land_vars::atmos_cossza
real(rp), dimension(:,:), allocatable, public atmos_cossza
Definition: mod_land_vars.F90:128
scale_land_grid_cartesc_real::land_grid_cartesc_real_totarea
real(rp), public land_grid_cartesc_real_totarea
total area
Definition: scale_land_grid_cartesC_real.F90:37
mod_land_vars::i_z0m
integer, parameter, public i_z0m
Definition: mod_land_vars.F90:149
mod_land_vars::atmos_sflx_rad_dn
real(rp), dimension(:,:,:,:), allocatable, public atmos_sflx_rad_dn
Definition: mod_land_vars.F90:127
mod_land_vars::land_ice_t
real(rp), dimension(:,:,:), allocatable, public land_ice_t
tendency of LAND_ICE
Definition: mod_land_vars.F90:78
scale_io::io_get_available_fid
integer function, public io_get_available_fid()
search & get available file ID
Definition: scale_io.F90:373
mod_land_vars::snow_wstar
real(rp), dimension(:,:), allocatable, public snow_wstar
Definition: mod_land_vars.F90:109
scale_landuse::landuse_exists_land
logical, dimension(:,:), allocatable, public landuse_exists_land
land calculation flag
Definition: scale_landuse.F90:51
mod_land_vars::atmos_sflx_water
real(rp), dimension(:,:), allocatable, public atmos_sflx_water
Definition: mod_land_vars.F90:129
mod_land_vars::soil_rlmo
real(rp), dimension(:,:), pointer, public soil_rlmo
Definition: mod_land_vars.F90:105
scale_file_history
module file_history
Definition: scale_file_history.F90:15
mod_land_admin::snow_type
character(len=h_short), public snow_type
Definition: mod_land_admin.F90:38
mod_land_vars::land_rlmo
real(rp), dimension(:,:), allocatable, target, public land_rlmo
inversed Obukhov length [1/m]
Definition: mod_land_vars.F90:100
mod_land_vars::land_vars_monitor
subroutine, public land_vars_monitor
monitor output
Definition: mod_land_vars.F90:956
scale_file
module file
Definition: scale_file.F90:15
scale_land_grid_cartesc_real::land_grid_cartesc_real_totvol
real(rp), public land_grid_cartesc_real_totvol
total volume
Definition: scale_land_grid_cartesC_real.F90:39
mod_land_vars::snow_tstar
real(rp), dimension(:,:), allocatable, public snow_tstar
Definition: mod_land_vars.F90:107
mod_land_vars::soil_tstar
real(rp), dimension(:,:), pointer, public soil_tstar
Definition: mod_land_vars.F90:102
scale_land_grid_cartesc_index
module land / grid / cartesianC / index
Definition: scale_land_grid_cartesC_index.F90:11
mod_land_vars::land_sflx_gh
real(rp), dimension(:,:), allocatable, public land_sflx_gh
land surface heat flux [J/m2/s]
Definition: mod_land_vars.F90:81
scale_prc
module PROCESS
Definition: scale_prc.F90:11
mod_land_vars::land_sflx_mw
real(rp), dimension(:,:), allocatable, public land_sflx_mw
land surface w-momentum flux [kg/m2/s]
Definition: mod_land_vars.F90:86
mod_land_vars::atmos_pres
real(rp), dimension(:,:), allocatable, public atmos_pres
Definition: mod_land_vars.F90:118
mod_land_vars::land_vars_restart_write
subroutine, public land_vars_restart_write
Write land variables to restart file.
Definition: mod_land_vars.F90:1583
mod_land_vars::land_vars_restart_close
subroutine, public land_vars_restart_close
Close restart file.
Definition: mod_land_vars.F90:1514
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
mod_land_vars::land_restart_out_postfix_timelabel
logical, public land_restart_out_postfix_timelabel
Add timelabel to the basename of output file?
Definition: mod_land_vars.F90:57
scale_io::io_get_fname
subroutine, public io_get_fname(outstr, instr, rank, ext, len)
generate process specific filename
Definition: scale_io.F90:421
scale_io
module STDIO
Definition: scale_io.F90:10
scale_cpl_sfc_index::i_r_nir
integer, parameter, public i_r_nir
Definition: scale_cpl_sfc_index.F90:30
mod_land_vars::soil_wstar
real(rp), dimension(:,:), pointer, public soil_wstar
Definition: mod_land_vars.F90:104
scale_tracer::k
real(rp), public k
Definition: scale_tracer.F90:45
scale_const
module CONSTANT
Definition: scale_const.F90:11
mod_land_vars::land_sflx_sh
real(rp), dimension(:,:), allocatable, public land_sflx_sh
land surface sensible heat flux [J/m2/s]
Definition: mod_land_vars.F90:89
mod_land_vars::land_wstar
real(rp), dimension(:,:), allocatable, target, public land_wstar
convective velocity scale [m/s]
Definition: mod_land_vars.F90:99
mod_land_vars::land_ustar
real(rp), dimension(:,:), allocatable, target, public land_ustar
friction velocity [m/s]
Definition: mod_land_vars.F90:96
mod_land_admin
module Land admin
Definition: mod_land_admin.F90:11
scale_debug::check
subroutine, public check(current_line, v)
Undefined value checker.
Definition: scale_debug.F90:59
mod_land_vars::land_property_in_filename
character(len=h_long), public land_property_in_filename
the file of land parameter table
Definition: mod_land_vars.F90:138
mod_land_vars::land_property
real(rp), dimension(:,:,:), allocatable, public land_property
land surface property
Definition: mod_land_vars.F90:136
mod_land_vars::land_temp_t
real(rp), dimension(:,:,:), allocatable, public land_temp_t
tendency of LAND_TEMP
Definition: mod_land_vars.F90:76
scale_land_grid_cartesc_index::lie
integer, public lie
Definition: scale_land_grid_cartesC_index.F90:43
mod_land_vars::snow_ustar
real(rp), dimension(:,:), allocatable, public snow_ustar
Definition: mod_land_vars.F90:106
scale_land_grid_cartesc_real
module land / grid / cartesianC / real
Definition: scale_land_grid_cartesC_real.F90:11
scale_landuse::landuse_index_pft
integer, dimension(:,:,:), allocatable, public landuse_index_pft
index of PFT for each mosaic
Definition: scale_landuse.F90:68
mod_land_vars::land_qstar
real(rp), dimension(:,:), allocatable, target, public land_qstar
moisture scale [kg/kg]
Definition: mod_land_vars.F90:98
scale_file_cartesc::file_cartesc_close
subroutine, public file_cartesc_close(fid)
Close a netCDF file.
Definition: scale_file_cartesC.F90:1044
mod_land_vars
module LAND Variables
Definition: mod_land_vars.F90:11
scale_landuse::landuse_pft_nmax
integer, public landuse_pft_nmax
number of plant functional type(PFT)
Definition: scale_landuse.F90:64
mod_land_vars::land_sflx_water
real(rp), dimension(:,:), allocatable, public land_sflx_water
land surface water flux [kg/m2/s]
Definition: mod_land_vars.F90:82
mod_land_vars::land_restart_out_aggregate
logical, public land_restart_out_aggregate
Switch to use aggregate file.
Definition: mod_land_vars.F90:56
mod_land_vars::land_vars_restart_open
subroutine, public land_vars_restart_open
Open land restart file for read.
Definition: mod_land_vars.F90:705
mod_land_vars::land_property_nmax
integer, parameter, public land_property_nmax
Definition: mod_land_vars.F90:140
scale_prof
module profiler
Definition: scale_prof.F90:11
mod_land_vars::snow_nosnowsec
real(rp), dimension(:,:), allocatable, public snow_nosnowsec
sec while no snow [s]
Definition: mod_land_vars.F90:73
mod_land_vars::i_thermalcond
integer, parameter, public i_thermalcond
Definition: mod_land_vars.F90:144
scale_monitor::monitor_reg
subroutine, public monitor_reg(name, desc, unit, itemid, ndims, dim_type, is_tendency)
Search existing item, or matching check between requested and registered item.
Definition: scale_monitor.F90:243
mod_land_vars::land_restart_output
logical, public land_restart_output
Output restart file?
Definition: mod_land_vars.F90:50
mod_land_vars::land_vars_restart_enddef
subroutine, public land_vars_restart_enddef
Exit netCDF define mode.
Definition: mod_land_vars.F90:1496
scale_time
module TIME
Definition: scale_time.F90:11
mod_land_vars::land_runoff_engi
real(rp), dimension(:,:), allocatable, public land_runoff_engi
internal energy of the runoff [J/m2/s]
Definition: mod_land_vars.F90:113
scale_land_grid_cartesc_index::lis
integer, public lis
Definition: scale_land_grid_cartesC_index.F90:42
mod_land_vars::i_heatcapacity
integer, parameter, public i_heatcapacity
Definition: mod_land_vars.F90:145
mod_land_vars::land_restart_in_basename
character(len=h_long), public land_restart_in_basename
Basename of the input file.
Definition: mod_land_vars.F90:52
mod_land_vars::land_restart_out_dtype
character(len=h_short), public land_restart_out_dtype
REAL4 or REAL8.
Definition: mod_land_vars.F90:59
mod_land_vars::soil_qstar
real(rp), dimension(:,:), pointer, public soil_qstar
Definition: mod_land_vars.F90:103
mod_land_vars::snow_swe
real(rp), dimension(:,:), allocatable, public snow_swe
snow water equivalent [kg/m2]
Definition: mod_land_vars.F90:70
mod_land_vars::i_waterlimit
integer, parameter, public i_waterlimit
Definition: mod_land_vars.F90:141
scale_tracer
module TRACER
Definition: scale_tracer.F90:12
mod_land_vars::i_z0h
integer, parameter, public i_z0h
Definition: mod_land_vars.F90:150
mod_land_vars::land_q2
real(rp), dimension(:,:), allocatable, public land_q2
land surface water vapor at 2m [kg/kg]
Definition: mod_land_vars.F90:95
scale_atmos_hydrometeor::i_qv
integer, public i_qv
Definition: scale_atmos_hydrometeor.F90:93
mod_land_vars::i_z0e
integer, parameter, public i_z0e
Definition: mod_land_vars.F90:151
mod_land_vars::convert_ws2vwc
real(rp) function, dimension(lia, lja), public convert_ws2vwc(WS, critical)
conversion from water saturation [fraction] to volumetric water content [m3/m3]
Definition: mod_land_vars.F90:1422
mod_land_vars::land_vars_check
subroutine, public land_vars_check(force)
Budget monitor for land.
Definition: mod_land_vars.F90:1089
mod_land_vars::atmos_dens
real(rp), dimension(:,:), allocatable, public atmos_dens
Definition: mod_land_vars.F90:122
scale_const::const_dwatr
real(rp), parameter, public const_dwatr
density of water [kg/m3]
Definition: scale_const.F90:89
scale_land_grid_cartesc_real::land_grid_cartesc_real_vol
real(rp), dimension(:,:,:), allocatable, public land_grid_cartesc_real_vol
volume of grid cell
Definition: scale_land_grid_cartesC_real.F90:38
mod_land_vars::land_sfc_temp
real(rp), dimension(:,:), allocatable, public land_sfc_temp
land surface skin temperature [K]
Definition: mod_land_vars.F90:65
scale_debug
module DEBUG
Definition: scale_debug.F90:11
mod_land_vars::snow_qstar
real(rp), dimension(:,:), allocatable, public snow_qstar
Definition: mod_land_vars.F90:108
mod_land_vars::land_vars_setup
subroutine, public land_vars_setup
Setup.
Definition: mod_land_vars.F90:283
scale_file_cartesc::file_cartesc_create
subroutine, public file_cartesc_create(basename, title, datatype, fid, date, subsec, haszcoord, append, aggregate, single)
Create/open a netCDF file.
Definition: scale_file_cartesC.F90:796
scale_statistics::statistics_checktotal
logical, public statistics_checktotal
calc&report variable totals to logfile?
Definition: scale_statistics.F90:109
scale_file_cartesc::file_cartesc_flush
subroutine, public file_cartesc_flush(fid)
Flush all pending requests to a netCDF file (PnetCDF only)
Definition: scale_file_cartesC.F90:1018
scale_time::time_gettimelabel
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:93
scale_comm_cartesc
module COMMUNICATION
Definition: scale_comm_cartesC.F90:11
scale_cpl_sfc_index
module coupler / surface-atmospehre
Definition: scale_cpl_sfc_index.F90:11
mod_land_vars::snow_depth
real(rp), dimension(:,:), allocatable, public snow_depth
snow depth [m]
Definition: mod_land_vars.F90:71
mod_land_admin::land_do
logical, public land_do
Definition: mod_land_admin.F90:41
mod_land_vars::land_u10
real(rp), dimension(:,:), allocatable, public land_u10
land surface velocity u at 10m [m/s]
Definition: mod_land_vars.F90:92
scale_cpl_sfc_index::i_r_vis
integer, parameter, public i_r_vis
Definition: scale_cpl_sfc_index.F90:31
mod_land_vars::snow_flag
logical, public snow_flag
Definition: mod_land_vars.F90:133
mod_land_vars::atmos_sfc_dens
real(rp), dimension(:,:), allocatable, public atmos_sfc_dens
Definition: mod_land_vars.F90:125
scale_atmos_hydrometeor::lhf
real(rp), public lhf
latent heat of fusion for use [J/kg]
Definition: scale_atmos_hydrometeor.F90:146
scale_file::file_get_aggregate
logical function, public file_get_aggregate(fid)
Definition: scale_file.F90:6316
mod_land_vars::land_sflx_lh
real(rp), dimension(:,:), allocatable, public land_sflx_lh
land surface latent heat flux [J/m2/s]
Definition: mod_land_vars.F90:90
scale_file_cartesc::file_cartesc_open
subroutine, public file_cartesc_open(basename, fid, single, aggregate)
open a netCDF file for read
Definition: scale_file_cartesC.F90:760
mod_land_vars::land_v10
real(rp), dimension(:,:), allocatable, public land_v10
land surface velocity v at 10m [m/s]
Definition: mod_land_vars.F90:93
scale_prof::prof_rapend
subroutine, public prof_rapend(rapname_base, level, disable_barrier)
Save raptime.
Definition: scale_prof.F90:246
mod_land_vars::land_vars_finalize
subroutine, public land_vars_finalize
Finalize.
Definition: mod_land_vars.F90:596
scale_tracer::description
character(len=h_mid), public description
Definition: scale_tracer.F90:40
scale_land_grid_cartesc_index::lke
integer, public lke
Definition: scale_land_grid_cartesC_index.F90:39
mod_land_vars::land_vars_restart_create
subroutine, public land_vars_restart_create
Create land restart file.
Definition: mod_land_vars.F90:1453
scale_landuse
module LANDUSE
Definition: scale_landuse.F90:19
scale_const::const_dice
real(rp), parameter, public const_dice
density of ice [kg/m3]
Definition: scale_const.F90:90
scale_cpl_sfc_index::n_rad_rgn
integer, parameter, public n_rad_rgn
Definition: scale_cpl_sfc_index.F90:28
mod_land_vars::land_vars_restart_read
subroutine, public land_vars_restart_read
Read land restart.
Definition: mod_land_vars.F90:752
mod_land_vars::land_ice
real(rp), dimension(:,:,:), allocatable, public land_ice
ice of each soil layer [m3/m3]
Definition: mod_land_vars.F90:64
mod_land_vars::land_t2
real(rp), dimension(:,:), allocatable, public land_t2
land surface temperature at 2m [K]
Definition: mod_land_vars.F90:94
scale_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:43
mod_land_vars::atmos_sflx_engi
real(rp), dimension(:,:), allocatable, public atmos_sflx_engi
Definition: mod_land_vars.F90:130
mod_land_vars::snow_rlmo
real(rp), dimension(:,:), allocatable, public snow_rlmo
Definition: mod_land_vars.F90:110
mod_land_vars::atmos_pbl
real(rp), dimension(:,:), allocatable, public atmos_pbl
Definition: mod_land_vars.F90:124
mod_land_vars::i_watercritical
integer, parameter, public i_watercritical
Definition: mod_land_vars.F90:142
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:57
scale_land_grid_cartesc_index::lks
integer, public lks
Definition: scale_land_grid_cartesC_index.F90:38
scale_file_cartesc
module file / cartesianC
Definition: scale_file_cartesC.F90:11
scale_atmos_hydrometeor::cv_water
real(rp), public cv_water
CV for water [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:151
mod_land_vars::snow_dzero
real(rp), dimension(:,:), allocatable, public snow_dzero
snow depth at melting point [m]
Definition: mod_land_vars.F90:72
mod_land_vars::atmos_v
real(rp), dimension(:,:), allocatable, public atmos_v
Definition: mod_land_vars.F90:121
mod_land_vars::land_restart_in_postfix_timelabel
logical, public land_restart_in_postfix_timelabel
Add timelabel to the basename of input file?
Definition: mod_land_vars.F90:54
mod_land_vars::land_sflx_qtrc
real(rp), dimension(:,:,:), allocatable, public land_sflx_qtrc
land surface tracer flux [kg/m2/s]
Definition: mod_land_vars.F90:91
scale_atmos_hydrometeor::cv_ice
real(rp), public cv_ice
CV for ice [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:153
scale_land_grid_cartesc_index::lka
integer, public lka
Definition: scale_land_grid_cartesC_index.F90:37
scale_land_grid_cartesc_real::land_grid_cartesc_real_area
real(rp), dimension(:,:), allocatable, public land_grid_cartesc_real_area
area of grid cell
Definition: scale_land_grid_cartesC_real.F90:36
scale_landuse::landuse_pft_nmin
integer, parameter, public landuse_pft_nmin
minimum number of PFT type
Definition: scale_landuse.F90:63
scale_monitor
module MONITOR
Definition: scale_monitor.F90:12