Line data Source code
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
14 : MODULE mo_mhm_read_config
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 :
27 : CONTAINS
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 :
48 : ! HISTORY
49 : !> \authors Matthias Zink
50 :
51 : !> \date Dec 2012
52 :
53 : ! Modifications:
54 : ! Luis Samaniego Jan 2013 - messages Rohini Kumar
55 : ! Matthias Cuntz Jan 2013 - namelist consolidation and positioning
56 : ! Matthias Zink Jan 2013 - bug fix, added gaugeinfo reading
57 : ! Rohini Kumar Jun 2013 - added restart flags
58 : ! R. Kumar & S. Thober Aug 2013 - code change to incorporate output timestep during
59 : ! writing of the netcdf file
60 : ! Rohini Kumar Aug 2013 - name changed from "inputFormat" to inputFormat_meteo_forcings
61 : ! Rohini Kumar Aug 2013 - added dirSoil_LUT and dirGeology_LUT, and changed
62 : ! in namelist made accordingly
63 : ! Rohini Kumar Aug 2013 - added new namelist for LAI related datasets, and changed in within
64 : ! the code made accordingly
65 : ! Matthias Zink Aug 2013 - changed read in for land cover period
66 : ! Juliane Mai Oct 2013 - adding global_parameters_name
67 : ! Matthias Zink Nov 2013 - edited documentation and included DEFAULT cases for ptocess Matrix
68 : ! Stephan Thober Nov 2013 - added read of directories where latitude longitude fields are located
69 : ! Matthias Zink Feb 2014 - added multiple options for PET process
70 : ! Matthias Zink Mar 2014 - added inflow from upstream areas and gauge information as namelist
71 : ! Rohini Kumar May 2014 - added options for the model run coordinate system
72 : ! Stephan Thober May 2014 - added switch for chunk read in
73 : ! Stephan Thober Jun 2014 - added option for switching off mpr
74 : ! Matthias Cuntz & Juliane Mai Nov 2014 - LAI input from daily, monthly or yearly files
75 : ! Matthias Zink Dec 2014 - adopted inflow gauges to ignore headwater cells
76 : ! Matthias Zink Mar 2015 - added optional soil moisture read in for calibration
77 : ! Matthias Cuntz Jul 2015 - removed adjustl from trim(adjustl()) of Geoparams for PGI compatibilty
78 : ! Stephan Thober Aug 2015 - added read_config_routing and read_routing_params from mRM
79 : ! Oldrich Rakovec Oct 2015 - added reading of the domain average TWS data
80 : ! Rohini Kumar Mar 2016 - options to handle different soil databases
81 : ! Stephan Thober Nov 2016 - moved nProcesses and processMatrix to common variables
82 : ! Rohini Kumar Dec 2016 - option to handle monthly mean gridded fields of LAI
83 : ! M.Zink & M. Cuneyd Demirel Mar 2017 - Added Jarvis soil water stress function at SM process(3)
84 : ! M.C. Demirel & Simon Stisen Apr 2017 - Added FC dependency on root fraction coefficient (ET) at SM process(3)
85 : ! Robert Schweppe Dec 2017 - switched from fractional julian day to integer
86 : ! Robert Schweppe Jun 2018 - refactoring and reformatting
87 :
88 14 : subroutine mhm_read_config(file_namelist)
89 :
90 : use mo_namelists, only : &
91 : nml_optional_data, &
92 : nml_panEvapo, &
93 : nml_NLoutputResults, &
94 : nml_baseflow_config
95 : use mo_common_constants, only : maxNoDomains, nodata_i4
96 : use mo_common_mHM_mRM_read_config, only : common_check_resolution
97 : use mo_common_mhm_mrm_variables, only : opti_function, optimize
98 : use mo_common_variables, only : domainMeta, processMatrix
99 : use mo_file, only : file_defOutput
100 : use mo_global_variables, only : &
101 : L1_twsaObs, L1_etObs, L1_smObs, L1_neutronsObs, &
102 : evap_coeff, &
103 : nSoilHorizons_sm_input, outputFlxState, &
104 : timeStep_model_outputs, &
105 : output_deflate_level, output_double_precision, output_time_reference, &
106 : BFI_calc, BFI_obs
107 : use mo_mpr_constants, only : maxNoSoilHorizons
108 : use mo_mpr_global_variables, only : nSoilHorizons_mHM
109 : use mo_string_utils, only : num2str
110 :
111 : implicit none
112 :
113 : character(*), intent(in) :: file_namelist
114 :
115 : integer(i4) :: iDomain, domainID
116 :
117 : ! soil moisture input
118 : character(256), dimension(maxNoDomains) :: dir_soil_moisture
119 :
120 : ! ground albedo neutron input
121 : character(256), dimension(maxNoDomains) :: dir_neutrons
122 :
123 : ! evapotranspiration input
124 : character(256), dimension(maxNoDomains) :: dir_evapotranspiration
125 :
126 : ! tws input
127 : character(256), dimension(maxNoDomains) :: dir_TWS
128 :
129 : integer(i4) :: timeStep_tws_input ! time step of optional data: tws
130 : integer(i4) :: timeStep_et_input ! time step of optional data: et
131 : integer(i4) :: timeStep_sm_input ! time step of optional data: sm
132 : integer(i4) :: timeStep_neutrons_input ! time step of optional data: neutrons
133 :
134 :
135 68 : allocate(L1_twsaObs(domainMeta%nDomains))
136 68 : allocate(L1_etObs(domainMeta%nDomains))
137 68 : allocate(L1_smObs(domainMeta%nDomains))
138 68 : allocate(L1_neutronsObs(domainMeta%nDomains))
139 : ! observed baseflow indizes
140 42 : allocate(BFI_obs(domainMeta%nDomains))
141 :
142 : !===============================================================
143 : ! Read namelist of optional input data
144 : !===============================================================
145 : ! read optional optional data if necessary
146 14 : if (optimize) then
147 : ! read nml
148 4 : select case (opti_function)
149 : case(10 : 13, 15, 17, 27 : 30, 33)
150 4 : call nml_optional_data%read(file_namelist)
151 4 : nSoilHorizons_sm_input = nml_optional_data%nSoilHorizons_sm_input
152 204 : dir_soil_moisture = nml_optional_data%dir_soil_moisture
153 204 : dir_neutrons = nml_optional_data%dir_neutrons
154 204 : dir_evapotranspiration = nml_optional_data%dir_evapotranspiration
155 204 : dir_TWS = nml_optional_data%dir_TWS
156 4 : timeStep_sm_input = nml_optional_data%timeStep_sm_input
157 4 : timeStep_neutrons_input = nml_optional_data%timeStep_neutrons_input
158 4 : timeStep_et_input = nml_optional_data%timeStep_et_input
159 4 : timeStep_tws_input = nml_optional_data%timeStep_tws_input
160 : case(34)
161 0 : call nml_baseflow_config%read(file_namelist)
162 0 : BFI_calc = nml_baseflow_config%BFI_calc
163 5 : BFI_obs = nml_baseflow_config%BFI_obs(1:size(BFI_obs))
164 : end select
165 :
166 1 : select case (opti_function)
167 : case(10 : 13, 28)
168 : ! soil moisture
169 2 : do iDomain = 1, domainMeta%nDomains
170 1 : domainID = domainMeta%indices(iDomain)
171 1 : L1_smObs(iDomain)%dir = dir_Soil_moisture(domainID)
172 1 : L1_smObs(iDomain)%timeStepInput = timeStep_sm_input
173 2 : L1_smObs(iDomain)%varname = 'sm'
174 : end do
175 1 : if (nSoilHorizons_sm_input .GT. nSoilHorizons_mHM) then
176 0 : call error_message('***ERROR: Number of soil horizons representative for input soil moisture exceeded', raise=.false.)
177 0 : call error_message(' defined number of soil horizions: ', adjustl(trim(num2str(maxNoSoilHorizons))), '!')
178 : end if
179 : case(17)
180 : ! neutrons
181 2 : do iDomain = 1, domainMeta%nDomains
182 1 : domainID = domainMeta%indices(iDomain)
183 1 : L1_neutronsObs(iDomain)%dir = dir_neutrons(domainID)
184 1 : L1_neutronsObs(iDomain)%timeStepInput = timeStep_neutrons_input
185 1 : L1_neutronsObs(iDomain)%timeStepInput = -1 ! TODO: daily, hard-coded, to be flexibilized
186 2 : L1_neutronsObs(iDomain)%varname = 'neutrons'
187 : end do
188 : case(27, 29, 30)
189 : ! evapotranspiration
190 0 : do iDomain = 1, domainMeta%nDomains
191 0 : domainID = domainMeta%indices(iDomain)
192 0 : L1_etObs(iDomain)%dir = dir_evapotranspiration(domainID)
193 0 : L1_etObs(iDomain)%timeStepInput = timeStep_et_input
194 0 : L1_etObs(iDomain)%varname = 'et'
195 : end do
196 : case(15)
197 : ! domain average TWS data
198 2 : do iDomain = 1, domainMeta%nDomains
199 1 : domainID = domainMeta%indices(iDomain)
200 1 : L1_twsaObs(iDomain)%dir = dir_TWS(domainID)
201 1 : L1_twsaObs(iDomain)%timeStepInput = timeStep_tws_input
202 2 : L1_twsaObs(iDomain)%varname = 'twsa'
203 : end do
204 : case(33)
205 : ! evapotranspiration
206 7 : do iDomain = 1, domainMeta%nDomains
207 6 : domainID = domainMeta%indices(iDomain)
208 6 : L1_etObs(iDomain)%dir = dir_evapotranspiration(domainID)
209 6 : L1_etObs(iDomain)%timeStepInput = timeStep_et_input
210 7 : L1_etObs(iDomain)%varname = 'et'
211 : end do
212 : ! domain average TWS data
213 12 : do iDomain = 1, domainMeta%nDomains
214 6 : domainID = domainMeta%indices(iDomain)
215 6 : L1_twsaObs(iDomain)%dir = dir_TWS(domainID)
216 6 : L1_twsaObs(iDomain)%timeStepInput = timeStep_tws_input
217 7 : L1_twsaObs(iDomain)%varname = 'twsa'
218 : end do
219 :
220 : end select
221 : end if
222 :
223 : !===============================================================
224 : ! Read pan evaporation
225 : !===============================================================
226 : ! Evap. coef. for free-water surfaces
227 14 : call nml_panEvapo%read(file_namelist)
228 182 : evap_coeff = nml_panEvapo%evap_coeff
229 :
230 14 : call common_check_resolution(.true., .false.)
231 :
232 : !===============================================================
233 : ! Read output specifications for mHM
234 : !===============================================================
235 14 : call nml_NLoutputResults%read(file_defOutput)
236 14 : output_deflate_level = nml_NLoutputResults%output_deflate_level
237 14 : output_double_precision = nml_NLoutputResults%output_double_precision
238 14 : timeStep_model_outputs = nml_NLoutputResults%timeStep_model_outputs
239 308 : outputFlxState = nml_NLoutputResults%outputFlxState
240 14 : output_time_reference = nml_NLoutputResults%output_time_reference
241 :
242 14 : call message('')
243 14 : call message('Following output will be written:')
244 14 : call message(' NetCDF deflate level: ', adjustl(trim(num2str(output_deflate_level))))
245 14 : if ( output_double_precision ) then
246 14 : call message(' NetCDF output precision: double')
247 : else
248 0 : call message(' NetCDF output precision: single')
249 : end if
250 14 : select case(output_time_reference)
251 : case(0)
252 14 : call message(' NetCDF output time reference point: start of time interval')
253 : case(1)
254 0 : call message(' NetCDF output time reference point: center of time interval')
255 : case(2)
256 14 : call message(' NetCDF output time reference point: end of time interval')
257 : end select
258 14 : call message(' STATES:')
259 14 : if (outputFlxState(1)) then
260 0 : call message(' interceptional storage (L1_inter) [mm]')
261 : end if
262 14 : if (outputFlxState(2)) then
263 0 : call message(' height of snowpack (L1_snowpack) [mm]')
264 : end if
265 14 : if (outputFlxState(3)) then
266 13 : call message(' soil water content in the single layers (L1_soilMoist) [mm]')
267 : end if
268 14 : if (outputFlxState(4)) then
269 0 : call message(' volumetric soil moisture in the single layers [mm/mm]')
270 : end if
271 14 : if (outputFlxState(5)) then
272 0 : call message(' mean volum. soil moisture averaged over all soil layers [mm/mm]')
273 : end if
274 14 : if (outputFlxState(6)) then
275 0 : call message(' waterdepth in reservoir of sealed areas (L1_sealSTW) [mm]')
276 : end if
277 14 : if (outputFlxState(7)) then
278 0 : call message(' waterdepth in reservoir of unsat. soil zone (L1_unsatSTW) [mm]')
279 : end if
280 14 : if (outputFlxState(8)) then
281 0 : call message(' waterdepth in reservoir of sat. soil zone (L1_satSTW) [mm]')
282 : end if
283 14 : if (processMatrix(10, 1) .eq. 0) outputFlxState(18) = .false. ! suppress output if process is off
284 14 : if (outputFlxState(18)) then
285 1 : call message(' ground albedo neutrons (L1_neutrons) [cph]')
286 : end if
287 :
288 14 : call message(' FLUXES:')
289 14 : if (outputFlxState(9)) then
290 2 : call message(' potential evapotranspiration PET (L1_pet) [mm/T]')
291 : end if
292 14 : if (outputFlxState(10)) then
293 3 : call message(' actual evapotranspiration aET (L1_aETCanopy) [mm/T]')
294 : end if
295 14 : if (outputFlxState(11)) then
296 13 : call message(' total discharge generated per cell (L1_total_runoff) [mm/T]')
297 : end if
298 14 : if (outputFlxState(12)) then
299 0 : call message(' direct runoff generated per cell (L1_runoffSeal) [mm/T]')
300 : end if
301 14 : if (outputFlxState(13)) then
302 0 : call message(' fast interflow generated per cell (L1_fastRunoff) [mm/T]')
303 : end if
304 14 : if (outputFlxState(14)) then
305 0 : call message(' slow interflow generated per cell (L1_slowRunoff) [mm/T]')
306 : end if
307 14 : if (outputFlxState(15)) then
308 0 : call message(' baseflow generated per cell (L1_baseflow) [mm/T]')
309 : end if
310 14 : if (outputFlxState(16)) then
311 2 : call message(' groundwater recharge (L1_percol) [mm/T]')
312 : end if
313 14 : if (outputFlxState(17)) then
314 0 : call message(' infiltration (L1_infilSoil) [mm/T]')
315 : end if
316 14 : if (outputFlxState(19)) then
317 0 : call message(' actual evapotranspiration from soil layers (L1_aETSoil) [mm/T]')
318 : end if
319 14 : if (outputFlxState(20)) then
320 0 : call message(' effective precipitation (L1_preEffect) [mm/T]')
321 : end if
322 14 : if (outputFlxState(21)) then
323 0 : call message(' snow melt (L1_melt) [mm/T]')
324 : end if
325 14 : call message('')
326 14 : call message('FINISHED reading config')
327 :
328 : ! warning message
329 61 : if (any(outputFlxState) .and. optimize) then
330 5 : call message('WARNING: FLUXES and STATES netCDF will be not written since optimization flag is TRUE ')
331 : end if
332 :
333 14 : end subroutine mhm_read_config
334 :
335 : END MODULE mo_mhm_read_config
|