5.13.2-dev0
mHM
The mesoscale Hydrological Model
Loading...
Searching...
No Matches
mo_mrm_init.f90
Go to the documentation of this file.
1!> \file mo_mrm_init.f90
2!> \brief \copybrief mo_mrm_init
3!> \details \copydetails mo_mrm_init
4
5!> \brief Wrapper for initializing Routing.
6!> \details Calling all routines to initialize all mRM variables
7!> \authors Luis Samaniego, Rohini Kumar and Stephan Thober
8!> \date Aug 2015
9!> \copyright Copyright 2005-\today, the mHM Developers, Luis Samaniego, Sabine Attinger: All rights reserved.
10!! mHM is released under the LGPLv3+ license \license_note
11!> \ingroup f_mrm
13
14 use mo_common_variables, only : dirout
15 use mo_message, only : message, error_message
16
17 ! This module sets the river network characteristics and routing order.
18
19 ! Written Luis Samaniego, Mar 2005
20
21 IMPLICIT NONE
22
26
27 private
28
29CONTAINS
30
31 !> \brief read mRM configuration from namelists
32 subroutine mrm_configuration(file_namelist, unamelist, file_namelist_param, unamelist_param)
39 use mo_kind, only : i4
40 implicit none
41
42 character(*), intent(in) :: file_namelist !< namelist file name
43 integer, intent(in) :: unamelist !< unit to open namelist
44 character(*), intent(in) :: file_namelist_param !< parameter namelist file name
45 integer, intent(in) :: unamelist_param !< unit to open parameter namelist
46
47 if (mrm_coupling_mode .eq. 0_i4) then
48 call common_read_config(file_namelist, unamelist)
49 call common_mhm_mrm_read_config(file_namelist, unamelist)
50 !-----------------------------------------------------------
51 ! PRINT STARTUP MESSAGE
52 !-----------------------------------------------------------
53 call print_startup_message(file_namelist, file_namelist_param)
54 else
55 call message('')
56 call message(' Inititalize mRM')
57 if ( processmatrix(11, 1) .ne. 0 ) then
58 ! processCase(11): river temperature routing
59 riv_temp_pcs%active = .true.
60 riv_temp_pcs%case = processmatrix(11, 1)
61 call message('')
62 call message(' Read config: river temperature routing')
63 call riv_temp_pcs%config(file_namelist, unamelist, file_namelist_param, unamelist_param)
64 end if
65 end if
66
67 ! read config for mrm, readlatlon is set here depending on whether output is needed
68 call mrm_read_config(file_namelist, unamelist, file_namelist_param, unamelist_param, (mrm_coupling_mode .eq. 0_i4))
69
70 ! this was moved here, because it depends on global_parameters that are only set in mrm_read_config
71 if (mrm_coupling_mode .eq. 0_i4) then
73 !-----------------------------------------------------------
74 ! CONFIG OUTPUT
75 !-----------------------------------------------------------
76 call config_output()
77 end if
78 end subroutine mrm_configuration
79
80
81 !> \brief Initialize all mRM variables at all levels (i.e., L0, L1, and L11).
82 !> \details Initialize all mRM variables at all levels (i.e., L0, L1, and L11)
83 !! either with default values or with values from restart file. The L0 mask (L0_mask),
84 !! L0 elevation (L0_elev), and L0 land cover (L0_LCover) can be provided as optional
85 !! variables to save memory because these variable will then not be read in again.
86 !> \changelog
87 !! - Stephan Thober Sep 2015
88 !! - added L0_mask, L0_elev, and L0_LCover
89 !! - Stephan Thober May 2016
90 !! - added warning message in case no gauge is found in modelling domain
91 !! - Matthias Kelbling Aug 2017
92 !! - added L11_flow_accumulation to Initialize Stream Netwo
93 !! - Lennart Schueler May 2018
94 !! - added initialization for groundwater coupling
95 !! - Stephan Thober Jun 2018
96 !! - refactored for mpr_extract version
97 !! - Stephan Thober May 2019
98 !! - added init of level0 in case of read restart
99 !> \authors Stephan Thober
100 !> \date Aug 2015
101 subroutine mrm_init(file_namelist, unamelist, file_namelist_param, unamelist_param)
102
110 use mo_kind, only : i4
115 riv_temp_pcs, &
123 use mo_read_latlon, only : read_latlon
125 use mo_mrm_mpr, only : mrm_init_param
126
127 implicit none
128
129 character(*), intent(in) :: file_namelist !< namelist file name
130 integer, intent(in) :: unamelist !< unit to open namelist
131 character(*), intent(in) :: file_namelist_param !< parameter namelist file name
132 integer, intent(in) :: unamelist_param !< unit to open parameter namelist
133
134 ! start and end index for routing parameters
135 integer(i4) :: istart, iend
136 ! start and end index at L11
137 integer(i4) :: s11, e11
138
139 integer(i4) :: domainid, idomain, gauge_counter
140
141
142 if (mrm_coupling_mode .eq. 0_i4) then
143 allocate(l0_l1_remap(domainmeta%nDomains))
144 allocate(level1(domainmeta%nDomains))
145 end if
146
147 ! ----------------------------------------------------------
148 ! READ DATA
149 ! ----------------------------------------------------------
150 allocate(level11(domainmeta%nDomains))
151 allocate(l0_l11_remap(domainmeta%nDomains))
152
153 if (.not. mrm_read_river_network) then
154 ! read all (still) necessary level 0 data
155 if (processmatrix(8, 1) .eq. 1_i4) call mrm_read_l0_data(mrm_coupling_mode .eq. 0_i4, readlatlon, .true.)
156 if (processmatrix(8, 1) .eq. 2_i4) call mrm_read_l0_data(mrm_coupling_mode .eq. 0_i4, readlatlon, .false.)
157 if (processmatrix(8, 1) .eq. 3_i4) call mrm_read_l0_data(mrm_coupling_mode .eq. 0_i4, readlatlon, .false.)
158 end if
159
160 do idomain = 1, domainmeta%nDomains
161 domainid = domainmeta%indices(idomain)
162 if (mrm_read_river_network) then
163 ! this reads the domain properties
164 if (.not. allocated(level0)) allocate(level0(domainmeta%nDomains))
165 ! ToDo: L0_Domain, parallel
166 call read_grid_info(mrmfilerestartin(idomain), "0", level0(domainmeta%L0DataFrom(idomain)))
167 if (mrm_coupling_mode .eq. 0_i4) then
168 call read_grid_info(mrmfilerestartin(idomain), "1", level1(idomain))
169 end if
170 call read_grid_info(mrmfilerestartin(idomain), "11", level11(idomain))
171 call mrm_read_restart_config(idomain, domainid, mrmfilerestartin(idomain))
172 else
173 if (idomain .eq. 1) then
174 call l0_check_input_routing(domainmeta%L0DataFrom(idomain))
175 if (mrm_coupling_mode .eq. 0_i4) then
176 call l0_grid_setup(level0(domainmeta%L0DataFrom(idomain)))
177 end if
178 else if ((domainmeta%L0DataFrom(idomain) == idomain)) then
179 call l0_check_input_routing(domainmeta%L0DataFrom(idomain))
180 if (mrm_coupling_mode .eq. 0_i4) then
181 call l0_grid_setup(level0(domainmeta%L0DataFrom(idomain)))
182 end if
183 end if
184
185 if (mrm_coupling_mode .eq. 0_i4) then
186 call init_lowres_level(level0(domainmeta%L0DataFrom(idomain)), resolutionhydrology(idomain), &
187 level1(idomain), l0_l1_remap(idomain))
188 end if
189 call init_lowres_level(level0(domainmeta%L0DataFrom(idomain)), resolutionrouting(idomain), &
190 level11(idomain), l0_l11_remap(idomain))
191 call l11_l1_mapping(idomain)
192
193 if (readlatlon) then
194 ! read lat lon coordinates of each domain
195 call read_latlon(idomain, "lon", "lat", "level1", level1(idomain))
196 call read_latlon(idomain, "lon_l11", "lat_l11", "level11", level11(idomain))
197 else
198 ! allocate the memory and set to nodata
199 allocate(level11(idomain)%x(level11(idomain)%nrows, level11(idomain)%ncols))
200 allocate(level11(idomain)%y(level11(idomain)%nrows, level11(idomain)%ncols))
201 level11(idomain)%x = nodata_dp
202 level11(idomain)%y = nodata_dp
203 end if
204 end if
205 end do
206
209 call set_domain_indices(level0, indices=domainmeta%L0DataFrom)
210
211 ! ----------------------------------------------------------
212 ! INITIALIZE STATES AND AUXILLIARY VARIABLES
213 ! ----------------------------------------------------------
214 do idomain = 1, domainmeta%nDomains
215 call variables_alloc_routing(idomain)
216 end do
217
218 ! ----------------------------------------------------------
219 ! INITIALIZE STREAM NETWORK
220 ! ----------------------------------------------------------
221 do idomain = 1, domainmeta%nDomains
222 if (.not. mrm_read_river_network) then
223 call l11_flow_direction(idomain)
224 call l11_flow_accumulation(idomain)
225 call l11_set_network_topology(idomain)
226 call l11_routing_order(idomain)
227 call l11_link_location(idomain)
228 call l11_set_drain_outlet_gauges(idomain)
229 ! stream characteristics
230 call l11_stream_features(idomain)
231 end if
232 end do
233
234 ! ----------------------------------------------------------
235 ! INITIALIZE PARAMETERS
236 ! ----------------------------------------------------------
237 do idomain = 1, domainmeta%nDomains
238 istart = processmatrix(8, 3) - processmatrix(8, 2) + 1
239 iend = processmatrix(8, 3)
240 call mrm_init_param(idomain, global_parameters(istart : iend, 3))
241 end do
242
243 ! check whether there are gauges within the modelling domain
244 if (allocated(domain_mrm)) then
245 gauge_counter = 0
246 do idomain = 1, domainmeta%nDomains
247 if (.not. all(domain_mrm(idomain)%gaugeNodeList .eq. nodata_i4)) then
248 gauge_counter = gauge_counter + 1
249 end if
250 end do
251 if (gauge_counter .lt. 1) then
252 call message('')
253 call message(' WARNING: no gauge found within modelling domain')
254 end if
255 end if
256 ! mpr-like definiton of sealed floodplain fraction
257 if ((processmatrix(8, 1) .eq. 1_i4) .and. (.not. mrm_read_river_network)) then
258 call l11_fraction_sealed_floodplain(2_i4, .true.)
259 else
260 ! dummy initialization
261 call l11_fraction_sealed_floodplain(2_i4, .false.)
262 end if
263
264 ! -------------------------------------------------------
265 ! READ INPUT DATA AND OBSERVED DISCHARGE DATA
266 ! -------------------------------------------------------
267 ! read simulated runoff at level 1
268 if (mrm_coupling_mode .eq. 0_i4) then
269 do idomain = 1, domainmeta%nDomains
270 call mrm_read_total_runoff(idomain)
271 end do
272 end if
273 ! discharge data
274 call mrm_read_discharge()
275
276 ! init groundwater coupling
277 if (gw_coupling) then
278 do idomain = 1, domainmeta%nDomains
280 call mrm_read_bankfull_runoff(idomain)
281 end do
283 end if
284
285 ! init riv temp
286 if ( riv_temp_pcs%active ) then
287 call message('')
288 call message(' Initialization of river temperature routing.')
289 do idomain = 1, domainmeta%nDomains
290 s11 = level11(idomain)%iStart
291 e11 = level11(idomain)%iEnd
292 call riv_temp_pcs%init(level11(idomain)%nCells)
293 call riv_temp_pcs%init_area( &
294 idomain, &
295 l11_netperm(s11 : e11), & ! routing order at L11
296 l11_fromn(s11 : e11), & ! link source at L11
297 l11_length(s11 : e11 - 1), & ! link length
298 level11(idomain)%nCells - l11_noutlets(idomain), &
299 level11(idomain)%nCells, &
300 level11(idomain)%nrows, &
301 level11(idomain)%ncols, &
302 level11(idomain)%mask &
303 )
304 end do
305 end if
306 call message('')
307 call message(' Finished Initialization of mRM')
308
309 end subroutine mrm_init
310
311
312 !> \brief Print mRM startup message
313 !> \authors Robert Schweppe
314 !> \date Jun 2018
315 subroutine print_startup_message(file_namelist, file_namelist_param)
316
317 use mo_kind, only : i4
319 use mo_string_utils, only : num2str, separator
320
321 implicit none
322
323 character(*), intent(in) :: file_namelist !< namelist file name
324 character(*), intent(in) :: file_namelist_param !< parameter namelist file name
325
326 ! Date and time
327 integer(i4), dimension(8) :: datetime
328
329 CHARACTER(len=1024) :: message_text = ''
330
331 call message(separator)
332 call message(' mRM-UFZ')
333 call message()
334 call message(' MULTISCALE ROUTING MODEL')
335 call message(' Version ', trim(version))
336 call message(' ', trim(version_date))
337 call message()
338 call message('Made available by S. Thober & M. Cuntz')
339 call message()
340 call message('Based on mHM-UFZ by L. Samaniego & R. Kumar')
341
342 call message(separator)
343
344 call message()
345 call date_and_time(values = datetime)
346 message_text = trim(num2str(datetime(3), '(I2.2)')) // "." // trim(num2str(datetime(2), '(I2.2)')) &
347 // "." // trim(num2str(datetime(1), '(I4.4)')) // " " // trim(num2str(datetime(5), '(I2.2)')) &
348 // ":" // trim(num2str(datetime(6), '(I2.2)')) // ":" // trim(num2str(datetime(7), '(I2.2)'))
349 call message('Start at ', trim(message_text), '.')
350 call message('Using main file ', trim(file_main), ' and namelists: ')
351 call message(' ', trim(file_namelist))
352 call message(' ', trim(file_namelist_param))
353 call message(' ', trim(file_defoutput), ' (if it is given)')
354 call message()
355
356 end subroutine print_startup_message
357
358
359 !> \brief print mRM configuration
360 !> \authors Robert Schweppe
361 !> \date Jun 2018
362 subroutine config_output
363
365 use mo_kind, only : i4
369 use mo_string_utils, only : num2str
370
371 implicit none
372
373 integer(i4) :: domainID, iDomain
374
375 integer(i4) :: jj
376
377
378 !
379 call message()
380 call message('Read namelist file: ', trim(file_namelist_mrm))
381 call message('Read namelist file: ', trim(file_namelist_param_mrm))
382 call message('Read namelist file: ', trim(file_defoutput), ' (if it is given)')
383
384 call message()
385 call message(' # of domains: ', trim(num2str(domainmeta%nDomains)))
386 call message()
387 call message(' Input data directories:')
388 do idomain = 1, domainmeta%nDomains
389 domainid = domainmeta%indices(idomain)
390 call message(' --------------')
391 call message(' DOMAIN ', num2str(domainid, '(I3)'))
392 call message(' --------------')
393 call message(' Morphological directory: ', trim(dirmorpho(idomain)))
394 call message(' Land cover directory: ', trim(dirlcover(idomain)))
395 call message(' Discharge directory: ', trim(dirgauges(idomain)))
396 call message(' Output directory: ', trim(dirout(idomain)))
397 call message(' Evaluation gauge ', 'ID')
398 do jj = 1, domain_mrm(idomain)%nGauges
399 call message(' ', trim(adjustl(num2str(jj))), ' ', &
400 trim(adjustl(num2str(domain_mrm(idomain)%gaugeIdList(jj)))))
401 end do
402 if (domain_mrm(idomain)%nInflowGauges .GT. 0) then
403 call message(' Inflow gauge ', 'ID')
404 do jj = 1, domain_mrm(idomain)%nInflowGauges
405 call message(' ', trim(adjustl(num2str(jj))), ' ', &
406 trim(adjustl(num2str(domain_mrm(idomain)%InflowGaugeIdList(jj)))))
407 end do
408 end if
409 end do
410 end subroutine config_output
411
412
413 !> \brief Default initalization mRM related L11 variables
414 !> \details Default initalization of mHM related L11 variables (e.g., states,
415 !! fluxes, and parameters) as per given constant values given in mo_mhm_constants.
416 !! Variables initalized here is defined in the mo_global_variables.f90 file.
417 !! Only Variables that are defined in the variables_alloc subroutine are
418 !! intialized here.
419 !! If a variable is added or removed here, then it also has to be added or removed
420 !! in the subroutine state_variables_set in the module mo_restart and in the
421 !! subroutine set_state in the module mo_set_netcdf_restart.
422 !> \authors Stephan Thober, Rohini Kumar, and Juliane Mai
423 !> \date Aug 2015
424 !> \authors Robert Schweppe
425 !> \date Jun 2018
427
430
431 implicit none
432
433 !-------------------------------------------
434 ! L11 ROUTING STATE VARIABLES, FLUXES AND
435 ! PARAMETERS
436 !-------------------------------------------
437
438 ! fluxes and states
440
441 ! kappa: Muskingum travel time parameter.
443 ! xi: Muskingum diffusion parameter
445 ! Routing parameter C1=f(K,xi, DT) (Chow, 25-41)
447 ! Routing parameter C2 =f(K,xi, DT) (Chow, 25-41)
449
450 end subroutine variables_default_init_routing
451
452 !> \brief initialize fluxes and states with default values for mRM
454
455 use mo_kind, only: i4
459
460 implicit none
461
462 !> number of Domain (if not present, set for all)
463 integer(i4), intent(in), optional :: idomain
464
465 integer(i4) :: s11, e11
466
467 !-------------------------------------------
468 ! L11 ROUTING STATE VARIABLES, FLUXES AND
469 ! PARAMETERS
470 !-------------------------------------------
471
472 if (present(idomain)) then
473 s11 = level11(idomain)%iStart
474 e11 = level11(idomain)%iEnd
475 ! simulated discharge at each node
476 l11_qmod(s11 : e11) = p1_initstatefluxes
477 ! Total outflow from cells L11 at time tt
478 l11_qout(s11 : e11) = p1_initstatefluxes
479 ! Total discharge inputs at t-1 and t
480 l11_qtin(s11 : e11, :) = p1_initstatefluxes
481 ! Routed outflow leaving a node
482 l11_qtr(s11 : e11, :) = p1_initstatefluxes
483 else
484 ! simulated discharge at each node
486 ! Total outflow from cells L11 at time tt
488 ! Total discharge inputs at t-1 and t
490 ! Routed outflow leaving a node
492 end if
493
495
496
497 !> \brief check routing input on level-0
498 !> \authors Robert Schweppe
499 !> \date Jun 2018
500 subroutine l0_check_input_routing(L0Domain_iDomain)
501
503 use mo_common_variables, only : level0
504 use mo_kind, only : i4
506 use mo_string_utils, only : num2str
507
508 implicit none
509
510 integer(i4), intent(in) :: L0Domain_iDomain !< domain index for associated level-0 data
511
512 integer(i4) :: k
513
514 CHARACTER(len=1024) :: message_text = ''
515
516 do k = level0(l0domain_idomain)%iStart, level0(l0domain_idomain)%iEnd
517 ! flow direction [-]
518 if (l0_fdir(k) .eq. nodata_i4) then
519 message_text = trim(num2str(k, '(I5)')) // ',' // trim(num2str(l0domain_idomain, '(I5)'))
520 call error_message(' Error: flow direction has missing value within the valid masked area at cell in domain ', &
521 trim(message_text))
522 end if
523 ! flow accumulation [-]
524 if (l0_facc(k) .eq. nodata_i4) then
525 message_text = trim(num2str(k, '(I5)')) // ',' // trim(num2str(l0domain_idomain, '(I5)'))
526 call error_message(' Error: flow accumulation has missing values within the valid masked area at cell in domain ', &
527 trim(message_text))
528 end if
529 end do
530
531 end subroutine l0_check_input_routing
532
533
534 !> \brief allocated routing related variables
535 !> \authors Robert Schweppe
536 !> \date Jun 2018
537 subroutine variables_alloc_routing(iDomain)
538
539 use mo_append, only : append
540 use mo_kind, only : dp, i4
546
547 implicit none
548
549 integer(i4), intent(in) :: iDomain !< domain index
550
551 real(dp), dimension(:), allocatable :: dummy_Vector11
552
553 real(dp), dimension(:, :), allocatable :: dummy_Matrix11_IT
554
555
556 ! dummy vector and matrix
557 allocate(dummy_vector11(level11(idomain)%nCells))
558 allocate(dummy_matrix11_it(level11(idomain)%nCells, nroutingstates))
559
560 ! simulated discharge at each node
561 dummy_vector11(:) = 0.0_dp
562 call append(l11_qmod, dummy_vector11)
563
564 ! Total outflow from cells L11 at time tt
565 dummy_vector11(:) = 0.0_dp
566 call append(l11_qout, dummy_vector11)
567
568 ! Total discharge inputs at t-1 and t
569 dummy_matrix11_it(:, :) = 0.0_dp
570 call append(l11_qtin, dummy_matrix11_it)
571
572 ! Routed outflow leaving a node
573 dummy_matrix11_it(:, :) = 0.0_dp
574 call append(l11_qtr, dummy_matrix11_it)
575
576 ! kappa: Muskingum travel time parameter.
577 dummy_vector11(:) = 0.0_dp
578 call append(l11_k, dummy_vector11)
579
580 ! xi: Muskingum diffusion parameter
581 dummy_vector11(:) = 0.0_dp
582 call append(l11_xi, dummy_vector11)
583
584 ! Routing parameter C1=f(K,xi, DT) (Chow, 25-41)
585 dummy_vector11(:) = 0.0_dp
586 call append(l11_c1, dummy_vector11)
587
588 ! Routing parameter C2 =f(K,xi, DT) (Chow, 25-41)
589 dummy_vector11(:) = 0.0_dp
590 call append(l11_c2, dummy_vector11)
591
592 ! Celerity at each link
593 dummy_vector11(:) = 0.0_dp
594 call append(l11_celerity, dummy_vector11)
595
596 ! celerity at level 0
597 if (allocated(dummy_vector11)) deallocate(dummy_vector11)
598 allocate(dummy_vector11(level0(domainmeta%L0DataFrom(idomain))%ncells))
599 dummy_vector11(:) = 0.0_dp
600 call append(l0_celerity, dummy_vector11)
601
602 ! free space
603 if (allocated(dummy_vector11)) deallocate(dummy_vector11)
604 if (allocated(dummy_matrix11_it)) deallocate(dummy_matrix11_it)
605
606 end subroutine variables_alloc_routing
607
608END MODULE mo_mrm_init
Provides constants commonly used by mHM, mRM and MPR.
real(dp), parameter, public p1_initstatefluxes
real(dp), parameter, public nodata_dp
integer(i4), parameter, public nodata_i4
Reading of main model configurations.
subroutine, public common_mhm_mrm_read_config(file_namelist, unamelist)
Read main configurations for common parts.
subroutine, public check_optimization_settings
check optimization settings
Provides structures needed by mHM, mRM and/or mpr.
character(256), dimension(:), allocatable, public mrmfilerestartin
real(dp), dimension(:), allocatable, public resolutionrouting
Reading of main model configurations.
subroutine, public common_read_config(file_namelist, unamelist)
Read main configurations commonly used by mHM, mRM and MPR.
common restart tools
subroutine, public read_grid_info(infile, level_name, new_grid)
reads configuration apart from Level 11 configuration from a restart directory
Provides structures needed by mHM, mRM and/or mpr.
real(dp), dimension(:), allocatable, public resolutionhydrology
real(dp), dimension(:, :), allocatable, target, public global_parameters
type(domain_meta), public domainmeta
character(256), dimension(:), allocatable, public dirlcover
character(256), dimension(:), allocatable, public dirout
character(256), dimension(:), allocatable, public dirmorpho
integer(i4), dimension(nprocesses, 3), public processmatrix
type(grid), dimension(:), allocatable, target, public level1
type(grid), dimension(:), allocatable, target, public level0
type(gridremapper), dimension(:), allocatable, public l0_l1_remap
gridding tools
Definition mo_grid.f90:12
subroutine, public set_domain_indices(grids, indices)
TODO: add description.
Definition mo_grid.f90:205
subroutine, public init_lowres_level(highres, target_resolution, lowres, highres_lowres_remap)
Level-1 variable initialization.
Definition mo_grid.f90:59
subroutine, public l0_grid_setup(new_grid)
level 0 variable initialization
Definition mo_grid.f90:268
Provides mRM specific constants.
integer(i4), parameter, public nroutingstates
Provides file names and units for mRM.
character(len=*), parameter version
Current mHM model version.
character(len=*), parameter file_main
Driver file.
character(:), allocatable file_defoutput
file defining mRM's outputs
character(len=*), parameter file_namelist_param_mrm
Parameter namelists file name.
character(len=*), parameter version_date
Time of current mHM model version release.
character(len=*), parameter file_namelist_mrm
Namelist file name.
Global variables for mRM only.
real(dp), dimension(:, :), allocatable, public l11_qtin
type(gridremapper), dimension(:), allocatable, public l0_l11_remap
integer(i4), dimension(:), allocatable, public l11_netperm
real(dp), dimension(:), allocatable, public l11_qout
real(dp), dimension(:), allocatable, public l0_celerity
type(riv_temp_type), public riv_temp_pcs
This is a container for the river temperature routing process (pcs)
integer(i4), dimension(:), allocatable, public l0_fdir
real(dp), dimension(:), allocatable, public l11_xi
character(256), dimension(:), allocatable, public dirgauges
integer(i4), dimension(:), allocatable, public l11_fromn
real(dp), dimension(:), allocatable, public l11_length
real(dp), dimension(:), allocatable, public l11_qmod
type(domaininfo_mrm), dimension(:), allocatable, target, public domain_mrm
type(grid), dimension(:), allocatable, target, public level11
integer(i4), dimension(:), allocatable, public l0_facc
real(dp), dimension(:), allocatable, public l11_c1
real(dp), dimension(:), allocatable, public l11_celerity
integer(i4), dimension(:), allocatable, public l11_noutlets
real(dp), dimension(:), allocatable, public l11_k
real(dp), dimension(:), allocatable, public l0_river_head_mon_sum
real(dp), dimension(:, :), allocatable, public l11_qtr
real(dp), dimension(:), allocatable, public l11_c2
Wrapper for initializing Routing.
subroutine, public fluxes_states_default_init_routing(idomain)
initialize fluxes and states with default values for mRM
subroutine config_output
print mRM configuration
subroutine print_startup_message(file_namelist, file_namelist_param)
Print mRM startup message.
subroutine, public mrm_configuration(file_namelist, unamelist, file_namelist_param, unamelist_param)
read mRM configuration from namelists
subroutine, public variables_default_init_routing
Default initalization mRM related L11 variables.
subroutine l0_check_input_routing(l0domain_idomain)
check routing input on level-0
subroutine variables_alloc_routing(idomain)
allocated routing related variables
subroutine, public mrm_init(file_namelist, unamelist, file_namelist_param, unamelist_param)
Initialize all mRM variables at all levels (i.e., L0, L1, and L11).
Perform Multiscale Parameter Regionalization on Routing Parameters.
subroutine, public mrm_init_param(idomain, param)
TODO: add description.
Startup drainage network for mHM.
subroutine, public l11_stream_features(idomain)
Stream features (stream network and floodplain)
subroutine, public l11_flow_direction(idomain)
Determine the flow direction of the upscaled river network at level L11.
subroutine, public l11_fraction_sealed_floodplain(lcclassimp, do_init)
Fraction of the flood plain with impervious cover.
subroutine, public l11_set_drain_outlet_gauges(idomain)
Draining cell identification and Set gauging node.
subroutine, public l11_set_network_topology(idomain)
Set network topology.
subroutine, public l11_routing_order(idomain)
Find routing order, headwater cells and sink.
subroutine, public l11_link_location(idomain)
Estimate the LO (row,col) location for each routing link at level L11.
subroutine, public l11_l1_mapping(idomain)
TODO: add description.
subroutine, public l11_flow_accumulation(idomain)
Calculates L11 flow accumulation per grid cell.
subroutine, public mrm_read_config(file_namelist, unamelist, file_namelist_param, unamelist_param, do_message)
Read the general config of mRM.
mRM reading routines
subroutine, public mrm_read_bankfull_runoff(idomain)
subroutine, public mrm_read_discharge
Read discharge timeseries from file.
subroutine, public mrm_read_l0_data(do_reinit, do_readlatlon, do_readlcover)
read L0 data from file
subroutine, public mrm_read_total_runoff(idomain)
read simulated runoff that is to be routed
Restart routines.
subroutine, public mrm_read_restart_config(idomain, domainid, infile)
reads Level 11 configuration from a restart directory
River head calculation.
subroutine, public init_masked_zeros_l0(idomain, data)
allocates memory for L0 variable
subroutine, public calc_channel_elevation()
calculates the channel elevation from the bankfull river discharge
reading latitude and longitude coordinates for each domain
subroutine, public read_latlon(ii, lon_var_name, lat_var_name, level_name, level)
reads latitude and longitude coordinates