5.13.2-dev0
mHM
The mesoscale Hydrological Model
Loading...
Searching...
No Matches
mo_startup.f90
Go to the documentation of this file.
1!> \file mo_startup.f90
2!> \brief \copybrief mo_startup
3!> \details \copydetails mo_startup
4
5!> \brief Startup procedures for mHM.
6!> \details This module initializes all variables required to run mHM. This
7!> module needs to be run only one time at the beginning of a simulation if
8!> re-starting files do not exist.
9!> \authors Luis Samaniego, Rohini Kumar
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_initialize ! initialization sequence
24
25CONTAINS
26
27
28 !> \brief Initialize main mHM variables
29 !> \details Initialize main mHM variables for a given domain.
30 !! Calls the following procedures in this order:
31 !! - Constant initialization.
32 !! - Generate soil database.
33 !! - Checking inconsistencies input fields.
34 !! - Variable initialization at level-0.
35 !! - Variable initialization at level-1.
36 !! - Variable initialization at level-11.
37 !! - Space allocation of remaining variable/parameters.
38 !! Global variables will be used at this stage.
39 !> \changelog
40 !! - Luis Samaniego Mar 2008
41 !! - fully distributed multilayer
42 !! - Rohini Kumar Oct 2010
43 !! - matrix to vector version
44 !! - openmp parallelization
45 !! - routing level 11
46 !! - Luis Samaniego Jul 2012
47 !! - removal of IMSL dependencies
48 !! - Luis Samaniego Dec 2012
49 !! - modular version
50 !! - Rohini Kumar May 2013
51 !! - code cleaned and error checks
52 !! - Rohini Kumar Nov 2013
53 !! - updated documentation
54 !! - Stephan Thober Jun 2014
55 !! - copied L2 initialization from mo_meteo_forcings
56 !! - Stephan Thober Jun 2014
57 !! - updated flag for read_restart
58 !! - Stephan Thober Aug 2015
59 !! - removed initialisation of routing
60 !! - Rohini Kumar Mar 2016
61 !! - changes for handling multiple soil database options
62 !! - Robert Schweppe Jun 2018
63 !! - refactoring and reformatting
64 !! - Sebastian Müller Mar 2023
65 !! - added separate read_nLAI_and_check_dims to correctly read nLAI from restart
66 !> \authors Luis Samaniego, Rohini Kumar
67 !> \date Dec 2012
68 subroutine mhm_initialize
69
73 use mo_grid, only : set_domain_indices
77
78 implicit none
79
80 integer(i4) :: idomain
81
82 ! constants initialization
83 call constants_init()
84
85 if (read_restart) then
86 allocate(level1(domainmeta%nDomains))
87 allocate(level0(domainmeta%nDomains))
88 ! read nLAI from restart files (-1 indicates first reading)
89 nlai = -1_i4
90 else
91 call mpr_initialize()
92 end if
93
94 do idomain = 1, domainmeta%nDomains
95
96 if (read_restart) then
97 ! this reads only the domain properties
98 if (domainmeta%L0DataFrom(idomain) == idomain) then
99 ! only read level0 data if it is new
100 ! similar to mo_common_read_data::read_dem
101 call read_grid_info(mhmfilerestartin(idomain), "0", level0(idomain))
102 endif
103 call read_grid_info(mhmfilerestartin(idomain), "1", level1(idomain))
104 ! read nLAI from restart
105 call read_nlai_and_check_dims(idomain, mhmfilerestartin(idomain))
106 ! Parameter fields have to be allocated in any case
107 call init_eff_params(level1(idomain)%nCells)
108 end if
109
110 ! State variables and fluxes
111 ! have to be allocated and initialised in any case
112 call variables_alloc(level1(idomain)%nCells)
113
114 end do
115
116 ! if no restart, this is done already in MPR
117 if (read_restart) then
118 call set_domain_indices(level0, indices=domainmeta%L0DataFrom)
120 end if
121
122 end subroutine mhm_initialize
123
124
125 !> \brief Initialize mHM constants
126 !> \details transformation of time units & initialize constants
127 !> \changelog
128 !! - Rohini Kumar Jan 2013
129 !! - Juliane Mai & Matthias Cuntz Nov 2013
130 !! - check timeStep
131 !! - Robert Schweppe Jun 2018
132 !! - refactoring and reformatting
133 !> \authors Luis Samaniego
134 !> \date Dec 2012
135 subroutine constants_init
143 use mo_string_utils, only : num2str
144
145 implicit none
146
147 !Fill Tabular for neutron flux integral
148 if (processmatrix(10, 1) .eq. 2) then
149 allocate(neutron_integral_afast(10000 + 2))
151 else
152 allocate(neutron_integral_afast(1))
153 neutron_integral_afast(:) = 0.0_dp
154 endif
155
156 ! if reading restart, we don't need GeoUnitList
157 if (.not. read_restart) then
158 ! check if enough geoparameter are defined in mhm_parameter.nml
159 ! this was formerly done after reading of data, but mHM and MPR are now seperate processes
160 if ((processmatrix(9, 2)) .NE. size(geounitlist, 1)) then
161 call error_message('***ERROR: Mismatch: Number of geological units in ', trim(adjustl(file_hydrogeoclass)), &
162 ' is ', trim(adjustl(num2str(size(geounitlist, 1)))), raise=.false.)
163 call error_message(' while it is ', trim(num2str(processmatrix(9, 2))), &
164 ' in ', trim(file_namelist_mhm_param), '!')
165 end if
166 end if
167
168 c2tstu = real(timestep, dp) / 24.0_dp ! from per timeStep to per day
169
170 end subroutine constants_init
171
172END MODULE mo_startup
Provides structures needed by mHM, mRM and/or mpr.
character(256), dimension(:), allocatable, public mhmfilerestartin
common restart tools
subroutine, public read_grid_info(infile, level_name, new_grid)
reads configuration apart from Level 11 configuration from a restart directory
subroutine, public read_nlai_and_check_dims(idomain, infile)
read nubmer of LAI time steps and check dimension configurations read from restart file
Provides structures needed by mHM, mRM and/or mpr.
type(domain_meta), public domainmeta
integer(i4), dimension(nprocesses, 3), public processmatrix
type(grid), dimension(:), allocatable, target, public level1
type(grid), dimension(:), allocatable, target, public level0
Provides file names and units for mHM.
Definition mo_file.F90:29
character(:), allocatable file_namelist_mhm_param
Parameter namelists file name.
Definition mo_file.F90:46
Main global variables for mHM.
real(dp), dimension(:), allocatable, public neutron_integral_afast
pre-calculated integrand for
gridding tools
Definition mo_grid.f90:12
subroutine, public set_domain_indices(grids, indices)
TODO: add description.
Definition mo_grid.f90:205
Initialization of all state variables of mHM.
subroutine, public variables_alloc(ncells1)
Allocation of space for mHM related L1 and L11 variables.
Provides file names and units for mRM.
character(len=*), parameter file_hydrogeoclass
hydrogeological classes input data file
Global variables for mpr only.
integer(i4), dimension(:), allocatable, public geounitlist
Startup procedures for mHM.
subroutine, public init_eff_params(ncells1)
Allocation of space for mHM related L1 and L11 variables.
subroutine, public mpr_initialize
Initialize main mHM variables.
Models to predict neutron intensities above soils.
subroutine, public tabularintegralafast(integral, maxc)
Save approximation data for A_fast.
Startup procedures for mHM.
subroutine constants_init
Initialize mHM constants.
subroutine, public mhm_initialize
Initialize main mHM variables.