Merge remote-tracking branch 'origin/release-v4.6.1'
[WRF.git] / hydro / OrchestratorLayer / config.F90
blob8188579658b2c705f2c900baf9d648ebd5c86d28
1 module config_base
2   !use netcdf_layer_base
4   use module_hydro_stop, only:HYDRO_stop
6   implicit none
8   integer, PARAMETER    :: MAX_SOIL_LEVELS = 10   ! maximum soil levels in namelist
9   !REAL                  ::  DTBL      ! timestep [s]
11   type NOAHLSM_OFFLINE_
12      character(len=256) :: indir
13      integer            :: nsoil ! number of soil layers
14      integer            :: crocus_opt = 0
15      integer            :: act_lev    = 0
16      integer            :: forcing_timestep
17      integer            :: noah_timestep
18      integer            :: start_year
19      integer            :: start_month
20      integer            :: start_day
21      integer            :: start_hour
22      integer            :: start_min
23      character(len=256) :: outdir = "."
24      character(len=256) :: restart_filename_requested = " "
25      integer            :: restart_frequency_hours
26      integer            :: output_timestep
27      integer            :: dynamic_veg_option
28      integer            :: canopy_stomatal_resistance_option
29      integer            :: btr_option
30      integer            :: runoff_option
31      integer            :: surface_drag_option
32      integer            :: supercooled_water_option
33      integer            :: frozen_soil_option
34      integer            :: radiative_transfer_option
35      integer            :: snow_albedo_option
36      integer            :: pcp_partition_option
37      integer            :: tbot_option
38      integer            :: temp_time_scheme_option
39      integer            :: glacier_option
40      integer            :: surface_resistance_option
42      integer            :: soil_data_option = 1
43      integer            :: pedotransfer_option = 0
44      integer            :: crop_option = 0
45      integer            :: imperv_option = 9
47      integer            :: split_output_count = 1
48      integer            :: khour
49      integer            :: kday = -999
50      real               :: zlvl
51      character(len=256) :: hrldas_setup_file = " "
52      character(len=256) :: mmf_runoff_file = " "
53      character(len=256) :: external_veg_filename_template = " "
54      character(len=256) :: external_lai_filename_template = " "
55      integer            :: xstart = 1
56      integer            :: ystart = 1
57      integer            :: xend = 0
58      integer            :: yend = 0
59      REAL, DIMENSION(MAX_SOIL_LEVELS) :: soil_thick_input       ! depth to soil interfaces from namelist [m]
60      integer :: rst_bi_out, rst_bi_in !0: default netcdf format. 1: binary write/read by each core.
61      CHARACTER(LEN = 256) :: spatial_filename
62   end type NOAHLSM_OFFLINE_
64   type WRF_HYDRO_OFFLINE_
65      integer  :: finemesh
66      integer  :: finemesh_factor
67      integer  :: forc_typ
68      integer  :: snow_assim
69   end type WRF_HYDRO_OFFLINE_
71   TYPE namelist_rt_
73      integer :: nsoil, SOLVEG_INITSWC
74      integer :: act_lev = 0
75      real,allocatable,dimension(:) :: ZSOIL8
76      real*8  :: out_dt, rst_dt
77      real    :: dt  !! dt is NOAH_TIMESTEP
78      integer :: START_YEAR, START_MONTH, START_DAY, START_HOUR, START_MIN
79      character(len=256)  :: restart_file = ""
80      integer             :: split_output_count
81      integer :: igrid
82      integer :: rst_bi_in   ! used for parallel io with large restart file.
83      integer :: rst_bi_out   ! used for parallel io with large restart file.
84      ! each process will output the restart tile.
85      character(len=256) :: geo_static_flnm = ""
86      character(len=1024) :: land_spatial_meta_flnm = ""
87      integer :: DEEPGWSPIN
88      integer ::  order_to_write, rst_typ
89      character(len=256)  :: upmap_file = ""    ! user defined mapping file for NHDPLUS
90      character(len=256)  :: hydrotbl_f = ""    ! hydrotbl file
92      !      additional character
93      character :: hgrid
94      character(len=19) :: olddate="123456"
95      character(len=19) :: startdate="123456"
96      character(len=19) :: sincedate="123456"
98      integer :: io_config_outputs  ! used for NCEP REALTIME OUTPUT
99      integer :: io_form_outputs ! Flag to turn specify level of internal compression
100      integer :: t0OutputFlag
101      integer :: channel_only, channelBucket_only
102      integer :: output_channelBucket_influx ! used for FORCE_TYPE 9 and 10
104      integer:: RT_OPTION, CHANRTSWCRT, channel_option, &
105           SUBRTSWCRT,OVRTSWCRT,AGGFACTRT, &
106           GWBASESWCRT,  GW_RESTART,RSTRT_SWC,TERADJ_SOLAR, &
107           sys_cpl, gwChanCondSw, GwPreCycles, GwSpinCycles, GwPreDiagInterval, &
108           gwsoilcpl, UDMP_OPT
109      logical:: GwPreDiag, GwSpinUp
110      real:: DTRT_TER,DTRT_CH, DTCT, dxrt0,  gwChanCondConstIn, gwChanCondConstOut, gwIhShift
111      character(len=256) :: route_topo_f=""
112      character(len=256) :: route_chan_f=""
113      character(len=256) :: route_link_f=""
114      character(len=256) :: route_lake_f=""
115      logical            :: reservoir_persistence_usgs
116      logical            :: reservoir_persistence_usace
117      character(len=256) :: reservoir_parameter_file=""
118      character(len=256) :: reservoir_usgs_timeslice_path=""
119      character(len=256) :: reservoir_usace_timeslice_path=""
120      integer            :: reservoir_observation_lookback_hours = 18
121      integer            :: reservoir_observation_update_time_interval_seconds = 86400
122      logical            :: reservoir_rfc_forecasts
123      character(len=256) :: reservoir_rfc_forecasts_time_series_path=""
124      integer            :: reservoir_rfc_forecasts_lookback_hours
125      logical            :: reservoir_type_specified
126      character(len=256) :: route_direction_f=""
127      character(len=256) :: route_order_f=""
128      character(len=256) :: gwbasmskfil =""
129      character(len=256) :: gwstrmfil =""
130      character(len=256) :: geo_finegrid_flnm =""
131      character(len=256) :: udmap_file =""
132      character(len=256) :: GWBUCKPARM_file = ""
133      integer :: reservoir_data_ingest ! STUB FOR USE OF REALTIME RESERVOIR DISCHARGE DATA. CURRENTLY NOT IN USE.
134      character(len=1024) :: reservoir_obs_dir = ""
136      logical :: compound_channel
137      integer ::frxst_pts_out            ! ASCII point timeseries output at user specified points
138      integer ::CHRTOUT_DOMAIN           ! Netcdf point timeseries output at all channel points
139      integer ::CHRTOUT_GRID                ! Netcdf grid of channel streamflow values
140      integer ::CHANOBS_DOMAIN             ! NetCDF point timeseries of output at forecast/gage points
141      integer ::LSMOUT_DOMAIN              ! Netcdf grid of variables passed between LSM and routing components
142      integer ::RTOUT_DOMAIN                ! Netcdf grid of terrain routing variables on routing grid
143      integer ::output_gw                   ! Netcdf grid of GW
144      integer ::outlake                   ! Netcdf grid of lake
145      integer :: rtFlag
146      integer ::khour
148      integer :: channel_loss_option = 0
150      character(len=256) :: nudgingParamFile
151      character(len=256) :: netwkReExFile
152      logical            :: readTimesliceParallel
153      logical            :: temporalPersistence
154      logical            :: persistBias
155      logical            :: biasWindowBeforeT0
156      character(len=256) :: nudgingLastObsFile
157      integer            :: minNumPairsBiasPersist
158      integer            :: maxAgePairsBiasPersist
159      logical            :: invDistTimeWeightBias
160      logical            :: noConstInterfBias
161      character(len=256) :: timeSlicePath
162      integer            :: nLastObs
163      integer            :: bucket_loss
164      integer            :: imperv_adj
166      logical            :: channel_bypass = .FALSE.
168    contains
170      procedure, pass(self) :: check => rt_nlst_check
172   END TYPE namelist_rt_
174   type, public :: Configuration_
175    contains
176      procedure, nopass :: init => config_init
177      procedure, nopass :: init_nlst => init_namelist_rt_field
178   end type Configuration_
180   type crocus_options
181      integer :: crocus_opt = 0
182      integer :: act_lev = 0
183   end type crocus_options
185   integer, parameter :: max_domain = 5
187   type(NOAHLSM_OFFLINE_), protected, save :: noah_lsm
188   type(WRF_HYDRO_OFFLINE_), protected, save :: wrf_hydro
189   type(namelist_rt_), dimension(max_domain), save :: nlst
191 contains
193   subroutine config_init()
194     implicit none
196     integer, parameter :: did = 1
198     call init_noah_lsm_and_wrf_hydro()
200   end subroutine config_init
202   subroutine rt_nlst_check(self)
203     ! Subroutine to check namelist options specified by the user.
204     implicit none
206     class(namelist_rt_) self
208     ! Local variables
209     logical :: fileExists = .false.
210     integer :: i
212     !  ! Go through and make some logical checks for each hydro.namelist option.
213     !  ! Some of these checks will depend on specific options chosen by the user.
215     if( (self%sys_cpl .lt. 1) .or. (self%sys_cpl .gt. 4) ) then
216        call hydro_stop("hydro.namelist ERROR: Invalid sys_cpl value specified.")
217     endif
218    if(len(trim(self%geo_static_flnm)) .eq. 0) then
219       call hydro_stop("hydro.namelist ERROR: Please specify a GEO_STATIC_FLNM file.")
220    else
221       inquire(file=trim(self%geo_static_flnm),exist=fileExists)
222       if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: GEO_STATIC_FLNM not found.')
223    endif
224    if(len(trim(self%geo_finegrid_flnm)) .eq. 0) then
225       call hydro_stop("hydro.namelist ERROR: Please specify a GEO_FINEGRID_FLNM file.")
226    else
227       inquire(file=trim(self%geo_finegrid_flnm),exist=fileExists)
228       if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: GEO_FINEGRID_FLNM not found.')
229    endif
230    !if(len(trim(self%land_spatial_meta_flnm)) .eq. 0) then
231    !   call hydro_stop("hydro.namelist ERROR: Please specify a LAND_SPATIAL_META_FLNM file.")
232    !else
233    !   inquire(file=trim(self%land_spatial_meta_flnm),exist=fileExists)
234    !   if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: LAND_SPATIAL_META_FLNM not found.')
235    !endif
236    if(len(trim(self%RESTART_FILE)) .ne. 0) then
237       inquire(file=trim(self%RESTART_FILE),exist=fileExists)
238       if (.not. fileExists) call hydro_stop('hydro.namelist ERROR:= Hydro RESTART_FILE not found.')
239    endif
240    if(self%igrid .le. 0) call hydro_stop('hydro.namelist ERROR: Invalid IGRID specified.')
241    if(self%out_dt .le. 0) call hydro_stop('hydro_namelist ERROR: Invalid out_dt specified.')
242    if( (self%split_output_count .lt. 0 ) .or. (self%split_output_count .gt. 1) ) then
243       call hydro_stop('hydro.namelist ERROR: Invalid SPLIT_OUTPUT_COUNT specified')
244    endif
245    if( (self%rst_typ .lt. 0 ) .or. (self%rst_typ .gt. 1) ) then
246       call hydro_stop('hydro.namelist ERROR: Invalid rst_typ specified')
247    endif
248    if( (self%rst_bi_in .lt. 0 ) .or. (self%rst_bi_in .gt. 1) ) then
249       call hydro_stop('hydro.namelist ERROR: Invalid rst_bi_in specified')
250    endif
251    if( (self%rst_bi_out .lt. 0 ) .or. (self%rst_bi_out .gt. 1) ) then
252       call hydro_stop('hydro.namelist ERROR: Invalid rst_bi_out specified')
253    endif
254    if( (self%RSTRT_SWC .lt. 0 ) .or. (self%RSTRT_SWC .gt. 1) ) then
255       call hydro_stop('hydro.namelist ERROR: Invalid RSTRT_SWC specified')
256    endif
257    if( (self%GW_RESTART .lt. 0 ) .or. (self%GW_RESTART .gt. 1) ) then
258       call hydro_stop('hydro.namelist ERROR: Invalid GW_RESTART specified')
259    endif
260    if( (self%order_to_write .lt. 1 ) .or. (self%order_to_write .gt. 12) ) then
261       call hydro_stop('hydro.namelist ERROR: Invalid order_to_write specified')
262    endif
263    if( (self%io_form_outputs .lt. 0 ) .or. (self%io_form_outputs .gt. 4) ) then
264       call hydro_stop('hydro.namelist ERROR: Invalid io_form_outputs specified')
265    endif
266    if( (self%io_config_outputs .lt. 0 ) .or. (self%io_config_outputs .gt. 6) ) then
267       call hydro_stop('hydro.namelist ERROR: Invalid io_config_outputs specified')
268    endif
269    if( (self%t0OutputFlag .lt. 0 ) .or. (self%t0OutputFlag .gt. 1) ) then
270       call hydro_stop('hydro.namelist ERROR: Invalid t0OutputFlag specified')
271    endif
272    if( (self%output_channelBucket_influx .lt. 0 ) .or. (self%output_channelBucket_influx .gt. 3) ) then
273       call hydro_stop('hydro.namelist ERROR: Invalid output_channelBucket_influx specified')
274    endif
275    if( (self%CHRTOUT_DOMAIN .lt. 0 ) .or. (self%CHRTOUT_DOMAIN .gt. 1) ) then
276       call hydro_stop('hydro.namelist ERROR: Invalid CHRTOUT_DOMAIN specified')
277    endif
278    if( (self%CHANOBS_DOMAIN .lt. 0 ) .or. (self%CHANOBS_DOMAIN .gt. 1) ) then
279       call hydro_stop('hydro.namelist ERROR: Invalid CHANOBS_DOMAIN specified')
280    endif
281    if( (self%CHRTOUT_GRID .lt. 0 ) .or. (self%CHRTOUT_GRID .gt. 1) ) then
282       call hydro_stop('hydro.namelist ERROR: Invalid CHRTOUT_GRID specified')
283    endif
284    if( (self%LSMOUT_DOMAIN .lt. 0 ) .or. (self%LSMOUT_DOMAIN .gt. 1) ) then
285       call hydro_stop('hydro.namelist ERROR: Invalid LSMOUT_DOMAIN specified')
286    endif
287    if( (self%RTOUT_DOMAIN .lt. 0 ) .or. (self%RTOUT_DOMAIN .gt. 1) ) then
288       call hydro_stop('hydro.namelist ERROR: Invalid RTOUT_DOMAIN specified')
289    endif
290    if( (self%output_gw .lt. 0 ) .or. (self%output_gw .gt. 2) ) then
291       call hydro_stop('hydro.namelist ERROR: Invalid output_gw specified')
292    endif
293    if( (self%outlake .lt. 0 ) .or. (self%outlake .gt. 2) ) then
294       call hydro_stop('hydro.namelist ERROR: Invalid outlake specified')
295    endif
296    if( (self%frxst_pts_out .lt. 0 ) .or. (self%frxst_pts_out .gt. 1) ) then
297       call hydro_stop('hydro.namelist ERROR: Invalid frxst_pts_out specified')
298    endif
299    if(self%TERADJ_SOLAR .ne. 0) then
300       call hydro_stop('hydro.namelist ERROR: Invalid TERADJ_SOLAR specified')
301    endif
303    ! The default value of nsoil == -999. When channel-only is used,
304    ! nsoil ==  -999999. In the case of channel-only, skip following block of code.
305    if(self%NSOIL .le. 0 .and. self%NSOIL .ne. -999999) then
306       call hydro_stop('hydro.namelist ERROR: Invalid NSOIL specified.')
307    endif
308    do i = 1,self%NSOIL
309       if(self%ZSOIL8(i) .gt. 0) then
310           call hydro_stop('hydro.namelist ERROR: Invalid ZSOIL layer depth specified.')
311       endif
312       if(i .gt. 1) then
313          if(self%ZSOIL8(i) .ge. self%ZSOIL8(i-1)) then
314             call hydro_stop('hydro.namelist ERROR: Invalid ZSOIL layer depth specified.')
315          endif
316       endif
317    end do
319    if(self%NSOIL .le. 0 .and. self%NSOIL .ne. -999999) then
320       call hydro_stop('hydro.namelist ERROR: Invalid NSOIL specified.')
321    endif
323    if(self%dxrt0 .le. 0) then
324       call hydro_stop('hydro.namelist ERROR: Invalid DXRT specified.')
325    endif
326    if(self%AGGFACTRT .le. 0) then
327       call hydro_stop('hydro.namelist ERROR: Invalid AGGFACTRT specified.')
328    endif
329    if(self%DTRT_CH .le. 0) then
330       call hydro_stop('hydro.namelist ERROR: Invalid DTRT_CH specified.')
331    endif
332    if(self%DTRT_TER .le. 0) then
333       call hydro_stop('hydro.namelist ERROR: Invalid DTRT_TER specified.')
334    endif
335    if( (self%SUBRTSWCRT .lt. 0 ) .or. (self%SUBRTSWCRT .gt. 1) ) then
336       call hydro_stop('hydro.namelist ERROR: Invalid SUBRTSWCRT specified')
337    endif
338    if( (self%OVRTSWCRT .lt. 0 ) .or. (self%OVRTSWCRT .gt. 1) ) then
339       call hydro_stop('hydro.namelist ERROR: Invalid OVRTSWCRT specified')
340    endif
341    if( (self%OVRTSWCRT .eq. 1 ) .or. (self%SUBRTSWCRT .eq. 1) ) then
342       if( (self%rt_option .lt. 1 ) .or. (self%rt_option .gt. 2) ) then
343       !if(self%rt_option .ne. 1) then
344          call hydro_stop('hydro.namelist ERROR: Invalid rt_option specified')
345       endif
346    endif
347    if( (self%CHANRTSWCRT .lt. 0 ) .or. (self%CHANRTSWCRT .gt. 1) ) then
348       call hydro_stop('hydro.namelist ERROR: Invalid CHANRTSWCRT specified')
349    endif
350    if(self%CHANRTSWCRT .eq. 1) then
351       if ( self%channel_option .eq. 5 ) then
352          self%channel_option = 2
353          self%channel_bypass = .TRUE.
354       endif
355       if( (self%channel_option .lt. 1 ) .or. (self%channel_option .gt. 3) ) then
356          call hydro_stop('hydro.namelist ERROR: Invalid channel_option specified')
357       endif
358    endif
359    if( (self%CHANRTSWCRT .eq. 1) .and. (self%channel_option .lt. 3) ) then
360       if(len(trim(self%route_link_f)) .eq. 0) then
361          call hydro_stop("hydro.namelist ERROR: Please specify a route_link_f file.")
362       else
363          inquire(file=trim(self%route_link_f),exist=fileExists)
364          if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: route_link_f not found.')
365       endif
366    endif
367    if( (self%bucket_loss .lt. 0 ) .or. (self%bucket_loss .gt. 1) ) then
368       call hydro_stop('hydro.namelist ERROR: Invalid bucket_loss specified')
369    endif
370    if( (self%bucket_loss .eq. 1 ) .and. (self%UDMP_OPT .ne. 1) ) then
371       call hydro_stop('hydro.namelist ERROR: Bucket loss only available when UDMP=1')
372    endif
373    if( (self%GWBASESWCRT .lt. 0 ) .or. (self%GWBASESWCRT .gt. 4) ) then
374       call hydro_stop('hydro.namelist ERROR: Invalid GWBASESWCRT specified')
375    endif
376    if( (self%GWBASESWCRT .eq. 1 ) .or. (self%GWBASESWCRT .eq. 4) ) then
377       if(len(trim(self%GWBUCKPARM_file)) .eq. 0) then
378          call hydro_stop("hydro.namelist ERROR: Please specify a GWBUCKPARM_file file.")
379       else
380          inquire(file=trim(self%GWBUCKPARM_file),exist=fileExists)
381          if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: GWBUCKPARM_file not found.')
382       endif
383    endif
384    if( (self%GWBASESWCRT .gt. 0) .and. (self%UDMP_OPT .ne. 1) ) then
385       if(len(trim(self%gwbasmskfil)) .eq. 0) then
386          call hydro_stop("hydro.namelist ERROR: Please specify a gwbasmskfil file.")
387       else
388          inquire(file=trim(self%gwbasmskfil),exist=fileExists)
389          if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: gwbasmskfil not found.')
390       endif
391    endif
392    if( (self%UDMP_OPT .lt. 0 ) .or. (self%UDMP_OPT .gt. 1) ) then
393       call hydro_stop('hydro.namelist ERROR: Invalid UDMP_OPT specified')
394    endif
395    if(self%UDMP_OPT .gt. 0) then
396       if(len(trim(self%udmap_file)) .eq. 0) then
397          call hydro_stop("hydro.namelist ERROR: Please specify a udmap_file file.")
398       else
399          inquire(file=trim(self%udmap_file),exist=fileExists)
400          if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: udmap_file not found.')
401       endif
402    endif
403    if( (self%UDMP_OPT .eq. 1) .and. (self%CHANRTSWCRT .eq. 0) ) then
404          call hydro_stop('hydro.namelist ERROR: User-defined mapping requires channel routing on.')
405    endif
406    if(self%outlake .ne. 0) then
407       if(len(trim(self%route_lake_f)) .eq. 0) then
408          call hydro_stop('hydro.namelist ERROR: You MUST specify a route_lake_f to ouptut and run lakes.')
409       endif
410    endif
411    if(len(trim(self%route_lake_f)) .ne. 0) then
412       inquire(file=trim(self%route_lake_f),exist=fileExists)
413       if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: route_lake_f not found.')
414    endif
416    if((self%channel_option .eq. 3) .and. (self%compound_channel)) then
417       call hydro_stop("Compound channel option not available for diffusive wave routing. ")
418    end if
420    if(self%reservoir_type_specified) then
421       if(len(trim(self%reservoir_parameter_file)) .eq. 0) then
422          call hydro_stop('hydro.namelist ERROR: You MUST specify a reservoir_parameter_file for &
423          inputs to reservoirs that are not level pool type.')
424       endif
425       if(len(trim(self%reservoir_parameter_file)) .ne. 0) then
426         inquire(file=trim(self%reservoir_parameter_file),exist=fileExists)
427         if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: reservoir_parameter_file not found.')
428       endif
429    end if
431    if(self%reservoir_persistence_usgs) then
432       if(len(trim(self%reservoir_usgs_timeslice_path)) .eq. 0) then
433          call hydro_stop('hydro.namelist ERROR: You MUST specify a reservoir_usgs_timeslice_path for &
434          reservoir USGS persistence capability.')
435       endif
436       if(len(trim(self%reservoir_parameter_file)) .ne. 0) then
437         inquire(file=trim(self%reservoir_parameter_file),exist=fileExists)
438         if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: reservoir_parameter_file not found.')
439       endif
440     end if
442    if(self%reservoir_persistence_usace) then
443       if(len(trim(self%reservoir_usace_timeslice_path)) .eq. 0) then
444          call hydro_stop('hydro.namelist ERROR: You MUST specify a reservoir_usace_timeslice_path for &
445          reservoir USACE persistence capability.')
446       endif
447       if(len(trim(self%reservoir_parameter_file)) .ne. 0) then
448         inquire(file=trim(self%reservoir_parameter_file),exist=fileExists)
449         if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: reservoir_parameter_file not found.')
450       endif
451     end if
453    if(self%reservoir_rfc_forecasts) then
454       if(len(trim(self%reservoir_parameter_file)) .eq. 0) then
455          call hydro_stop('hydro.namelist ERROR: You MUST specify a reservoir_parameter_file for inputs to rfc forecast type reservoirs.')
456       endif
457       if(len(trim(self%reservoir_rfc_forecasts_time_series_path)) .eq. 0) then
458          call hydro_stop('hydro.namelist ERROR: You MUST specify a reservoir_rfc_forecasts_time_series_path for reservoir rfc forecast capability.')
459       endif
460       if(len(trim(self%reservoir_parameter_file)) .ne. 0) then
461         inquire(file=trim(self%reservoir_parameter_file),exist=fileExists)
462         if (.not. fileExists) call hydro_stop('hydro.namelist ERROR: reservoir_parameter_file not found.')
463       endif
464    end if
466    if( (self%imperv_adj .lt. 0 ) .or. (self%imperv_adj .gt. 1) ) then
467       call hydro_stop('hydro.namelist ERROR: Invalid imperv_adj specified')
468    endif
470   end subroutine rt_nlst_check
472   subroutine init_namelist_rt_field(did)
473     implicit none
475     integer, intent(in) :: did
477     integer ierr
478     integer:: RT_OPTION, CHANRTSWCRT, channel_option, &
479          SUBRTSWCRT,OVRTSWCRT,AGGFACTRT, &
480          GWBASESWCRT,  GW_RESTART,RSTRT_SWC,TERADJ_SOLAR, &
481          sys_cpl, rst_typ, rst_bi_in, rst_bi_out, &
482          gwChanCondSw, GwPreCycles, GwSpinCycles, GwPreDiagInterval, gwsoilcpl, &
483          UDMP_OPT, io_form_outputs, bucket_loss, imperv_adj
484     real:: DTRT_TER,DTRT_CH,dxrt, gwChanCondConstIn, gwChanCondConstOut, gwIhShift
485     character(len=256) :: route_topo_f=""
486     character(len=256) :: route_chan_f=""
487     character(len=256) :: route_link_f=""
488     logical            :: compound_channel
489     integer            :: channel_loss_option = 0
490     character(len=256) :: route_lake_f=""
491     logical            :: reservoir_persistence_usgs
492     logical            :: reservoir_persistence_usace
493     character(len=256) :: reservoir_parameter_file=""
494     character(len=256) :: reservoir_usgs_timeslice_path=""
495     character(len=256) :: reservoir_usace_timeslice_path=""
496     integer            :: reservoir_observation_lookback_hours = 24
497     integer            :: reservoir_observation_update_time_interval_seconds = 86400
498     logical            :: reservoir_rfc_forecasts
499     character(len=256) :: reservoir_rfc_forecasts_time_series_path=""
500     integer            :: reservoir_rfc_forecasts_lookback_hours = 28
501     logical            :: reservoir_type_specified
502     character(len=256) :: route_direction_f=""
503     character(len=256) :: route_order_f=""
504     character(len=256) :: gwbasmskfil =""
505     character(len=256) :: gwstrmfil =""
506     character(len=256) :: geo_finegrid_flnm =""
507     character(len=256) :: udmap_file =""
508     character(len=256) :: GWBUCKPARM_file = ""
509     integer :: reservoir_data_ingest ! STUB FOR USE OF REALTIME RESERVOIR DISCHARGE DATA. CURRENTLY NOT IN USE.
510     integer :: SOLVEG_INITSWC
511     real*8 :: out_dt, rst_dt
512     character(len=256)  :: RESTART_FILE = ""
513     character(len=256)  :: hydrotbl_f   = ""
514     logical            :: GwPreDiag, GwSpinUp
515     integer            :: split_output_count, order_to_write
516     integer :: igrid, io_config_outputs, t0OutputFlag, output_channelBucket_influx
517     character(len=256) :: geo_static_flnm = ""
518     character(len=1024) :: land_spatial_meta_flnm = ""
519     integer  :: DEEPGWSPIN
521     integer :: i
523     integer ::CHRTOUT_DOMAIN           ! Netcdf point timeseries output at all channel points
524     integer ::CHRTOUT_GRID                ! Netcdf grid of channel streamflow values
525     integer ::LSMOUT_DOMAIN              ! Netcdf grid of variables passed between LSM and routing components
526     integer ::RTOUT_DOMAIN                ! Netcdf grid of terrain routing variables on routing grid
527     integer  :: output_gw
528     integer  :: outlake
529     integer :: frxst_pts_out            ! ASCII text file of streamflow at forecast points
530     integer :: CHANOBS_DOMAIN           ! NetCDF point timeseries output at forecast points.
532 !!! add the following two dummy variables
533     integer  :: NSOIL
534     real :: ZSOIL8(8)
535     type(crocus_options) :: crocus_opts
537     logical            :: dir_e
538     character(len=1024) :: reservoir_obs_dir
539 #ifdef WRF_HYDRO_NUDGING
540     character(len=256) :: nudgingParamFile
541     character(len=256) :: netwkReExFile
542     logical            :: readTimesliceParallel
543     logical            :: temporalPersistence
544     logical            :: persistBias
545     logical            :: biasWindowBeforeT0
546     character(len=256) :: nudgingLastObsFile
547     character(len=256) :: timeSlicePath
548     integer            :: nLastObs
549     integer            :: minNumPairsBiasPersist
550     integer            :: maxAgePairsBiasPersist
551     logical            :: invDistTimeWeightBias
552     logical            :: noConstInterfBias
553 #endif
555     namelist /HYDRO_nlist/ NSOIL, ZSOIL8,&
556          RESTART_FILE,SPLIT_OUTPUT_COUNT,IGRID,&
557          geo_static_flnm, &
558          land_spatial_meta_flnm, &
559          out_dt, rst_dt, &
560          DEEPGWSPIN, SOLVEG_INITSWC, &
561          RT_OPTION, CHANRTSWCRT, channel_option, &
562          SUBRTSWCRT,OVRTSWCRT,AGGFACTRT, dtrt_ter,dtrt_ch,dxrt,&
563          GwSpinCycles, GwPreCycles, GwSpinUp, GwPreDiag, GwPreDiagInterval, gwIhShift, &
564          GWBASESWCRT, gwChanCondSw, gwChanCondConstIn, gwChanCondConstOut , &
565          route_topo_f,route_chan_f,route_link_f, compound_channel, channel_loss_option, route_lake_f, &
566          reservoir_persistence_usgs, reservoir_persistence_usace, reservoir_parameter_file, reservoir_usgs_timeslice_path, &
567          reservoir_usace_timeslice_path, reservoir_observation_lookback_hours, reservoir_observation_update_time_interval_seconds, &
568          reservoir_rfc_forecasts, reservoir_rfc_forecasts_time_series_path, reservoir_rfc_forecasts_lookback_hours, &
569          reservoir_type_specified, route_direction_f,route_order_f,gwbasmskfil, &
570          geo_finegrid_flnm, gwstrmfil,GW_RESTART,RSTRT_SWC,TERADJ_SOLAR, sys_cpl, &
571          order_to_write , rst_typ, rst_bi_in, rst_bi_out, gwsoilcpl, &
572          CHRTOUT_DOMAIN,CHANOBS_DOMAIN,CHRTOUT_GRID,LSMOUT_DOMAIN,&
573          RTOUT_DOMAIN, output_gw, outlake, &
574          frxst_pts_out, udmap_file, UDMP_OPT, GWBUCKPARM_file, bucket_loss, &
575          io_config_outputs, io_form_outputs, hydrotbl_f, t0OutputFlag, output_channelBucket_influx, imperv_adj
577 #ifdef WRF_HYDRO_NUDGING
578     namelist /NUDGING_nlist/ nudgingParamFile,       netwkReExFile,          &
579          readTimesliceParallel,  temporalPersistence,    &
580          persistBias,            nudgingLastObsFile,     &
581          timeSlicePath,          nLastObs,               &
582          minNumPairsBiasPersist, maxAgePairsBiasPersist, &
583          biasWindowBeforeT0,     invDistTimeWeightBias,  &
584          noConstInterfBias
585 #endif
587     !! ---- End definitions ----
589     ! Default values for HYDRO_nlist
590     UDMP_OPT = 0
591     rst_bi_in = 0
592     rst_bi_out = 0
593     io_config_outputs = 0
594     io_form_outputs = 0
595     frxst_pts_out = 0
596     CHANOBS_DOMAIN = 0
597     t0OutputFlag = 1
598     output_channelBucket_influx = 0
599     TERADJ_SOLAR = 0
600     reservoir_data_ingest = 0 ! STUB FOR USE OF REALTIME RESERVOIR DISCHARGE DATA. CURRENTLY NOT IN USE.
601     compound_channel = .FALSE.
602     channel_loss_option = 0
603     bucket_loss = 0
604     reservoir_persistence_usgs = .FALSE.
605     reservoir_persistence_usace = .FALSE.
606     reservoir_observation_lookback_hours = 18
607     reservoir_observation_update_time_interval_seconds = 86400
608     reservoir_rfc_forecasts = .FALSE.
609     reservoir_rfc_forecasts_lookback_hours = 24
610     reservoir_type_specified = .FALSE.
611     imperv_adj = 0
613 #ifdef WRF_HYDRO_NUDGING
614     ! Default values for NUDGING_nlist
615     nudgingParamFile = "DOMAIN/nudgingParams.nc"
616     netwkReExFile    = "DOMAIN/netwkReExFile.nc"
617     readTimesliceParallel  = .true.
618     temporalPersistence    = .true.
619     persistBias            = .false.
620     biasWindowBeforeT0     = .false.
621     nudgingLastObsFile     = ""
622     timeSlicePath          = "./nudgingTimeSliceObs/"
623     nLastObs               = 960
624     minNumPairsBiasPersist = 8
625     maxAgePairsBiasPersist = -99999
626     invDistTimeWeightBias  = .false.
627     noConstInterfBias      = .false.
628 #endif
630 ! #ifdef MPP_LAND
631 !     if(IO_id .eq. my_id) then
632 ! #endif
633 #ifndef NCEP_WCOSS
634     open(12, file="hydro.namelist", form="FORMATTED")
635 #else
636     open(12, form="FORMATTED")
637 #endif
638     read(12, HYDRO_nlist, iostat=ierr)
639     if(ierr .ne. 0) call hydro_stop("HYDRO_nlst namelist error in read_rt_nlst")
641 #ifdef WRF_HYDRO_NUDGING
642     read(12, NUDGING_nlist, iostat=ierr)
643     if(ierr .ne. 0) call hydro_stop("NUDGING_nlst namelist error in read_rt_nlst")
644     !! Conditional default values for nuding_nlist
645     if(maxAgePairsBiasPersist .eq. -99999) maxAgePairsBiasPersist = -1*nLastObs
646 #endif
647     close(12)
648     if (sys_cpl == 1) call read_crocus_namelist(crocus_opts)
649 ! #ifdef MPP_LAND
650 !     endif
651 ! #endif
653     ! ADCHANGE: move these checks to more universal namelist checks...
654     if ( io_config_outputs .eq. 4 ) RTOUT_DOMAIN = 0
656     if(output_channelBucket_influx .ne. 0) then
657        if(nlst(did)%dt .ne. out_dt*60) &
658             call hydro_stop("read_rt_nlst:: output_channelBucket_influx =! 0 inconsistent with out_dt and NOAH_TIMESTEP choices.")
659        if(output_channelBucket_influx .eq. 2 .and. GWBASESWCRT .ne. 1 .and. GWBASESWCRT .ne. 2 .and. GWBASESWCRT .ne. 4) &
660             call hydro_stop("read_rt_nlst:: output_channelBucket_influx = 2 but GWBASESWCRT != 1 or 2.")
661     end if
663     if(CHANRTSWCRT .eq. 0 .and. channel_option .lt. 3) channel_option = 3
665     !used to be broadcasted with MPI
666     !nlst(did)%NSOIL = NSOIL
667     !allocate(nlst(did)%ZSOIL8(NSOIL))
668     !nlst(did)%ZSOIL8 = ZSOIL8
670     nlst(did)%RESTART_FILE = RESTART_FILE
671     nlst(did)%hydrotbl_f = trim(hydrotbl_f)
672     nlst(did)%SPLIT_OUTPUT_COUNT = SPLIT_OUTPUT_COUNT
673     nlst(did)%IGRID = IGRID
674     nlst(did)%io_config_outputs = io_config_outputs
675     nlst(did)%io_form_outputs = io_form_outputs
676     nlst(did)%t0OutputFlag = t0OutputFlag
677     nlst(did)%output_channelBucket_influx = output_channelBucket_influx
678     nlst(did)%geo_static_flnm = geo_static_flnm
679     nlst(did)%land_spatial_meta_flnm = land_spatial_meta_flnm
680     nlst(did)%out_dt = out_dt
681     nlst(did)%rst_dt = rst_dt
682     nlst(did)%DEEPGWSPIN = DEEPGWSPIN
683     nlst(did)%SOLVEG_INITSWC = SOLVEG_INITSWC
684     nlst(did)%reservoir_obs_dir = "testDirectory"
686     nlst(did)%reservoir_persistence_usgs = reservoir_persistence_usgs
687     nlst(did)%reservoir_persistence_usace = reservoir_persistence_usace
688     nlst(did)%reservoir_parameter_file = reservoir_parameter_file
689     nlst(did)%reservoir_usgs_timeslice_path = reservoir_usgs_timeslice_path
690     nlst(did)%reservoir_usace_timeslice_path = reservoir_usace_timeslice_path
691     nlst(did)%reservoir_observation_lookback_hours = reservoir_observation_lookback_hours
692     nlst(did)%reservoir_observation_update_time_interval_seconds = reservoir_observation_update_time_interval_seconds
693     nlst(did)%reservoir_rfc_forecasts = reservoir_rfc_forecasts
694     nlst(did)%reservoir_rfc_forecasts_time_series_path = reservoir_rfc_forecasts_time_series_path
695     nlst(did)%reservoir_rfc_forecasts_lookback_hours = reservoir_rfc_forecasts_lookback_hours
697     if (reservoir_persistence_usgs .or. reservoir_persistence_usace .or. reservoir_rfc_forecasts) then
698         reservoir_type_specified = .TRUE.
699     end if
701     nlst(did)%reservoir_type_specified = reservoir_type_specified
703     write(nlst(did)%hgrid,'(I1)') igrid
705     if(RESTART_FILE .eq. "") rst_typ = 0
707     if(rst_bi_out .eq. 1) then
708        ! This part works for intel not pgi
709        !     inquire(directory='restart', exist=dir_e)
710        inquire(file='restart/.', exist=dir_e)
711        if(.not. dir_e) then
712           call system('mkdir restart')
713        endif
714     endif
716     if(channel_option .eq. 4) then
717        CHANRTSWCRT = 0
718        OVRTSWCRT = 0
719        SUBRTSWCRT = 0
720     endif
722     nlst(did)%CHRTOUT_DOMAIN = CHRTOUT_DOMAIN
723     nlst(did)%CHANOBS_DOMAIN = CHANOBS_DOMAIN
724     nlst(did)%output_gw      = output_gw
725     nlst(did)%outlake      = outlake
726     nlst(did)%frxst_pts_out = frxst_pts_out
727     nlst(did)%CHRTOUT_GRID = CHRTOUT_GRID
728     nlst(did)%LSMOUT_DOMAIN = LSMOUT_DOMAIN
729     nlst(did)%RTOUT_DOMAIN = RTOUT_DOMAIN
730     nlst(did)%RT_OPTION = RT_OPTION
731     nlst(did)%CHANRTSWCRT = CHANRTSWCRT
732     nlst(did)%GW_RESTART  = GW_RESTART
733     nlst(did)%RSTRT_SWC   = RSTRT_SWC
734     nlst(did)%channel_option = channel_option
735     nlst(did)%DTRT_TER   = DTRT_TER
736     nlst(did)%DTRT_CH   = DTRT_CH
737     nlst(did)%DTCT      = DTRT_CH   ! small time step for grid based channel routing
739     ! Some fields haven't been initialized yet (e.g. DT)
741     if(nlst(did)%DT .lt. DTRT_CH) then
742           print*, "nlst(did)%DT,  DTRT_CH = ",nlst(did)%DT,  DTRT_CH
743           print*, "reset DTRT_CH=nlst(did)%DT "
744           DTRT_CH=nlst(did)%DT
745     endif
746     if(nlst(did)%DT .lt. DTRT_TER) then
747           print*, "nlst(did)%DT,  DTRT_TER = ",nlst(did)%DT,  DTRT_TER
748           print*, "reset DTRT_TER=nlst(did)%DT "
749           DTRT_TER=nlst(did)%DT
750     endif
751     if (modulo(nlst(did)%DT, DTRT_TER) /= 0) then
752          print*, "nlst(did)%DT,  DTRT_TER = ",nlst(did)%DT,  DTRT_TER
753          call hydro_stop("module_namelist: DT not a multiple of DTRT_TER")
754     endif
755     if (modulo(nlst(did)%DT, DTRT_CH) /= 0) then
756          print*, "nlst(did)%DT,  DTRT_CH = ",nlst(did)%DT,  DTRT_CH
757          call hydro_stop("module_namelist: DT not a multiple of DTRT_CH")
758     endif
760     nlst(did)%act_lev = crocus_opts%act_lev
761     nlst(did)%SUBRTSWCRT = SUBRTSWCRT
762     nlst(did)%OVRTSWCRT = OVRTSWCRT
763     nlst(did)%dxrt0 = dxrt
764     nlst(did)%AGGFACTRT = AGGFACTRT
765     nlst(did)%GWBASESWCRT = GWBASESWCRT
766     nlst(did)%bucket_loss = bucket_loss
767     nlst(did)%GWSOILCPL= GWSOILCPL
768     nlst(did)%gwChanCondSw = gwChanCondSw
769     nlst(did)%gwChanCondConstIn = gwChanCondConstIn
770     nlst(did)%gwChanCondConstOut = gwChanCondConstOut
771     nlst(did)%gwIhShift = gwIhShift
772     nlst(did)%GwSpinCycles = GwSpinCycles
773     nlst(did)%GwPreCycles = GwPreCycles
774     nlst(did)%GwPreDiag = GwPreDiag
775     nlst(did)%GwSpinUp = GwSpinUp
776     nlst(did)%GwPreDiagInterval = GwPreDiagInterval
777     nlst(did)%TERADJ_SOLAR = TERADJ_SOLAR
778     nlst(did)%sys_cpl = sys_cpl
779     nlst(did)%rst_typ = rst_typ
780     nlst(did)%rst_bi_in = rst_bi_in
781     nlst(did)%rst_bi_out = rst_bi_out
782     nlst(did)%order_to_write = order_to_write
783     nlst(did)%compound_channel = compound_channel
784     nlst(did)%channel_loss_option = channel_loss_option
785     nlst(did)%imperv_adj = imperv_adj
786     ! files
787     nlst(did)%route_topo_f = route_topo_f
788     nlst(did)%route_chan_f = route_chan_f
789     nlst(did)%route_link_f = route_link_f
790     nlst(did)%route_lake_f = route_lake_f
792     nlst(did)%reservoir_persistence_usgs = reservoir_persistence_usgs
793     nlst(did)%reservoir_persistence_usace = reservoir_persistence_usace
794     nlst(did)%reservoir_parameter_file = reservoir_parameter_file
795     nlst(did)%reservoir_usgs_timeslice_path = reservoir_usgs_timeslice_path
796     nlst(did)%reservoir_usace_timeslice_path = reservoir_usace_timeslice_path
797     nlst(did)%reservoir_observation_lookback_hours = reservoir_observation_lookback_hours
798     nlst(did)%reservoir_observation_update_time_interval_seconds = reservoir_observation_update_time_interval_seconds
799     nlst(did)%reservoir_rfc_forecasts = reservoir_rfc_forecasts
800     nlst(did)%reservoir_rfc_forecasts_time_series_path = reservoir_rfc_forecasts_time_series_path
801     nlst(did)%reservoir_rfc_forecasts_lookback_hours = reservoir_rfc_forecasts_lookback_hours
803     nlst(did)%route_direction_f =  route_direction_f
804     nlst(did)%route_order_f =  route_order_f
805     nlst(did)%gwbasmskfil =  gwbasmskfil
806     nlst(did)%gwstrmfil =  gwstrmfil
807     nlst(did)%geo_finegrid_flnm =  geo_finegrid_flnm
808     nlst(did)%udmap_file =  udmap_file
809     nlst(did)%UDMP_OPT = UDMP_OPT
810     nlst(did)%GWBUCKPARM_file =  GWBUCKPARM_file
811     nlst(did)%reservoir_data_ingest = 0 ! STUB FOR USE OF REALTIME RESERVOIR DISCHARGE DATA. CURRENTLY NOT IN USE.
812     nlst(did)%reservoir_obs_dir = 'testDirectory'
813 #ifdef WRF_HYDRO_NUDGING
814     nlst(did)%nudgingParamFile       = nudgingParamFile
815     write(*,*) 'Nudging param file ',nudgingParamFile
816     nlst(did)%netWkReExFile          = netWkReExFile
817     nlst(did)%readTimesliceParallel  = readTimesliceParallel
818     nlst(did)%temporalPersistence    = temporalPersistence
819     nlst(did)%persistBias            = persistBias
820     nlst(did)%biasWindowBeforeT0     = biasWindowBeforeT0
821     nlst(did)%nudgingLastObsFile     = nudgingLastObsFile
822     nlst(did)%timeSlicePath          = timeSlicePath
823     nlst(did)%nLastObs               = nLastObs
824     nlst(did)%minNumPairsBiasPersist = minNumPairsBiasPersist
825     nlst(did)%maxAgePairsBiasPersist = maxAgePairsBiasPersist
826     nlst(did)%invDistTimeWeightBias  = invDistTimeWeightBias
827     nlst(did)%noConstInterfBias      = noConstInterfBias
828 #endif
830     call nlst(did)%check()
832     ! derive rtFlag
833     nlst(did)%rtFlag = 1
834     if(channel_option .eq. 4) nlst(did)%rtFlag = 0
835     !      if(CHANRTSWCRT .eq. 0 .and.  SUBRTSWCRT .eq. 0 .and. OVRTSWCRT .eq. 0 .and. GWBASESWCRT .eq. 0) nlst(did)%rtFlag = 0
836     if(SUBRTSWCRT .eq. 0 .and. OVRTSWCRT .eq. 0 .and. GWBASESWCRT .eq. 0) nlst(did)%rtFlag = 0
838   end subroutine init_namelist_rt_field
840   subroutine init_wrf_hydro()
841     implicit none
843     integer  :: ierr
844     integer  :: finemesh, finemesh_factor
845     integer  :: forc_typ, snow_assim
847     namelist /WRF_HYDRO_OFFLINE/ &
848          !LRK - Remove HRLDAS_ini_typ and GEO_STATIC_FLNM for WRF-Hydro
849          finemesh,finemesh_factor,forc_typ, snow_assim
850     !finemesh,finemesh_factor,forc_typ, snow_assim , GEO_STATIC_FLNM, HRLDAS_ini_typ
852 #ifndef NCEP_WCOSS
853     read(30, NML=WRF_HYDRO_OFFLINE, iostat=ierr)
854 #else
855     read(11, NML=WRF_HYDRO_OFFLINE, iostat=ierr)
856 #endif
857     if (ierr /= 0) then
858        write(*,'(/," ***** ERROR: Problem reading namelist WRF_HYDRO_OFFLINE",/)')
859        call hydro_stop (" FATAL ERROR: Problem reading namelist WRF_HYDRO_OFFLINE")
860     endif
862 #ifndef NCEP_WCOSS
863     close(30)
864 #else
865     close(11)
866 #endif
868     wrf_hydro%finemesh = finemesh
869     wrf_hydro%finemesh_factor = finemesh_factor
870     wrf_hydro%forc_typ = forc_typ
871     wrf_hydro%snow_assim = snow_assim
873   end subroutine init_wrf_hydro
875   subroutine init_noah_lsm_and_wrf_hydro()
876     implicit none
877      character(len=256) :: indir
878      integer            :: nsoil ! number of soil layers
879      type(crocus_options) :: crocus_opts
880      integer            :: forcing_timestep
881      integer            :: noah_timestep
882      integer            :: start_year
883      integer            :: start_month
884      integer            :: start_day
885      integer            :: start_hour
886      integer            :: start_min
887      character(len=256) :: outdir = "."
888      character(len=256) :: restart_filename_requested = " "
889      integer            :: restart_frequency_hours
890      integer            :: output_timestep
891      integer            :: dynamic_veg_option
892      integer            :: canopy_stomatal_resistance_option
893      integer            :: btr_option
894      integer            :: runoff_option
895      integer            :: surface_drag_option
896      integer            :: supercooled_water_option
897      integer            :: frozen_soil_option
898      integer            :: radiative_transfer_option
899      integer            :: snow_albedo_option
900      integer            :: pcp_partition_option
901      integer            :: tbot_option
902      integer            :: temp_time_scheme_option
903      integer            :: glacier_option
904      integer            :: surface_resistance_option
905      integer            :: soil_data_option = 1
906      integer            :: pedotransfer_option = 0
907      integer            :: crop_option = 0
908      integer            :: imperv_option = 9
909      integer            :: split_output_count = 1
910      integer            :: khour = -999
911      integer            :: kday = -999
912      real               :: zlvl
913      character(len=256) :: hrldas_setup_file = " "
914      character(len=256) :: mmf_runoff_file = " "
915      character(len=256) :: external_veg_filename_template = " "
916      character(len=256) :: external_lai_filename_template = " "
917      integer            :: xstart = 1
918      integer            :: ystart = 1
919      integer            :: xend = 0
920      integer            :: yend = 0
921      REAL, DIMENSION(MAX_SOIL_LEVELS) :: soil_thick_input       ! depth to soil interfaces from namelist [m]
922      integer :: rst_bi_out, rst_bi_in !0: default netcdf format. 1: binary write/read by each core.
923      CHARACTER(LEN = 256)                    ::  spatial_filename
924      integer :: ierr = 0
926     integer  :: finemesh, finemesh_factor
927     integer  :: forc_typ, snow_assim
929     namelist / NOAHLSM_OFFLINE /    &
930          indir, nsoil, soil_thick_input, forcing_timestep, noah_timestep, &
931          start_year, start_month, start_day, start_hour, start_min, &
932          outdir, &
933          restart_filename_requested, restart_frequency_hours, output_timestep, &
935          dynamic_veg_option, canopy_stomatal_resistance_option, &
936          btr_option, runoff_option, surface_drag_option, supercooled_water_option, &
937          frozen_soil_option, radiative_transfer_option, snow_albedo_option, &
938          pcp_partition_option, tbot_option, temp_time_scheme_option, &
939          glacier_option, surface_resistance_option, &
941          soil_data_option, pedotransfer_option, crop_option, &
942          imperv_option, &
944          split_output_count, &
945          khour, kday, zlvl, hrldas_setup_file, mmf_runoff_file, &
946          spatial_filename, &
947          external_veg_filename_template, external_lai_filename_template, &
948          xstart, xend, ystart, yend, rst_bi_out, rst_bi_in
950     namelist /WRF_HYDRO_OFFLINE/ &
951          finemesh,finemesh_factor,forc_typ, snow_assim
953     noah_lsm%nsoil                   = -999
954     noah_lsm%soil_thick_input        = -999
955     ! dtbl                             = -999
956     noah_lsm%start_year              = -999
957     noah_lsm%start_month             = -999
958     noah_lsm%start_day               = -999
959     noah_lsm%start_hour              = -999
960     noah_lsm%start_min               = -999
961     noah_lsm%khour                   = -999
962     noah_lsm%kday                    = -999
963     noah_lsm%zlvl                    = -999
964     noah_lsm%forcing_timestep        = -999
965     noah_lsm%noah_timestep           = -999
966     noah_lsm%output_timestep         = -999
967     noah_lsm%restart_frequency_hours = -999
969     write(*,*) 'Calling config noahlsm_offline'
971 #ifndef NCEP_WCOSS
972     open(30, file="namelist.hrldas", form="FORMATTED")
973     read(30, NML=NOAHLSM_OFFLINE, iostat=ierr)
974 #else
975     open(11, form="FORMATTED")
976     read(11, NML=NOAHLSM_OFFLINE, iostat=ierr)
977 #endif
979     if (ierr /= 0) then
980        write(*,'(/," ***** ERROR: Problem reading namelist NOAHLSM_OFFLINE",/)')
981 #ifndef NCEP_WCOSS
982        rewind(30)
983        read(30, NOAHLSM_OFFLINE)
984 #else
985             rewind(11)
986             read(11, NOAHLSM_OFFLINE)
987 #endif
988        stop "FATAL ERROR: Problem reading namelist NOAHLSM_OFFLINE"
989     endif
991 #ifndef NCEP_WCOSS
992     read(30, NML=WRF_HYDRO_OFFLINE, iostat=ierr)
993 #else
994     read(11, NML=WRF_HYDRO_OFFLINE, iostat=ierr)
995 #endif
996     if (ierr /= 0) then
997        write(*,'(/," ***** ERROR: Problem reading namelist WRF_HYDRO_OFFLINE",/)')
998        call hydro_stop (" FATAL ERROR: Problem reading namelist WRF_HYDRO_OFFLINE")
999     endif
1001 #ifndef NCEP_WCOSS
1002     call read_crocus_namelist(crocus_opts, 30)
1003 #else
1004     call read_crocus_namelist(crocus_opts, 11)
1005 #endif
1007 #ifndef NCEP_WCOSS
1008     close(30)
1009 #else
1010     close(11)
1011 #endif
1013     wrf_hydro%finemesh = 0!finemesh
1014     wrf_hydro%finemesh_factor = 0!finemesh_factor
1015     wrf_hydro%forc_typ = forc_typ
1016     wrf_hydro%snow_assim = 0!snow_assim
1018     noah_lsm%indir = indir
1019     noah_lsm%nsoil = nsoil ! number of soil layers
1020     noah_lsm%crocus_opt = crocus_opts%crocus_opt
1021     noah_lsm%act_lev = crocus_opts%act_lev
1022     noah_lsm%forcing_timestep = forcing_timestep
1023     noah_lsm%noah_timestep = noah_timestep
1024     noah_lsm%start_year = start_year
1025     noah_lsm%start_month = start_month
1026     noah_lsm%start_day = start_day
1027     noah_lsm%start_hour = start_hour
1028     noah_lsm%start_min = start_min
1029     noah_lsm%outdir = outdir
1030     noah_lsm%restart_filename_requested = restart_filename_requested
1031     noah_lsm%restart_frequency_hours = restart_frequency_hours
1032     noah_lsm%output_timestep = output_timestep
1033     noah_lsm%dynamic_veg_option = dynamic_veg_option
1034     noah_lsm%canopy_stomatal_resistance_option = canopy_stomatal_resistance_option
1035     noah_lsm%btr_option = btr_option
1036     noah_lsm%runoff_option = runoff_option
1037     noah_lsm%surface_drag_option = surface_drag_option
1038     noah_lsm%supercooled_water_option = supercooled_water_option
1039     noah_lsm%frozen_soil_option = frozen_soil_option
1040     noah_lsm%radiative_transfer_option = radiative_transfer_option
1041     noah_lsm%snow_albedo_option = snow_albedo_option
1042     noah_lsm%pcp_partition_option = pcp_partition_option
1043     noah_lsm%tbot_option = tbot_option
1044     noah_lsm%temp_time_scheme_option = temp_time_scheme_option
1045     noah_lsm%glacier_option = glacier_option
1046     noah_lsm%surface_resistance_option = surface_resistance_option
1048     noah_lsm%soil_data_option = soil_data_option
1049     noah_lsm%pedotransfer_option = pedotransfer_option
1050     noah_lsm%crop_option = crop_option
1051     noah_lsm%imperv_option = imperv_option
1053     noah_lsm%split_output_count = split_output_count
1055     if (kday > 0) then
1056         if (khour > 0) then
1057             write(*, '("WARNING: Check Namelist: KHOUR and KDAY both defined, KHOUR will take precedence.")')
1058             kday = -999
1059         else
1060             write(*, '("WARNING: KDAY is deprecated and may be removed in a future version, please use KHOUR.")')
1061             khour = -999
1062         end if
1063     end if
1064     noah_lsm%kday = kday
1065     noah_lsm%khour = khour
1067     noah_lsm%zlvl = zlvl
1068     noah_lsm%hrldas_setup_file = hrldas_setup_file
1069     noah_lsm%mmf_runoff_file = " "!mmf_runoff_file
1070     noah_lsm%external_veg_filename_template = " "!external_veg_filename_template
1071     noah_lsm%external_lai_filename_template = " "!external_lai_filename_template
1072     noah_lsm%xstart = 1!xstart
1073     noah_lsm%ystart = 1!ystart
1074     noah_lsm%xend = 0!xend
1075     noah_lsm%yend = 0!yend
1076     noah_lsm%soil_thick_input = soil_thick_input
1077     noah_lsm%rst_bi_out = rst_bi_out
1078     noah_lsm%rst_bi_in = rst_bi_in
1079     noah_lsm%spatial_filename = spatial_filename
1081   end subroutine init_noah_lsm_and_wrf_hydro
1083   subroutine read_crocus_namelist(opt, f_in)
1084     type(crocus_options), intent(OUT) :: opt
1085     integer, intent(IN), optional :: f_in
1086     character(len=15) :: filename = "namelist.hrldas"
1087     logical :: f_exists
1088     integer :: crocus_opt, act_lev
1089     integer :: ierr, f_local
1090     namelist /CROCUS_nlist/ &
1091          crocus_opt, act_lev
1093     ! check if file is opened
1094     if (present(f_in)) then
1095        rewind(f_in)
1096        read(f_in, NML=CROCUS_nlist, iostat=ierr)
1097     else
1098        ! check that file exists
1099        inquire(file=filename, exist=f_exists)
1100        if (f_exists .eqv. .false.) &
1101            call hydro_stop (" FATAL ERROR: namelist.hrldas does not exist")
1102        open(newunit=f_local, file=filename, form="FORMATTED", iostat=ierr)
1103        read(f_local, NML=CROCUS_nlist, iostat=ierr)
1104        close(f_local)
1105     end if
1107     if ((ierr .ne. 0) .or. (crocus_opt .eq. 0)) &
1108          return
1109     if ((act_lev .gt. 50) .or. (act_lev .lt. 0)) then
1110        call hydro_stop (" FATAL ERROR: Crocus act_lev out of range of 0-50 ")
1111     end if
1113     opt%crocus_opt = crocus_opt
1114     if (crocus_opt == 0) then
1115        opt%act_lev = 0
1116     else
1117        opt%act_lev = act_lev
1118     end if
1119   end subroutine read_crocus_namelist
1121 end module config_base