MPI-AMRVAC 3.1
The MPI - Adaptive Mesh Refinement - Versatile Advection Code (development version)
Loading...
Searching...
No Matches
mod_nonlinear_phys.t
Go to the documentation of this file.
1!> Module containing the physics routines for scalar nonlinear equation
3
4 implicit none
5 private
6
7 !> index of the single scalar unknown
8 integer, protected, public :: rho_ = 1
9
10 !> switch between burgers (i.e. rho**2)
11 !> or nonconvex flux (i.e. rho**3)
12 integer, protected, public :: nonlinear_flux_type = 1
13
14 !> whether the KdV source term is added
15 logical, protected, public :: kdv_source_term = .false.
16
17 !> Whether particles module is added
18 logical, public, protected :: nonlinear_particles = .false.
19
20 ! Public methods
21 public :: nonlinear_phys_init
22 public :: nonlinear_get_v
23
24contains
25
26 !> Read this module's parameters from a file
27 subroutine nonlinear_params_read(files)
29 character(len=*), intent(in) :: files(:)
30 integer :: n
31
33
34 do n = 1, size(files)
35 open(unitpar, file=trim(files(n)), status='old')
36 read(unitpar, nonlinear_list, end=111)
37111 close(unitpar)
38 end do
39
40 end subroutine nonlinear_params_read
41
42 !> Write this module's parameters to a snapshot
43 subroutine nonlinear_write_info(fh)
44 ! for nonlinear scalar equation, nothing to write
45 ! note: this is info only stored at end of dat files,
46 ! is never read/used for restarts, only expects
47 ! an integer (number of parameters) and
48 ! corresponding double values and character names
49 ! and is meant for use in the python tools
51 integer, intent(in) :: fh
52 integer, dimension(MPI_STATUS_SIZE) :: st
53 integer :: er
54
55 ! Write zero parameters
56 call mpi_file_write(fh, 0, 1, mpi_integer, st, er)
57
58 end subroutine nonlinear_write_info
59
62 use mod_physics
63 use mod_kdv, only: kdv_init
65
66 call nonlinear_params_read(par_files)
67
68 physics_type = "nonlinear"
69 phys_energy = .false.
71
72 allocate(start_indices(number_species),stop_indices(number_species))
73 ! set the index of the first flux variable for species 1
74 start_indices(1)=1
75 rho_ = var_set_rho()
76
77 ! set number of variables which need update ghostcells
78 nwgc=nwflux
79
80 ! set the index of the last flux variable for species 1
81 stop_indices(1)=nwflux
82
83 ! Number of variables need reconstruction in w
84 nw_recon=nwflux
85
86 ! Check whether custom flux types have been defined
87 if (.not. allocated(flux_type)) then
88 allocate(flux_type(ndir, nw))
90 else if (any(shape(flux_type) /= [ndir, nw])) then
91 call mpistop("phys_check error: flux_type has wrong shape")
92 end if
93
94 phys_get_cmax => nonlinear_get_cmax
95 phys_get_cbounds => nonlinear_get_cbounds
96 phys_get_flux => nonlinear_get_flux
97 phys_add_source_geom => nonlinear_add_source_geom
98 phys_add_source => nonlinear_add_source
99 phys_to_conserved => nonlinear_to_conserved
100 phys_to_primitive => nonlinear_to_primitive
101 phys_get_dt => nonlinear_get_dt
102 phys_write_info => nonlinear_write_info
103
104 if (kdv_source_term) call kdv_init()
105
106 ! Initialize particles module
107 if (nonlinear_particles) then
108 call particles_init()
109 end if
110
111 end subroutine nonlinear_phys_init
112
113 subroutine nonlinear_to_conserved(ixI^L, ixO^L, w, x)
115 integer, intent(in) :: ixi^l, ixo^l
116 double precision, intent(inout) :: w(ixi^s, nw)
117 double precision, intent(in) :: x(ixi^s, 1:^nd)
118
119 ! Do nothing (primitive and conservative are equal for nonlinear module)
120 end subroutine nonlinear_to_conserved
121
122 subroutine nonlinear_to_primitive(ixI^L, ixO^L, w, x)
124 integer, intent(in) :: ixi^l, ixo^l
125 double precision, intent(inout) :: w(ixi^s, nw)
126 double precision, intent(in) :: x(ixi^s, 1:^nd)
127
128 ! Do nothing (primitive and conservative are equal for nonlinear module)
129 end subroutine nonlinear_to_primitive
130
131 subroutine nonlinear_get_v(w, x, ixI^L, ixO^L, idim, v)
133 integer, intent(in) :: ixi^l, ixo^l, idim
134 double precision, intent(in) :: w(ixi^s, nw), x(ixi^s, 1:^nd)
135 double precision, intent(out) :: v(ixi^s)
136
137 select case(nonlinear_flux_type)
138 case(1)
139 v(ixo^s)=w(ixo^s,rho_)
140 case(2)
141 v(ixo^s)=3.0d0*w(ixo^s,rho_)**2
142 case default
143 call mpistop('Undefined fluxtype: set nonlinear_flux_type to 1 or 2')
144 end select
145
146 end subroutine nonlinear_get_v
147
148 subroutine nonlinear_get_cmax(w, x, ixI^L, ixO^L, idim, cmax)
150 integer, intent(in) :: ixi^l, ixo^l, idim
151 double precision, intent(in) :: w(ixi^s, nw), x(ixi^s, 1:^nd)
152 double precision, intent(inout) :: cmax(ixi^s)
153
154 call nonlinear_get_v(w, x, ixi^l, ixo^l, idim, cmax)
155
156 cmax(ixo^s) = abs(cmax(ixo^s))
157
158 end subroutine nonlinear_get_cmax
159
160 subroutine nonlinear_get_cbounds(wLC, wRC, wLp, wRp, x, ixI^L, ixO^L, idim,Hspeed, cmax, cmin)
162 use mod_variables
163 integer, intent(in) :: ixi^l, ixo^l, idim
164 double precision, intent(in) :: wlc(ixi^s, nw), wrc(ixi^s,nw)
165 double precision, intent(in) :: wlp(ixi^s, nw), wrp(ixi^s,nw)
166 double precision, intent(in) :: x(ixi^s, 1:^nd)
167 double precision, intent(inout) :: cmax(ixi^s,1:number_species)
168 double precision, intent(inout), optional :: cmin(ixi^s,1:number_species)
169 double precision, intent(in) :: hspeed(ixi^s,1:number_species)
170 double precision :: wmean(ixi^s,nw)
171
172 ! since get_v depends on w, the first argument should be some average over the
173 ! left and right state
174 wmean(ixo^s,1:nwflux)=0.5d0*(wlc(ixo^s,1:nwflux)+wrc(ixo^s,1:nwflux))
175 call nonlinear_get_v(wmean, x, ixi^l, ixo^l, idim, cmax(ixi^s,1))
176
177 if (present(cmin)) then
178 cmin(ixo^s,1) = min(cmax(ixo^s,1), zero)
179 cmax(ixo^s,1) = max(cmax(ixo^s,1), zero)
180 else
181 cmax(ixo^s,1) = maxval(abs(cmax(ixo^s,1)))
182 end if
183
184 end subroutine nonlinear_get_cbounds
185
186 subroutine nonlinear_get_dt(w, ixI^L, ixO^L, dtnew, dx^D, x)
188 use mod_kdv, only: kdv_get_dt
189
190 integer, intent(in) :: ixi^l, ixo^l
191 double precision, intent(in) :: dx^d, x(ixi^s, 1:^nd)
192 double precision, intent(in) :: w(ixi^s, 1:nw)
193 double precision, intent(inout) :: dtnew
194
195 dtnew = bigdouble
196
197 if(kdv_source_term) then
198 call kdv_get_dt(w, ixi^l, ixo^l, dtnew, dx^d, x)
199 endif
200 end subroutine nonlinear_get_dt
201
202 ! here we select the flux according to the nonlinear_flux_type parameter
203 subroutine nonlinear_get_flux(wC, w, x, ixI^L, ixO^L, idim, f)
205 integer, intent(in) :: ixi^l, ixo^l, idim
206 double precision, intent(in) :: wc(ixi^s, 1:nw)
207 double precision, intent(in) :: w(ixi^s, 1:nw)
208 double precision, intent(in) :: x(ixi^s, 1:^nd)
209 double precision, intent(out) :: f(ixi^s, nwflux)
210
211 select case(nonlinear_flux_type)
212 case(1)
213 f(ixo^s,rho_)=half*w(ixo^s,rho_)**2
214 case(2)
215 f(ixo^s,rho_)=w(ixo^s,rho_)**3
216 case default
217 call mpistop('Undefined fluxtype: set nonlinear_flux_type to 1 or 2')
218 end select
219
220 end subroutine nonlinear_get_flux
221
222 subroutine nonlinear_add_source_geom(qdt, dtfactor, ixI^L, ixO^L, wCT,wprim, w, x)
223
224 ! Add geometrical source terms to w
225 ! There are no geometrical source terms
226
228
229 integer, intent(in) :: ixi^l, ixo^l
230 double precision, intent(in) :: qdt, dtfactor, x(ixi^s, 1:^nd)
231 double precision, intent(inout) :: wct(ixi^s, 1:nw), wprim(ixi^s,1:nw),w(ixi^s, 1:nw)
232
233 end subroutine nonlinear_add_source_geom
234
235 subroutine nonlinear_add_source(qdt, dtfactor, ixI^L,ixO^L,wCT,wCTprim,w,x,qsourcesplit,active)
237 use mod_kdv, only: kdv_add_source
238
239 integer, intent(in) :: ixi^l, ixo^l
240 double precision, intent(in) :: qdt,dtfactor
241 double precision, intent(in) :: wct(ixi^s, 1:nw),wctprim(ixi^s,1:nw), x(ixi^s, 1:ndim)
242 double precision, intent(inout) :: w(ixi^s, 1:nw)
243 logical, intent(in) :: qsourcesplit
244 logical, intent(inout) :: active
245
246 if(kdv_source_term) then
247 call kdv_add_source(qdt,ixi^l,ixo^l,wct,w,x,qsourcesplit,active)
248 end if
249
250 end subroutine nonlinear_add_source
251
252end module mod_nonlinear_phys
This module contains definitions of global parameters and variables and some generic functions/subrou...
integer, parameter unitpar
file handle for IO
integer, parameter ndim
Number of spatial dimensions for grid variables.
logical use_particles
Use particles module or not.
character(len=std_len), dimension(:), allocatable par_files
Which par files are used as input.
double precision, dimension(:), allocatable, parameter d
integer ndir
Number of spatial dimensions (components) for vector variables.
double precision, dimension(:,:), allocatable dx
Module for including kdv source term in simulations adds over dimensions i.
Definition mod_kdv.t:3
subroutine kdv_add_source(qdt, ixil, ixol, wct, w, x, qsourcesplit, active)
w[iw]=w[iw]+qdt*S[wCT,qtC,x] where S is the source based on wCT within ixO
Definition mod_kdv.t:41
subroutine kdv_init()
Initialize the module.
Definition mod_kdv.t:33
subroutine kdv_get_dt(w, ixil, ixol, dtnew, dxd, x)
Definition mod_kdv.t:95
Module containing the physics routines for scalar nonlinear equation.
logical, public, protected nonlinear_particles
Whether particles module is added.
integer, public, protected nonlinear_flux_type
switch between burgers (i.e. rho**2) or nonconvex flux (i.e. rho**3)
logical, public, protected kdv_source_term
whether the KdV source term is added
integer, public, protected rho_
index of the single scalar unknown
subroutine, public nonlinear_phys_init()
subroutine, public nonlinear_get_v(w, x, ixil, ixol, idim, v)
Module containing all the particle routines.
subroutine particles_init()
Initialize particle data and parameters.
This module defines the procedures of a physics module. It contains function pointers for the various...
Definition mod_physics.t:4
procedure(sub_convert), pointer phys_to_primitive
Definition mod_physics.t:55
procedure(sub_write_info), pointer phys_write_info
Definition mod_physics.t:77
procedure(sub_get_flux), pointer phys_get_flux
Definition mod_physics.t:64
procedure(sub_get_cbounds), pointer phys_get_cbounds
Definition mod_physics.t:63
procedure(sub_get_dt), pointer phys_get_dt
Definition mod_physics.t:67
procedure(sub_add_source_geom), pointer phys_add_source_geom
Definition mod_physics.t:68
integer, parameter flux_default
Indicates a normal flux.
Definition mod_physics.t:24
integer, dimension(:, :), allocatable flux_type
Array per direction per variable, which can be used to specify that certain fluxes have to be treated...
Definition mod_physics.t:21
procedure(sub_convert), pointer phys_to_conserved
Definition mod_physics.t:54
character(len=name_len) physics_type
String describing the physics type of the simulation.
Definition mod_physics.t:50
procedure(sub_add_source), pointer phys_add_source
Definition mod_physics.t:69
procedure(sub_get_cmax), pointer phys_get_cmax
Definition mod_physics.t:57
logical phys_energy
Solve energy equation or not.
Definition mod_physics.t:35
integer nw
Total number of variables.
integer number_species
number of species: each species has different characterictic speeds and should be used accordingly in...
integer nwflux
Number of flux variables.