IMEX_SfloW2D  0.9
Shallowwatergranularflowmodel
parameters_2d.f90
Go to the documentation of this file.
1 !********************************************************************************
3 !
6 !********************************************************************************
8 
9  IMPLICIT NONE
10 
11  REAL*8 :: eps_newton
13 
14  REAL*8 :: dt0
15 
16  REAL*8 :: max_dt
17 
18  REAL*8 :: cfl
19 
20  REAL*8 :: eps_sing
21 
22  CHARACTER(LEN=20) :: reconstr_variables
23 
24  REAL*8 :: reconstr_coeff
25 
31 
37 
42  LOGICAL :: topography_demfile
43 
48  LOGICAL :: riemann_flag
49 
54  LOGICAL :: rheology_flag
55 
60  INTEGER :: rheology_model
61 
66  LOGICAL :: temperature_flag
67 
73 
78  LOGICAL :: source_flag
79 
80  REAL*8 :: x_source
81  REAL*8 :: y_source
82  REAL*8 :: r_source
83  REAL*8 :: vfr_source
84  REAL*8 :: vel_source
85  REAL*8 :: t_source
86 
88  REAL*8 :: released_volume
89 
91  REAL*8 :: x_release
92 
94  REAL*8 :: y_release
95 
98 
102  !.
103 
105 
107  REAL*8 :: t_init
108 
110  REAL*8 :: t_ambient
111 
113  REAL*8 :: xs_init
114 
116  REAL*8 :: xs_ambient
117 
118  REAL*8 :: sed_vol_perc
119 
120  INTEGER :: n_vars
121  INTEGER :: n_eqns
122 
123  INTEGER :: n_nh
124 
125  INTEGER :: n_rk
126 
127  INTEGER, PARAMETER :: max_nl_iter = 100
128 
129  REAL*8, PARAMETER :: tol_abs = 1.d-5
130  REAL*8, PARAMETER :: tol_rel = 1.d-5
131 
138  INTEGER :: limiter(10)
139 
145  CHARACTER(LEN=20) :: solver_scheme
146 
147  REAL*8 :: theta
148  REAL*8 :: t_start
149  REAL*8 :: t_end
150  REAL*8 :: t_output
151  REAL*8 :: dt_output
152  REAL*8 :: t_runout
153  REAL*8 :: t_steady
154 
155  INTEGER :: verbose_level
156 
157  TYPE bc
158  INTEGER :: flag
159  REAL*8 :: value
160  END TYPE bc
161 
162  ! -------boundary conditions variables
163 
172  TYPE(bc), ALLOCATABLE :: bcw(:)
173 
182  TYPE(bc), ALLOCATABLE :: bce(:)
183 
192  TYPE(bc), ALLOCATABLE :: bcs(:)
193 
202  TYPE(bc), ALLOCATABLE :: bcn(:)
203 
204 END MODULE parameters_2d
real *8 max_dt
Largest time step allowed.
logical topography_demfile
Flag for uploading topography from a different file (topography_dem.asc)
real *8 sed_vol_perc
integer n_rk
Runge-Kutta order.
real *8 t_steady
end time when reached steady solution
real *8, parameter tol_rel
real *8 vel_source
logical temperature_flag
Flag to choose if we model temperature transport.
logical rheology_flag
Flag to choose if we add the rheology.
real *8 t_init
Initial temperature of the pile of material.
Parameters.
real *8 y_release
Initial y-coordinate of the pile.
real *8 t_end
end time for the run
integer rheology_model
choice of the rheology model
type(bc), dimension(:), allocatable bcw
bcW&flag defines the west boundary condition:
real *8 velocity_ang_release
Initial velocity direction (angle in degree): .
real *8 velocity_mod_release
Initial velocity module of the pile.
real *8 released_volume
Initial volume of the flow.
integer n_vars
Number of conservative variables.
real *8 cfl
Courant-Friedrichs-Lewy parameter.
real *8 t_ambient
Ambient temperature.
integer, parameter max_nl_iter
logical source_flag
Flag to choose if there is a source of mass within the domain.
real *8 vfr_source
real *8 dt0
Initial time step.
real *8 x_release
Initial x-coordiante of the pile.
character(len=20) solver_scheme
Finite volume method: .
real *8 theta
Van Leer limiter parameter.
logical riemann_flag
Flag to choose the sort of problem to solve.
real *8 eps_newton
threshold for the convergence of the Newton's method
real *8 t_output
time of the next output
integer verbose_level
real *8 xs_init
Initial sediment concentration in the pile of material.
real *8 xs_ambient
Ambient sediment concentration.
character(len=20) reconstr_variables
logical topography_function_flag
Flag to choose in which way we upload the topography.
integer, dimension(10) limiter
Limiter for the slope in the linear reconstruction: .
type(bc), dimension(:), allocatable bcn
bcN&flag defines the north boundary condition:
real *8 t_runout
time of the next runout output
integer n_eqns
Number of equations.
real *8, parameter tol_abs
real *8 reconstr_coeff
Slope coefficient in the linear reconstruction.
type(bc), dimension(:), allocatable bcs
bcS&flag defines the south boundary condition:
real *8 eps_sing
parameter for desingularization
type(bc), dimension(:), allocatable bce
bcE&flag defines the east boundary condition:
real *8 dt_output
time interval for the output of the solution
logical solid_transport_flag
Flag to choose if we model solid phase transport.
logical interfaces_relaxation
Flag to add the relaxation terms after the linear reconstruction: .
real *8 t_start
initial time for the run
integer n_nh
Number of non-hyperbolic terms.