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