5.13.2-dev0
mHM
The mesoscale Hydrological Model
Loading...
Searching...
No Matches
mo_mhm_read_config.f90
Go to the documentation of this file.
1!> \file mo_mhm_read_config.f90
2!> \brief \copybrief mo_mhm_read_config
3!> \details \copydetails mo_mhm_read_config
4
5!> \brief Reading of main model configurations.
6!> \details This routine reads the configurations of mHM including, input and
7!! output directories, module usage specification, simulation time periods,
8!! global parameters, ...
9!> \authors Matthias Zink
10!> \date Dec 2012
11!> \copyright Copyright 2005-\today, the mHM Developers, Luis Samaniego, Sabine Attinger: All rights reserved.
12!! mHM is released under the LGPLv3+ license \license_note
13!> \ingroup f_mhm
15
16 USE mo_kind, ONLY : i4, dp
17 use mo_message, only: message, error_message
18
19 IMPLICIT NONE
20
21 PRIVATE
22
23 PUBLIC :: mhm_read_config ! read main directories
24
25 ! ------------------------------------------------------------------
26
27CONTAINS
28
29 ! ------------------------------------------------------------------
30
31 ! NAME
32 ! mhm_read_config
33
34 ! PURPOSE
35 !> \brief Read main configurations for mHM
36
37 !> \details The main configurations in mHM are read from three files:
38 !> <ol>
39 !> <li> mhm.nml
40 !> <li> mhm_parameters.nml
41 !> <li> mhm_outputs.nml
42 !> </ol>
43 !> For details please refer to the above mentioned namelist files.
44
45 ! INTENT(IN)
46 !> \param[in] "character(*) :: file_namelist"
47 !> \param[in] "integer :: unamelist"
48
49 ! HISTORY
50 !> \authors Matthias Zink
51
52 !> \date Dec 2012
53
54 ! Modifications:
55 ! Luis Samaniego Jan 2013 - messages Rohini Kumar
56 ! Matthias Cuntz Jan 2013 - namelist consolidation and positioning
57 ! Matthias Zink Jan 2013 - bug fix, added gaugeinfo reading
58 ! Rohini Kumar Jun 2013 - added restart flags
59 ! R. Kumar & S. Thober Aug 2013 - code change to incorporate output timestep during
60 ! writing of the netcdf file
61 ! Rohini Kumar Aug 2013 - name changed from "inputFormat" to inputFormat_meteo_forcings
62 ! Rohini Kumar Aug 2013 - added dirSoil_LUT and dirGeology_LUT, and changed
63 ! in namelist made accordingly
64 ! Rohini Kumar Aug 2013 - added new namelist for LAI related datasets, and changed in within
65 ! the code made accordingly
66 ! Matthias Zink Aug 2013 - changed read in for land cover period
67 ! Juliane Mai Oct 2013 - adding global_parameters_name
68 ! Matthias Zink Nov 2013 - edited documentation and included DEFAULT cases for ptocess Matrix
69 ! Stephan Thober Nov 2013 - added read of directories where latitude longitude fields are located
70 ! Matthias Zink Feb 2014 - added multiple options for PET process
71 ! Matthias Zink Mar 2014 - added inflow from upstream areas and gauge information as namelist
72 ! Rohini Kumar May 2014 - added options for the model run coordinate system
73 ! Stephan Thober May 2014 - added switch for chunk read in
74 ! Stephan Thober Jun 2014 - added option for switching off mpr
75 ! Matthias Cuntz & Juliane Mai Nov 2014 - LAI input from daily, monthly or yearly files
76 ! Matthias Zink Dec 2014 - adopted inflow gauges to ignore headwater cells
77 ! Matthias Zink Mar 2015 - added optional soil moisture read in for calibration
78 ! Matthias Cuntz Jul 2015 - removed adjustl from trim(adjustl()) of Geoparams for PGI compatibilty
79 ! Stephan Thober Aug 2015 - added read_config_routing and read_routing_params from mRM
80 ! Oldrich Rakovec Oct 2015 - added reading of the domain average TWS data
81 ! Rohini Kumar Mar 2016 - options to handle different soil databases
82 ! Stephan Thober Nov 2016 - moved nProcesses and processMatrix to common variables
83 ! Rohini Kumar Dec 2016 - option to handle monthly mean gridded fields of LAI
84 ! M.Zink & M. Cuneyd Demirel Mar 2017 - Added Jarvis soil water stress function at SM process(3)
85 ! M.C. Demirel & Simon Stisen Apr 2017 - Added FC dependency on root fraction coefficient (ET) at SM process(3)
86 ! Robert Schweppe Dec 2017 - switched from fractional julian day to integer
87 ! Robert Schweppe Jun 2018 - refactoring and reformatting
88
89 subroutine mhm_read_config(file_namelist, unamelist)
90
96 use mo_global_variables, only : &
98 evap_coeff, &
105 use mo_nml, only : close_nml, open_nml, position_nml
106 use mo_string_utils, only : num2str
107
108 implicit none
109
110 character(*), intent(in) :: file_namelist
111
112 integer, intent(in) :: unamelist
113
114 integer(i4) :: idomain, domainid
115
116 ! soil moisture input
117 character(256), dimension(maxNoDomains) :: dir_soil_moisture
118
119 ! ground albedo neutron input
120 character(256), dimension(maxNoDomains) :: dir_neutrons
121
122 ! evapotranspiration input
123 character(256), dimension(maxNoDomains) :: dir_evapotranspiration
124
125 ! tws input
126 character(256), dimension(maxNoDomains) :: dir_tws
127
128 integer(i4) :: timestep_tws_input ! time step of optional data: tws
129 integer(i4) :: timestep_et_input ! time step of optional data: et
130 integer(i4) :: timestep_sm_input ! time step of optional data: sm
131 integer(i4) :: timestep_neutrons_input ! time step of optional data: neutrons
132
133
134 ! define namelists
135 ! optional data used for optimization
136 namelist /optional_data/ &
137 dir_soil_moisture, &
139 dir_neutrons, &
140 dir_evapotranspiration, &
141 dir_tws, &
142 timestep_sm_input, &
143 timestep_neutrons_input, &
144 timestep_et_input, &
145 timestep_tws_input
146 ! namelist for pan evaporation
147 namelist /panevapo/evap_coeff
148
149 ! name list regarding output
150 namelist /nloutputresults/ &
156 ! namelist for baseflow index optimzation
157 namelist /baseflow_config/ bfi_calc, bfi_obs
158
159 !===============================================================
160 ! Read namelist main directories
161 !===============================================================
162 call open_nml(file_namelist, unamelist, quiet = .true.)
163
164 allocate(l1_twsaobs(domainmeta%nDomains))
165 allocate(l1_etobs(domainmeta%nDomains))
166 allocate(l1_smobs(domainmeta%nDomains))
167 allocate(l1_neutronsobs(domainmeta%nDomains))
168 ! observed baseflow indizes
169 allocate(bfi_obs(domainmeta%nDomains))
170 bfi_obs = -1.0_dp ! negative value to flag missing values
171 bfi_calc = .false.
172
173 !===============================================================
174 ! Read namelist of optional input data
175 !===============================================================
176 ! read optional optional data if necessary
177 if (optimize) then
178 select case (opti_function)
179 case(10 : 13, 28)
180 ! soil moisture
181 call position_nml('optional_data', unamelist)
182 read(unamelist, nml = optional_data)
183 do idomain = 1, domainmeta%nDomains
184 domainid = domainmeta%indices(idomain)
185 l1_smobs(idomain)%dir = dir_soil_moisture(domainid)
186 l1_smobs(idomain)%timeStepInput = timestep_sm_input
187 l1_smobs(idomain)%varname = 'sm'
188 end do
190 call error_message('***ERROR: Number of soil horizons representative for input soil moisture exceeded', raise=.false.)
191 call error_message(' defined number of soil horizions: ', adjustl(trim(num2str(maxnosoilhorizons))), '!')
192 end if
193 case(17)
194 ! neutrons
195 call position_nml('optional_data', unamelist)
196 read(unamelist, nml = optional_data)
197 do idomain = 1, domainmeta%nDomains
198 domainid = domainmeta%indices(idomain)
199 l1_neutronsobs(idomain)%dir = dir_neutrons(domainid)
200 l1_neutronsobs(idomain)%timeStepInput = timestep_neutrons_input
201 l1_neutronsobs(idomain)%timeStepInput = -1 ! TODO: daily, hard-coded, to be flexibilized
202 l1_neutronsobs(idomain)%varname = 'neutrons'
203 end do
204 case(27, 29, 30)
205 ! evapotranspiration
206 call position_nml('optional_data', unamelist)
207 read(unamelist, nml = optional_data)
208 do idomain = 1, domainmeta%nDomains
209 domainid = domainmeta%indices(idomain)
210 l1_etobs(idomain)%dir = dir_evapotranspiration(domainid)
211 l1_etobs(idomain)%timeStepInput = timestep_et_input
212 l1_etobs(idomain)%varname = 'et'
213 end do
214 case(15)
215 ! domain average TWS data
216 call position_nml('optional_data', unamelist)
217 read(unamelist, nml = optional_data)
218 do idomain = 1, domainmeta%nDomains
219 domainid = domainmeta%indices(idomain)
220 l1_twsaobs(idomain)%dir = dir_tws(domainid)
221 l1_twsaobs(idomain)%timeStepInput = timestep_tws_input
222 l1_twsaobs(idomain)%varname = 'twsa'
223 end do
224 case(33)
225 ! evapotranspiration
226 call position_nml('optional_data', unamelist)
227 read(unamelist, nml = optional_data)
228 do idomain = 1, domainmeta%nDomains
229 domainid = domainmeta%indices(idomain)
230 l1_etobs(idomain)%dir = dir_evapotranspiration(domainid)
231 l1_etobs(idomain)%timeStepInput = timestep_et_input
232 l1_etobs(idomain)%varname = 'et'
233 end do
234
235 ! domain average TWS data
236 call position_nml('optional_data', unamelist)
237 read(unamelist, nml = optional_data)
238 do idomain = 1, domainmeta%nDomains
239 domainid = domainmeta%indices(idomain)
240 l1_twsaobs(idomain)%dir = dir_tws(domainid)
241 l1_twsaobs(idomain)%timeStepInput = timestep_tws_input
242 l1_twsaobs(idomain)%varname = 'twsa'
243 end do
244
245 case(34)
246 !baseflow index optimization
247 call position_nml('baseflow_config', unamelist)
248 read(unamelist, nml = baseflow_config)
249
250 end select
251 end if
252
253 !===============================================================
254 ! Read pan evaporation
255 !===============================================================
256 ! Evap. coef. for free-water surfaces
257 call position_nml('panEvapo', unamelist)
258 read(unamelist, nml = panevapo)
259
260 call common_check_resolution(.true., .false.)
261
262 call close_nml(unamelist)
263
264 !===============================================================
265 ! Read output specifications for mHM
266 !===============================================================
267 call open_nml(file_defoutput, udefoutput, quiet = .true.)
271 outputflxstate = .false.
272 call position_nml('NLoutputResults', udefoutput)
273 read(udefoutput, nml = nloutputresults)
274 call close_nml(udefoutput)
275
276 call message('')
277 call message('Following output will be written:')
278 call message(' NetCDF deflate level: ', adjustl(trim(num2str(output_deflate_level))))
279 if ( output_double_precision ) then
280 call message(' NetCDF output precision: double')
281 else
282 call message(' NetCDF output precision: single')
283 end if
284 select case(output_time_reference)
285 case(0)
286 call message(' NetCDF output time reference point: start of time interval')
287 case(1)
288 call message(' NetCDF output time reference point: center of time interval')
289 case(2)
290 call message(' NetCDF output time reference point: end of time interval')
291 end select
292 call message(' STATES:')
293 if (outputflxstate(1)) then
294 call message(' interceptional storage (L1_inter) [mm]')
295 end if
296 if (outputflxstate(2)) then
297 call message(' height of snowpack (L1_snowpack) [mm]')
298 end if
299 if (outputflxstate(3)) then
300 call message(' soil water content in the single layers (L1_soilMoist) [mm]')
301 end if
302 if (outputflxstate(4)) then
303 call message(' volumetric soil moisture in the single layers [mm/mm]')
304 end if
305 if (outputflxstate(5)) then
306 call message(' mean volum. soil moisture averaged over all soil layers [mm/mm]')
307 end if
308 if (outputflxstate(6)) then
309 call message(' waterdepth in reservoir of sealed areas (L1_sealSTW) [mm]')
310 end if
311 if (outputflxstate(7)) then
312 call message(' waterdepth in reservoir of unsat. soil zone (L1_unsatSTW) [mm]')
313 end if
314 if (outputflxstate(8)) then
315 call message(' waterdepth in reservoir of sat. soil zone (L1_satSTW) [mm]')
316 end if
317 if (processmatrix(10, 1) .eq. 0) outputflxstate(18) = .false. ! suppress output if process is off
318 if (outputflxstate(18)) then
319 call message(' ground albedo neutrons (L1_neutrons) [cph]')
320 end if
321
322 call message(' FLUXES:')
323 if (outputflxstate(9)) then
324 call message(' potential evapotranspiration PET (L1_pet) [mm/T]')
325 end if
326 if (outputflxstate(10)) then
327 call message(' actual evapotranspiration aET (L1_aETCanopy) [mm/T]')
328 end if
329 if (outputflxstate(11)) then
330 call message(' total discharge generated per cell (L1_total_runoff) [mm/T]')
331 end if
332 if (outputflxstate(12)) then
333 call message(' direct runoff generated per cell (L1_runoffSeal) [mm/T]')
334 end if
335 if (outputflxstate(13)) then
336 call message(' fast interflow generated per cell (L1_fastRunoff) [mm/T]')
337 end if
338 if (outputflxstate(14)) then
339 call message(' slow interflow generated per cell (L1_slowRunoff) [mm/T]')
340 end if
341 if (outputflxstate(15)) then
342 call message(' baseflow generated per cell (L1_baseflow) [mm/T]')
343 end if
344 if (outputflxstate(16)) then
345 call message(' groundwater recharge (L1_percol) [mm/T]')
346 end if
347 if (outputflxstate(17)) then
348 call message(' infiltration (L1_infilSoil) [mm/T]')
349 end if
350 if (outputflxstate(19)) then
351 call message(' actual evapotranspiration from soil layers (L1_aETSoil) [mm/T]')
352 end if
353 if (outputflxstate(20)) then
354 call message(' effective precipitation (L1_preEffect) [mm/T]')
355 end if
356 if (outputflxstate(21)) then
357 call message(' snow melt (L1_melt) [mm/T]')
358 end if
359 call message('')
360 call message('FINISHED reading config')
361
362 ! warning message
363 if (any(outputflxstate) .and. optimize) then
364 call message('WARNING: FLUXES and STATES netCDF will be not written since optimization flag is TRUE ')
365 end if
366
367 end subroutine mhm_read_config
368
369END MODULE mo_mhm_read_config
Provides constants commonly used by mHM, mRM and MPR.
integer(i4), parameter, public maxnodomains
integer(i4), parameter, public nodata_i4
Reading of main model configurations.
subroutine, public common_check_resolution(do_message, allow_subgrid_routing)
check resolution
Provides structures needed by mHM, mRM and/or mpr.
Provides structures needed by mHM, mRM and/or mpr.
type(domain_meta), public domainmeta
integer(i4), dimension(nprocesses, 3), public processmatrix
Provides file names and units for mHM.
Definition mo_file.F90:29
integer, parameter udefoutput
Unit for file defining mHM's outputs.
Definition mo_file.F90:52
character(:), allocatable file_defoutput
file defining mHM's outputs
Definition mo_file.F90:50
Main global variables for mHM.
logical, dimension(noutflxstate) outputflxstate
Define model outputs see "mhm_outputs.nml" dim1 = number of output variables to be written.
type(optidata), dimension(:), allocatable, public l1_twsaobs
this stores L1_tws, the mask, the directory of the observerd data, and the timestepInput of the simul...
logical, public bfi_calc
calculate observed BFI from gauges with Eckhardt filter
type(optidata), dimension(:), allocatable, public l1_neutronsobs
type(optidata), dimension(:), allocatable, public l1_smobs
integer(i4) timestep_model_outputs
timestep for writing model outputs
integer(i4) output_deflate_level
deflate level in nc files
logical output_double_precision
output precision in nc files
integer(i4) output_time_reference
time reference point location in output nc files
real(dp), dimension(int(yearmonths, i4)), public evap_coeff
[-] Evap.
type(optidata), dimension(:), allocatable, public l1_etobs
real(dp), dimension(:), allocatable, public bfi_obs
given base-flow index per domain
Reading of main model configurations.
subroutine, public mhm_read_config(file_namelist, unamelist)
Read main configurations for mHM.
Provides MPR specific constants.
integer(i4), parameter, public maxnosoilhorizons
Global variables for mpr only.
integer(i4), public nsoilhorizons_mhm