MPI-AMRVAC 3.1
The MPI - Adaptive Mesh Refinement - Versatile Advection Code (development version)
Loading...
Searching...
No Matches
mod_variables.t
Go to the documentation of this file.
3
4 implicit none
5 public
6
7 !> Number of flux variables
8 integer :: nwflux = 0
9
10 !> Number of flux variables which need user to specify boundary type
11 integer :: nwfluxbc = 0
12
13 !> Number of auxiliary variables in w
14 integer :: nwaux = 0
15
16 !> Number of extra variables in w
17 integer :: nwextra = 0
18
19 !> Number of extra variables in wextra seperated from w
20 integer :: nw_extra = 0
21
22 !> Total number of variables
23 integer :: nw = 0
24
25 !> Total number of stagger variables
26 integer :: nws = 0
27
28 !> Number of variables which need to be updated in ghost cells
29 integer :: nwgc = 0
30
31 !> Number of vector variables (used for writing output)
32 integer :: nvector = 0
33
34 !> Indices of vector variables
35 integer, dimension(:), allocatable :: iw_vector
36
37 ! the number of the first w variable to exchange ghost cells
38 integer :: iwstart=1
39
40 !> Maximum number of variables
41 integer, parameter :: max_nw = 50
42
43 ! Global indices of variables that are often used
44
45 !> Index of the (gas) density
46 integer :: iw_rho = -1
47
48 !> Indices of the momentum density
49 integer, allocatable :: iw_mom(:)
50
51 !> Index of the energy density
52 integer :: iw_e = -1
53
54 !> Index of the radiation energy density
55 integer :: iw_r_e = -1
56
57 !> Index of heat flux
58 integer :: iw_q = -1
59
60 !> Indices of the magnetic field components
61 integer, allocatable, protected :: iw_mag(:)
62
63 !> Index of the cutoff temperature for the TRAC method
64 integer :: iw_tcoff = -1
65 integer :: iw_tweight= -1
66
67 !> number of species: each species has different characterictic speeds and should
68 !> be used accordingly in mod_finite_volume and mod_finite_difference
69 integer :: number_species = 1
70
71 !> index of the var
72 !> whose velocity appears in the induction eq.
73 integer :: index_v_mag = 1
74
75 !> the indices in 1:nwflux array are assumed consecutive for each species
76 !> this array should be of size number_species and contain the first index in the array of
77 !> the number_species
78 integer, allocatable :: start_indices(:)
79 !> the indices in 1:nwflux array are assumed consecutive for each species
80 !> this array should be of size number_species and contain the last index in the array of
81 !> the first number_species, the last index for the last one is nwflux
82 integer, allocatable :: stop_indices(:)
83
84 ! indices of equi for the species index_v_mag
85 ! these are needed for hlld solver, TODO: consider moving in a separate file
86 integer :: iw_equi_rho = -1
87 integer :: iw_equi_p = -1
88
89 !> Primitive variable names
90 character(len=name_len) :: prim_wnames(max_nw)
91
92 !> Conservative variable names
93 character(len=name_len) :: cons_wnames(max_nw)
94
95contains
96
97 !> Set generic flux variable
98 function var_set_fluxvar(name_cons, name_prim, ix, need_bc) result(iw)
99 character(len=*), intent(in) :: name_cons !< Conservative name
100 character(len=*), intent(in) :: name_prim !< Primitive name
101 integer, intent(in), optional :: ix !< Optional index (to make var1, var2, ...)
102 logical, intent(in), optional :: need_bc !< Require boundary condition (default: true)
103 integer :: iw
104 logical :: add_bc
105
106 nwflux = nwflux + 1
107 nw = nw + 1
108 iw = nwflux
109
110 add_bc = .true.
111 if (present(need_bc)) add_bc = need_bc
112 if (add_bc) nwfluxbc = nwfluxbc + 1
113
114 if (.not. present(ix)) then
115 prim_wnames(nwflux) = name_cons
116 cons_wnames(nwflux) = name_prim
117 else
118 write(cons_wnames(nwflux),"(A,I0)") name_cons, ix
119 write(prim_wnames(nwflux),"(A,I0)") name_prim, ix
120 end if
121 end function var_set_fluxvar
122
123 !> Set extra variable in w, which is not advected and has no boundary conditions.
124 !> This has to be done after defining flux variables and auxiliary variables.
125 function var_set_extravar(name_cons, name_prim, ix) result(iw)
126 character(len=*), intent(in) :: name_cons, name_prim
127 integer, intent(in), optional :: ix
128 integer :: iw
129
130 nwextra = nwextra + 1
131 nw = nw + 1
132 iw = nw
133
134 if (.not. present(ix)) then
135 prim_wnames(iw) = name_cons
136 cons_wnames(iw) = name_prim
137 else
138 write(cons_wnames(iw),"(A,I0)") name_cons, ix
139 write(prim_wnames(iw),"(A,I0)") name_prim, ix
140 end if
141 end function var_set_extravar
142
143 !> Set extra variable in wextra, which is not advected and has no boundary conditions and not output in dat.
144 !> This has to be done after defining flux variables and auxiliary variables.
145 function var_set_wextra() result(iw)
146 integer :: iw
147
148 nw_extra = nw_extra + 1
149 iw = nw_extra
150
151 end function var_set_wextra
152
153 !> Set auxiliary variable, which is not advected but has boundary conditions.
154 !> This has to be done after defining flux variables.
155 function var_set_auxvar(name_cons, name_prim, ix) result(iw)
156 character(len=*), intent(in) :: name_cons, name_prim
157 integer, intent(in), optional :: ix
158 integer :: iw
159
160 nwaux = nwaux + 1
161 nw = nw + 1
162 iw = nw
163
164 if (.not. present(ix)) then
165 prim_wnames(iw) = name_cons
166 cons_wnames(iw) = name_prim
167 else
168 write(cons_wnames(iw),"(A,I0)") name_cons, ix
169 write(prim_wnames(iw),"(A,I0)") name_prim, ix
170 end if
171 end function var_set_auxvar
172
173 !> Set density variable
174 function var_set_rho() result(iw)
175 integer :: iw
176
177 nwflux = nwflux + 1
178 nwfluxbc = nwfluxbc + 1
179 nw = nw + 1
180 iw_rho = nwflux
181 iw = nwflux
182 prim_wnames(nwflux) = 'rho'
183 cons_wnames(nwflux) = 'rho'
184 end function var_set_rho
185
186 ! THE INCLUDE files cannot use other modules
187 ! mpistop replaced by errormsg, should it exit?
188 !> Exit MPI-AMRVAC with an error message
189 subroutine errormsg(message)
190
191 character(len=*), intent(in) :: message !< The error message
192
193 write(*, *) "ERROR for processor"
194 write(*, *) trim(message)
195
196
197 end subroutine errormsg
198 !> Set momentum variables
199 function var_set_momentum(ndir) result(iw)
200 integer, intent(in) :: ndir
201 integer :: iw(ndir), idir
202
203 if (allocated(iw_mom)) &
204 call errormsg("Error: set_mom was already called")
205 allocate(iw_mom(ndir))
206
207 do idir = 1, ndir
208 nwflux = nwflux + 1
209 nwfluxbc = nwfluxbc + 1
210 nw = nw + 1
211 iw_mom(idir) = nwflux
212 iw(idir) = nwflux
213 write(cons_wnames(nwflux),"(A1,I1)") "m", idir
214 write(prim_wnames(nwflux),"(A1,I1)") "v", idir
215 end do
216 end function var_set_momentum
217
218 !> Set energy variable
219 function var_set_energy() result(iw)
220 integer :: iw
221
222 nwflux = nwflux + 1
223 nwfluxbc = nwfluxbc + 1
224 nw = nw + 1
225 iw_e = nwflux
226 iw = nwflux
227 cons_wnames(nwflux) = 'e'
228 prim_wnames(nwflux) = 'p'
229 end function var_set_energy
230
231 function var_set_q() result(iw)
232 integer :: iw
233
234 nwflux = nwflux + 1
235 nwfluxbc = nwfluxbc + 1
236 nw = nw + 1
237 iw_q = nwflux
238 iw = nwflux
239 prim_wnames(nwflux) = 'q'
240 cons_wnames(nwflux) = 'q'
241 end function var_set_q
242
243 function var_set_radiation_energy() result(iw)
244 integer :: iw
245
246 nwflux = nwflux + 1
247 nwfluxbc = nwfluxbc + 1
248 nw = nw + 1
249 iw_r_e = nwflux
250 iw = nwflux
251 cons_wnames(nwflux) = 'r_e'
252 prim_wnames(nwflux) = 'r_e'
253 end function var_set_radiation_energy
254
255 !> Set magnetic field variables
256 function var_set_bfield(ndir) result(iw)
257 integer, intent(in) :: ndir
258 integer :: iw(ndir), idir
259
260 if (allocated(iw_mag)) &
261 call errormsg("Error: set_mag was already called")
262 allocate(iw_mag(ndir))
263
264 do idir = 1, ndir
265 nwflux = nwflux + 1
266 nwfluxbc = nwfluxbc + 1
267 nw = nw + 1
268 iw_mag(idir) = nwflux
269 iw(idir) = nwflux
270 write(cons_wnames(nwflux),"(A1,I1)") "b", idir
271 write(prim_wnames(nwflux),"(A1,I1)") "b", idir
272 end do
273 end function var_set_bfield
274
275end module mod_variables
Module with basic data types used in amrvac.
integer function var_set_q()
integer iw_tcoff
Index of the cutoff temperature for the TRAC method.
integer nwextra
Number of extra variables in w.
character(len=name_len), dimension(max_nw) prim_wnames
Primitive variable names.
integer nw
Total number of variables.
character(len=name_len), dimension(max_nw) cons_wnames
Conservative variable names.
integer iw_equi_rho
integer nwaux
Number of auxiliary variables in w.
integer function var_set_rho()
Set density variable.
integer function var_set_energy()
Set energy variable.
integer nvector
Number of vector variables (used for writing output)
integer number_species
number of species: each species has different characterictic speeds and should be used accordingly in...
integer, dimension(:), allocatable iw_mom
Indices of the momentum density.
integer, dimension(:), allocatable start_indices
the indices in 1:nwflux array are assumed consecutive for each species this array should be of size n...
integer nws
Total number of stagger variables.
integer, dimension(:), allocatable stop_indices
the indices in 1:nwflux array are assumed consecutive for each species this array should be of size n...
integer, dimension(:), allocatable, protected iw_mag
Indices of the magnetic field components.
integer function var_set_auxvar(name_cons, name_prim, ix)
Set auxiliary variable, which is not advected but has boundary conditions. This has to be done after ...
integer iw_tweight
subroutine errormsg(message)
Exit MPI-AMRVAC with an error message.
integer function var_set_wextra()
Set extra variable in wextra, which is not advected and has no boundary conditions and not output in ...
integer, dimension(:), allocatable iw_vector
Indices of vector variables.
integer, parameter max_nw
Maximum number of variables.
integer function var_set_extravar(name_cons, name_prim, ix)
Set extra variable in w, which is not advected and has no boundary conditions. This has to be done af...
integer nwgc
Number of variables which need to be updated in ghost cells.
integer function, dimension(ndir) var_set_momentum(ndir)
Set momentum variables.
integer function var_set_radiation_energy()
integer iw_rho
Index of the (gas) density.
integer nwflux
Number of flux variables.
integer iw_r_e
Index of the radiation energy density.
integer iw_equi_p
integer index_v_mag
index of the var whose velocity appears in the induction eq.
integer function, dimension(ndir) var_set_bfield(ndir)
Set magnetic field variables.
integer iw_q
Index of heat flux.
integer nw_extra
Number of extra variables in wextra seperated from w.
integer iw_e
Index of the energy density.
integer function var_set_fluxvar(name_cons, name_prim, ix, need_bc)
Set generic flux variable.
integer nwfluxbc
Number of flux variables which need user to specify boundary type.