MPI-AMRVAC  3.0
The MPI - Adaptive Mesh Refinement - Versatile Advection Code
mod_source.t
Go to the documentation of this file.
1 !> Module for handling split source terms (split from the fluxes)
2 module mod_source
3  implicit none
4  public
5 
6  !> How to apply dimensional splitting to the source terms, see
7  !> @ref discretization.md
8  integer :: sourcesplit =-1
9  integer, parameter :: sourcesplit_sfs = 0
10  integer, parameter :: sourcesplit_sf = 1
11  integer, parameter :: sourcesplit_ssf = 2
12  integer, parameter :: sourcesplit_ssfss = 3
13 
14  public :: add_split_source
15  public :: addsource2
16 
17 contains
18 
19  subroutine add_split_source(prior)
25 
26  logical, intent(in) :: prior
27  ! This variable, later allocated on the thread stack, causes segmentation fault
28  ! when openmp is used with intel. That could be solved otherwise, by increasing
29  ! the thread stack size, but not using it at all could speed up.
30  !double precision :: w1(ixG^T,nw)
31  double precision :: qt
32  integer :: iigrid, igrid
33  logical :: src_active
34 
35  ! add stiff source terms via super time stepping
36  if(is_sts_initialized()) then
37  select case (sourcetype_sts)
39  if(prior) then
40  call sts_add_source(dt)
41  endif
43  if(.not. prior) then
44  call sts_add_source(dt)
45  endif
47  call sts_add_source(0.5d0*dt)
48  endselect
49  endif
50  src_active = .false.
51 
52  if ((.not.prior).and.&
54 
55  if (prior) then
56  qt=global_time
57  else
58  qt=global_time+dt
59  end if
60 
61  ! add normal split source terms
62  select case (sourcesplit)
63  case (sourcesplit_sfs)
64  !$OMP PARALLEL DO PRIVATE(igrid)
65  do iigrid=1,igridstail_active; igrid=igrids_active(iigrid);
66  block=>ps(igrid)
67  ^d&dxlevel(^d)=rnode(rpdx^d_,igrid);
68  call addsource2(0.5d0*dt,ixg^ll,ixm^ll,1,nw,qt,ps(igrid)%w,qt,ps(igrid)%w,&
69  ps(igrid)%x,.true.,src_active)
70  end do
71  !$OMP END PARALLEL DO
72  case (sourcesplit_sf)
73  !$OMP PARALLEL DO PRIVATE(igrid)
74  do iigrid=1,igridstail_active; igrid=igrids_active(iigrid);
75  block=>ps(igrid)
76  ^d&dxlevel(^d)=rnode(rpdx^d_,igrid);
77  call addsource2(dt ,ixg^ll,ixm^ll,1,nw,qt,ps(igrid)%w,qt,ps(igrid)%w,&
78  ps(igrid)%x,.true.,src_active)
79  end do
80  !$OMP END PARALLEL DO
81  case (sourcesplit_ssf)
82  !$OMP PARALLEL DO PRIVATE(igrid)
83  do iigrid=1,igridstail_active; igrid=igrids_active(iigrid);
84  block=>ps(igrid)
85  ^d&dxlevel(^d)=rnode(rpdx^d_,igrid);
86  call addsource2(0.5d0*dt,ixg^ll,ixg^ll,1,nw,qt,ps(igrid)%w,qt,ps(igrid)%w,&
87  ps(igrid)%x,.true.,src_active)
88  call addsource2(dt ,ixg^ll,ixm^ll,1,nw,qt,ps(igrid)%w,qt,ps(igrid)%w,&
89  ps(igrid)%x,.true.,src_active)
90  end do
91  !$OMP END PARALLEL DO
92  case (sourcesplit_ssfss)
93  !$OMP PARALLEL DO PRIVATE(igrid)
94  do iigrid=1,igridstail_active; igrid=igrids_active(iigrid);
95  block=>ps(igrid)
96  ^d&dxlevel(^d)=rnode(rpdx^d_,igrid);
97  call addsource2(0.25d0*dt,ixg^ll,ixg^ll,1,nw,qt,ps(igrid)%w,qt,ps(igrid)%w,&
98  ps(igrid)%x,.true.,src_active)
99  call addsource2(0.5d0*dt,ixg^ll,ixm^ll,1,nw,qt,ps(igrid)%w,qt,ps(igrid)%w,&
100  ps(igrid)%x,.true.,src_active)
101  end do
102  !$OMP END PARALLEL DO
103  case default
104  write(unitterm,*)'No such type of sourcesplit=',sourcesplit
105  call mpistop("Error: Unknown type of sourcesplit!")
106  end select
107 
108  if (.not. prior .and. associated(phys_global_source_after)) then
109  call phys_global_source_after(dt, qt, src_active)
110  end if
111 
112  if (src_active) then
113  call getbc(qt,0.d0,ps,iwstart,nwgc,phys_req_diagonal)
114  end if
115 
116  end subroutine add_split_source
117 
118  !> Add source within ixO for iws: w=w+qdt*S[wCT]
119  subroutine addsource2(qdt,ixI^L,ixO^L,iw^LIM,qtC,wCT,qt,&
120  w,x,qsourcesplit,src_active,wCTprim)
122  use mod_physics, only: phys_add_source
123  use mod_usr_methods, only: usr_source
124  ! differences with VAC is in iw^LIM and in declaration of ranges for wCT,w
125 
126  integer, intent(in) :: ixi^l, ixo^l, iw^lim
127  double precision, intent(in) :: qdt, qtc, qt
128  double precision, intent(in) :: wct(ixi^s,1:nw), x(ixi^s,1:ndim)
129  double precision, intent(inout) :: w(ixi^s,1:nw)
130  logical, intent(in) :: qsourcesplit
131  logical, intent(inout), optional :: src_active
132  double precision, intent(in), optional :: wctprim(ixi^s,1:nw)
133 
134  logical :: tmp_active
135 
136  tmp_active = .false.
137 
138  ! physics defined sources, typically explicitly added,
139  ! along with geometrical source additions
140  call phys_add_source(qdt,ixi^l,ixo^l,wct,w,x,qsourcesplit,tmp_active,wctprim)
141 
142  ! user defined sources, typically explicitly added
143  if ((qsourcesplit .eqv. source_split_usr) .and. associated(usr_source)) then
144  tmp_active = .true.
145  call usr_source(qdt,ixi^l,ixo^l,iw^lim,qtc,wct,qt,w,x)
146  end if
147 
148  if (present(src_active)) src_active = src_active .or. tmp_active
149 
150  end subroutine addsource2
151 
152 end module mod_source
subroutine mpistop(message)
Exit MPI-AMRVAC with an error message.
Definition: comm_lib.t:194
update ghost cells of all blocks including physical boundaries
subroutine getbc(time, qdt, psb, nwstart, nwbc, req_diag)
do update ghost cells of all blocks including physical boundaries
This module contains definitions of global parameters and variables and some generic functions/subrou...
type(state), pointer block
Block pointer for using one block and its previous state.
logical source_split_usr
Use split or unsplit way to add user's source terms, default: unsplit.
double precision global_time
The global simulation time.
integer, parameter ndim
Number of spatial dimensions for grid variables.
integer, dimension(:), allocatable, parameter d
integer, parameter unitterm
Unit for standard output.
double precision, dimension(:,:), allocatable rnode
Corner coordinates.
double precision, dimension(ndim) dxlevel
This module defines the procedures of a physics module. It contains function pointers for the various...
Definition: mod_physics.t:4
logical phys_req_diagonal
Whether the physics routines require diagonal ghost cells, for example for computing a curl.
Definition: mod_physics.t:27
procedure(sub_global_source), pointer phys_global_source_after
Definition: mod_physics.t:72
procedure(sub_add_source), pointer phys_add_source
Definition: mod_physics.t:71
Module for handling split source terms (split from the fluxes)
Definition: mod_source.t:2
integer sourcesplit
How to apply dimensional splitting to the source terms, see Discretization.
Definition: mod_source.t:8
integer, parameter sourcesplit_ssf
Definition: mod_source.t:11
integer, parameter sourcesplit_ssfss
Definition: mod_source.t:12
integer, parameter sourcesplit_sfs
Definition: mod_source.t:9
integer, parameter sourcesplit_sf
Definition: mod_source.t:10
subroutine, public addsource2(qdt, ixIL, ixOL, iwLIM, qtC, wCT, qt, w, x, qsourcesplit, src_active, wCTprim)
Add source within ixO for iws: w=w+qdt*S[wCT].
Definition: mod_source.t:121
subroutine, public add_split_source(prior)
Definition: mod_source.t:20
Generic supertimestepping method 1) in amrvac.par in sts_list set the following parameters which have...
integer, public sourcetype_sts
pure logical function, public is_sts_initialized()
integer, parameter, public sourcetype_sts_prior
integer, parameter, public sourcetype_sts_split
integer, parameter, public sourcetype_sts_after
procedure(subr3), pointer, public sts_add_source
Module with all the methods that users can customize in AMRVAC.
procedure(source), pointer usr_source