MPI-AMRVAC  3.1
The MPI - Adaptive Mesh Refinement - Versatile Advection Code (development version)
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 
24 contains
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 
32  namelist /nonlinear_list/ nonlinear_flux_type, kdv_source_term, nonlinear_particles
33 
34  do n = 1, size(files)
35  open(unitpar, file=trim(files(n)), status='old')
36  read(unitpar, nonlinear_list, end=111)
37 111 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 
60  subroutine nonlinear_phys_init()
62  use mod_physics
63  use mod_kdv, only: kdv_init
64  use mod_particles, only: particles_init
65 
66  call nonlinear_params_read(par_files)
67 
68  physics_type = "nonlinear"
69  phys_energy = .false.
70  ! Whether diagonal ghost cells are required for the physics
71  phys_req_diagonal = .false.
73 
74  allocate(start_indices(number_species),stop_indices(number_species))
75  ! set the index of the first flux variable for species 1
76  start_indices(1)=1
77  rho_ = var_set_rho()
78 
79  ! set number of variables which need update ghostcells
80  nwgc=nwflux
81 
82  ! set the index of the last flux variable for species 1
83  stop_indices(1)=nwflux
84 
85  ! Number of variables need reconstruction in w
86  nw_recon=nwflux
87 
88  ! Check whether custom flux types have been defined
89  if (.not. allocated(flux_type)) then
90  allocate(flux_type(ndir, nw))
92  else if (any(shape(flux_type) /= [ndir, nw])) then
93  call mpistop("phys_check error: flux_type has wrong shape")
94  end if
95 
105 
106  if (kdv_source_term) call kdv_init()
107 
108  ! Initialize particles module
109  if (nonlinear_particles) then
110  call particles_init()
111  phys_req_diagonal = .true.
112  end if
113 
114  end subroutine nonlinear_phys_init
115 
116  subroutine nonlinear_to_conserved(ixI^L, ixO^L, w, x)
118  integer, intent(in) :: ixI^L, ixO^L
119  double precision, intent(inout) :: w(ixI^S, nw)
120  double precision, intent(in) :: x(ixI^S, 1:^ND)
121 
122  ! Do nothing (primitive and conservative are equal for nonlinear module)
123  end subroutine nonlinear_to_conserved
124 
125  subroutine nonlinear_to_primitive(ixI^L, ixO^L, w, x)
127  integer, intent(in) :: ixI^L, ixO^L
128  double precision, intent(inout) :: w(ixI^S, nw)
129  double precision, intent(in) :: x(ixI^S, 1:^ND)
130 
131  ! Do nothing (primitive and conservative are equal for nonlinear module)
132  end subroutine nonlinear_to_primitive
133 
134  subroutine nonlinear_get_v(w, x, ixI^L, ixO^L, idim, v)
136  integer, intent(in) :: ixi^l, ixo^l, idim
137  double precision, intent(in) :: w(ixi^s, nw), x(ixi^s, 1:^nd)
138  double precision, intent(out) :: v(ixi^s)
139 
140  select case(nonlinear_flux_type)
141  case(1)
142  v(ixo^s)=w(ixo^s,rho_)
143  case(2)
144  v(ixo^s)=3.0d0*w(ixo^s,rho_)**2
145  case default
146  call mpistop('Undefined fluxtype: set nonlinear_flux_type to 1 or 2')
147  end select
148 
149  end subroutine nonlinear_get_v
150 
151  subroutine nonlinear_get_cmax(w, x, ixI^L, ixO^L, idim, cmax)
153  integer, intent(in) :: ixI^L, ixO^L, idim
154  double precision, intent(in) :: w(ixI^S, nw), x(ixI^S, 1:^ND)
155  double precision, intent(inout) :: cmax(ixI^S)
156 
157  call nonlinear_get_v(w, x, ixi^l, ixo^l, idim, cmax)
158 
159  cmax(ixo^s) = abs(cmax(ixo^s))
160 
161  end subroutine nonlinear_get_cmax
162 
163  subroutine nonlinear_get_cbounds(wLC, wRC, wLp, wRp, x, ixI^L, ixO^L, idim,Hspeed, cmax, cmin)
165  use mod_variables
166  integer, intent(in) :: ixI^L, ixO^L, idim
167  double precision, intent(in) :: wLC(ixI^S, nw), wRC(ixI^S,nw)
168  double precision, intent(in) :: wLp(ixI^S, nw), wRp(ixI^S,nw)
169  double precision, intent(in) :: x(ixI^S, 1:^ND)
170  double precision, intent(inout) :: cmax(ixI^S,1:number_species)
171  double precision, intent(inout), optional :: cmin(ixI^S,1:number_species)
172  double precision, intent(in) :: Hspeed(ixI^S,1:number_species)
173  double precision :: wmean(ixI^S,nw)
174 
175  ! since get_v depends on w, the first argument should be some average over the
176  ! left and right state
177  wmean(ixo^s,1:nwflux)=0.5d0*(wlc(ixo^s,1:nwflux)+wrc(ixo^s,1:nwflux))
178  call nonlinear_get_v(wmean, x, ixi^l, ixo^l, idim, cmax(ixi^s,1))
179 
180  if (present(cmin)) then
181  cmin(ixo^s,1) = min(cmax(ixo^s,1), zero)
182  cmax(ixo^s,1) = max(cmax(ixo^s,1), zero)
183  else
184  cmax(ixo^s,1) = maxval(abs(cmax(ixo^s,1)))
185  end if
186 
187  end subroutine nonlinear_get_cbounds
188 
189  subroutine nonlinear_get_dt(w, ixI^L, ixO^L, dtnew, dx^D, x)
191  use mod_kdv, only: kdv_get_dt
192 
193  integer, intent(in) :: ixI^L, ixO^L
194  double precision, intent(in) :: dx^D, x(ixI^S, 1:^ND)
195  double precision, intent(in) :: w(ixI^S, 1:nw)
196  double precision, intent(inout) :: dtnew
197 
198  dtnew = bigdouble
199 
200  if(kdv_source_term) then
201  call kdv_get_dt(w, ixi^l, ixo^l, dtnew, dx^d, x)
202  endif
203  end subroutine nonlinear_get_dt
204 
205  ! here we select the flux according to the nonlinear_flux_type parameter
206  subroutine nonlinear_get_flux(wC, w, x, ixI^L, ixO^L, idim, f)
208  integer, intent(in) :: ixI^L, ixO^L, idim
209  double precision, intent(in) :: wC(ixI^S, 1:nw)
210  double precision, intent(in) :: w(ixI^S, 1:nw)
211  double precision, intent(in) :: x(ixI^S, 1:^ND)
212  double precision, intent(out) :: f(ixI^S, nwflux)
213 
214  select case(nonlinear_flux_type)
215  case(1)
216  f(ixo^s,rho_)=half*w(ixo^s,rho_)**2
217  case(2)
218  f(ixo^s,rho_)=w(ixo^s,rho_)**3
219  case default
220  call mpistop('Undefined fluxtype: set nonlinear_flux_type to 1 or 2')
221  end select
222 
223  end subroutine nonlinear_get_flux
224 
225  subroutine nonlinear_add_source_geom(qdt, dtfactor, ixI^L, ixO^L, wCT,wprim, w, x)
226 
227  ! Add geometrical source terms to w
228  ! There are no geometrical source terms
229 
231 
232  integer, intent(in) :: ixI^L, ixO^L
233  double precision, intent(in) :: qdt, dtfactor, x(ixI^S, 1:^ND)
234  double precision, intent(inout) :: wCT(ixI^S, 1:nw), wprim(ixI^S,1:nw),w(ixI^S, 1:nw)
235 
236  end subroutine nonlinear_add_source_geom
237 
238  subroutine nonlinear_add_source(qdt, dtfactor, ixI^L,ixO^L,wCT,wCTprim,w,x,qsourcesplit,active)
240  use mod_kdv, only: kdv_add_source
241 
242  integer, intent(in) :: ixI^L, ixO^L
243  double precision, intent(in) :: qdt,dtfactor
244  double precision, intent(in) :: wCT(ixI^S, 1:nw),wCTprim(ixI^S,1:nw), x(ixI^S, 1:ndim)
245  double precision, intent(inout) :: w(ixI^S, 1:nw)
246  logical, intent(in) :: qsourcesplit
247  logical, intent(inout) :: active
248 
249  if(kdv_source_term) then
250  call kdv_add_source(qdt,ixi^l,ixo^l,wct,w,x,qsourcesplit,active)
251  end if
252 
253  end subroutine nonlinear_add_source
254 
255 end 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
logical use_particles
Use particles module or not.
character(len=std_len), dimension(:), allocatable par_files
Which par files are used as input.
integer ndir
Number of spatial dimensions (components) for vector variables.
Module for including kdv source term in simulations adds over dimensions i.
Definition: mod_kdv.t:3
subroutine kdv_get_dt(w, ixIL, ixOL, dtnew, dxD, x)
Definition: mod_kdv.t:95
subroutine kdv_init()
Initialize the module.
Definition: mod_kdv.t:33
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
Module containing the physics routines for scalar nonlinear equation.
subroutine nonlinear_add_source_geom(qdt, dtfactor, ixIL, ixOL, wCT, wprim, w, x)
subroutine nonlinear_get_flux(wC, w, x, ixIL, ixOL, idim, f)
logical, public, protected nonlinear_particles
Whether particles module is added.
subroutine nonlinear_get_dt(w, ixIL, ixOL, dtnew, dxD, x)
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)
subroutine nonlinear_get_cmax(w, x, ixIL, ixOL, idim, cmax)
subroutine nonlinear_get_cbounds(wLC, wRC, wLp, wRp, x, ixIL, ixOL, idim, Hspeed, cmax, cmin)
subroutine nonlinear_add_source(qdt, dtfactor, ixIL, ixOL, wCT, wCTprim, w, x, qsourcesplit, active)
subroutine nonlinear_to_conserved(ixIL, ixOL, w, x)
subroutine nonlinear_write_info(fh)
Write this module's parameters to a snapshot.
subroutine nonlinear_to_primitive(ixIL, ixOL, w, x)
Module containing all the particle routines.
Definition: mod_particles.t:2
subroutine particles_init()
Initialize particle data and parameters.
Definition: mod_particles.t:15
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:59
procedure(sub_write_info), pointer phys_write_info
Definition: mod_physics.t:81
procedure(sub_get_flux), pointer phys_get_flux
Definition: mod_physics.t:68
logical phys_req_diagonal
Whether the physics routines require diagonal ghost cells, for example for computing a curl.
Definition: mod_physics.t:36
procedure(sub_get_cbounds), pointer phys_get_cbounds
Definition: mod_physics.t:67
procedure(sub_get_dt), pointer phys_get_dt
Definition: mod_physics.t:71
procedure(sub_add_source_geom), pointer phys_add_source_geom
Definition: mod_physics.t:72
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:58
character(len=name_len) physics_type
String describing the physics type of the simulation.
Definition: mod_physics.t:54
procedure(sub_add_source), pointer phys_add_source
Definition: mod_physics.t:73
procedure(sub_get_cmax), pointer phys_get_cmax
Definition: mod_physics.t:61
logical phys_energy
Solve energy equation or not.
Definition: mod_physics.t:39
integer nwflux
Number of flux variables.
Definition: mod_variables.t:8