17 integer,
dimension(2^D&),
intent(in) :: child_igrid, child_ipe
18 integer,
intent(in) :: igrid, ipe
19 logical,
intent(in) :: active
28 if ((time_advance .and. active).or.convert.or.reset_grid)
then
34 call initial_condition(child_igrid(ic^d))
39 if(convert)
call dealloc_node(igrid)
48 integer,
dimension(2^D&),
intent(in) :: child_igrid, child_ipe
49 integer,
intent(in) :: igrid, ipe
51 integer :: ix^L, ichild, ixCo^L, ic^D
52 double precision :: dxCo^D, xComin^D, dxFi^D, xFimin^D
64 ichild=child_igrid(ic^d)
66 ixcomin^d=ixmlo^d+(ic^d-1)*
block_nx^d/2\
67 ixcomax^d=ixmhi^d+(ic^d-2)*
block_nx^d/2\
72 dxco^d,xcomin^d,dxfi^d,xfimin^d,igrid,ichild)
76 if (prolongprimitive)
call phys_to_conserved(ixg^ll,ix^l,ps(igrid)%w,ps(igrid)%x)
81 subroutine prolong_2nd(sCo,ixCo^L,sFi,dxCo^D,xComin^D,dxFi^D,xFimin^D,igridCo,igridFi)
86 integer,
intent(in) :: ixCo^L, igridFi, igridCo
87 double precision,
intent(in) :: dxCo^D, xComin^D, dxFi^D, xFimin^D
88 type(state),
intent(in) :: sCo
89 type(state),
intent(inout) :: sFi
91 integer :: ixCo^D, jxCo^D, hxCo^D, ixFi^D, ix^D, idim, iw, ixCg^L, el
92 double precision :: slopeL, slopeR, slopeC, signC, signR
93 double precision :: slope(nw,ndim)
94 double precision :: eta^D
97 associate(wco=>sco%w, wfi=>sfi%w)
99 {
do ixco^db = ixcg^lim^db
101 ixfi^db=2*(ixco^db-ixcomin^db)+ixmlo^db\}
104 hxco^d=ixco^d-
kr(^d,idim)\
105 jxco^d=ixco^d+
kr(^d,idim)\
108 slopel=wco(ixco^d,iw)-wco(hxco^d,iw)
109 sloper=wco(jxco^d,iw)-wco(ixco^d,iw)
110 slopec=half*(sloper+slopel)
113 signr=sign(one,sloper)
114 signc=sign(one,slopec)
132 slope(iw,idim)=signc*max(zero,min(dabs(slopec), &
133 signc*slopel,signc*sloper))
139 {
do ix^db=ixfi^db,ixfi^db+1 \}
148 eta^d=0.5d0*(dble(ix^d-ixfi^d)-0.5d0);
151 eta^d=(dble(ix^d-ixfi^d)-0.5d0)*(one-sfi%dvolume(ix^dd) &
152 /sum(sfi%dvolume(ixfi^d:ixfi^d+1^d%ix^dd))) \}
154 wfi(ix^d,1:nw) = wco(ixco^d,1:nw) &
155 + {(slope(1:nw,^d)*eta^d)+}
158 if(stagger_grid)
then
159 call already_fine(sfi,igridfi,fine_^l)
160 call prolong_2nd_stg(sco,sfi,ixco^l,ixm^ll,dxco^d,xcomin^d,dxfi^d,xfimin^d,.false.,fine_^l)
163 if(fix_small_values)
call phys_handle_small_values(prolongprimitive,wfi,sfi%x,ixg^ll,ixm^ll,
'prolong_2nd')
164 if(prolongprimitive)
call phys_to_conserved(ixg^ll,ixm^ll,wfi,sfi%x)
173 integer,
intent(in) :: ixCo^L
174 double precision,
intent(in) :: wCo(ixG^T,nw), xFi(ixG^T,1:ndim)
175 double precision,
intent(out) :: wFi(ixG^T,nw)
177 integer :: ixCo^D, ixFi^D, iw
180 {
do ixco^db = ixco^lim^db
181 ixfi^db=2*(ixco^db-ixcomin^db)+ixmlo^db\}
182 forall(iw=1:nw) wfi(ixfi^d:ixfi^d+1,iw)=wco(ixco^d,iw)
subroutine, public old_neighbors(child_igrid, child_ipe, igrid, ipe)
subroutine, public already_fine(sFi, ichild, fine_L)
This routine fills the fine faces before prolonging. It is the face equivalent of fix_conserve.
subroutine, public prolong_2nd_stg(sCo, sFi, ixCoLin, ixFiLin, dxCoD, xCominD, dxFiD, xFiminD, ghost, fine_Lin)
This subroutine performs a 2nd order prolongation for a staggered field F, preserving the divergence ...
subroutine, public dealloc_node(igrid)
subroutine, public alloc_node(igrid)
allocate arrays on igrid node
This module contains definitions of global parameters and variables and some generic functions/subrou...
integer, dimension(3, 3) kr
Kronecker delta tensor.
integer, parameter rpxmin
logical stagger_grid
True for using stagger grid.
integer block_nx
number of cells for each dimension in grid block excluding ghostcells
integer, dimension(:), allocatable, parameter d
integer ixm
the mesh range of a physical block without ghost cells
double precision, dimension(:,:), allocatable rnode
Corner coordinates.
logical slab_uniform
uniform Cartesian geometry or not (stretched Cartesian)
subroutine, public initial_condition(igrid)
fill in initial condition
This module defines the procedures of a physics module. It contains function pointers for the various...
procedure(sub_convert), pointer phys_to_primitive
procedure(sub_small_values), pointer phys_handle_small_values
procedure(sub_convert), pointer phys_to_conserved
subroutine prolong_1st(wCo, ixCoL, wFi, xFi)
do 1st order prolongation
subroutine prolong_grid(child_igrid, child_ipe, igrid, ipe)
prolong one block
subroutine prolong_2nd(sCo, ixCoL, sFi, dxCoD, xCominD, dxFiD, xFiminD, igridCo, igridFi)
do 2nd order prolongation
subroutine, public refine_grids(child_igrid, child_ipe, igrid, ipe, active)
refine one block to its children blocks