18 recursive subroutine prefilrecur(level,nvar,valbig,auxbig,naux,time,mitot,mjtot, &
19 nrowst,ncolst,ilo,ihi,jlo,jhi,iglo,ighi,jglo,jghi,patchonly)
23 use amr_module, only: iregsz, jregsz, nghost, xlower, ylower, xperdom, yperdom
24 use amr_module, only: spheredom, hxposs, hyposs, needs_to_be_set, alloc
29 integer,
intent(in) :: level, nvar, naux, mitot, mjtot
30 integer,
intent(in) :: ilo,ihi,jlo,jhi,iglo,ighi,jglo,jghi
31 real(kind=8),
intent(in) :: time
37 real(kind=8),
intent(in out) :: valbig(nvar,mitot,mjtot)
38 real(kind=8),
intent(in out) :: auxbig(naux,mitot,mjtot)
41 integer :: i, j, ii, jj, ivar, ng, i1, i2, j1, j2, nrowst, ncolst
42 integer :: iputst, jputst, mi, mj, locpatch, locpaux
43 integer :: jbump, iwrap1, iwrap2, jwrap1, tmp, locflip, rect(4)
44 real(kind=8) :: xlwrap, ybwrap
48 integer :: ist(3), iend(3), jst(3), jend(3), ishift(3), jshift(3)
49 real(kind=8) :: scratch(max(mitot,mjtot)*nghost*nvar)
50 real(kind=8) :: scratchaux(max(mitot,mjtot)*nghost*naux)
53 real(kind=8) :: valpatch((ihi-ilo+1) * (jhi-jlo+1) * nvar)
54 real(kind=8) :: auxpatch((ihi-ilo+1) * (jhi-jlo+1) * naux)
69 ist(3) = iregsz(level)
71 iend(2) = iregsz(level)-1
73 ishift(1) = iregsz(level)
75 ishift(3) = -iregsz(level)
77 ist(1) = iregsz(level)
79 ist(3) = iregsz(level)
88 if (yperdom .or. spheredom)
then
91 jst(3) = jregsz(level)
93 jend(2) = jregsz(level)-1
95 jshift(1) = jregsz(level)
97 jshift(3) = -jregsz(level)
99 jst(1) = jregsz(level)
101 jst(3) = jregsz(level)
117 i1 = max(ilo, ist(i))
118 i2 = min(ihi, iend(i))
119 if (i1 .gt. i2) go to 20
122 j1 = max(jlo, jst(j))
123 j2 = min(jhi, jend(j))
127 if (.not. spheredom .or. j .eq. 2)
then
131 if (mi .gt. (ihi-ilo+1) .or. mj .gt. (jhi-jlo+1))
then
132 write(*,*)
" prefilp: not big enough dimension"
135 call
auxcopyin(auxpatch,mi,mj,auxbig,mitot,mjtot,naux,i1,i2,j1,j2, &
138 call
filrecur(level,nvar,valpatch,auxpatch,naux,time,mi,mj, &
139 1,1,i1+ishift(i),i2+ishift(i),j1+jshift(j),j2+jshift(j),.true.,msrc)
141 call
patchcopyout(nvar,valpatch,mi,mj,valbig,mitot,mjtot,i1,i2,j1,j2, &
151 if (j1 < 0) jbump = abs(j1)
152 if (j2 >= jregsz(level)) jbump = -(j2+1-jregsz(level))
155 iwrap1 = i1 + ishift(i)
156 iwrap2 = i2 + ishift(i)
158 iwrap1 = iregsz(level) - iwrap1 -1
159 iwrap2 = iregsz(level) - iwrap2 -1
166 xlwrap = xlower + iwrap1*hxposs(level)
167 ybwrap = ylower + jwrap1*hyposs(level)
170 scratchaux = needs_to_be_set
171 call
setaux(ng,mi,mj,xlwrap,ybwrap,hxposs(level),hyposs(level),naux,scratchaux)
174 rect = [iwrap1,iwrap2,j1+jbump,j2+jbump]
175 call
filrecur(level,nvar,scratch,scratchaux,naux,time,mi, &
176 mj,1,1,iwrap1,iwrap2,j1+jbump,j2+jbump,.false.,msrc)
185 valbig(ivar,nrowst+(ii-ilo),ncolst+(jj-jlo)) = &
200 integer pure function iadd(n,i,j)
202 integer,
intent(in) :: n, i, j
203 iadd = locflip + n-1 + nvar*((j-1)*mi+i-1)
208 integer,
intent(in) :: n, i, j
218 subroutine patchcopyout(nvar,valpatch,mi,mj,valbig,mitot,mjtot,i1,i2,j1,j2,iglo,jglo)
227 integer :: mi, mj, nvar, mitot, mjtot, i1, i2,j1, j2, iglo, ighi, jglo, jghi
230 real(kind=8),
intent(in out) :: valbig(nvar,mitot,mjtot)
231 real(kind=8),
intent(in out) :: valpatch(nvar,mi,mj)
243 valbig(:,ist:ist+mi-1, jst:jst+mj-1) = valpatch
249 subroutine auxcopyin(auxPatch,mi,mj,auxbig,mitot,mjtot,naux,i1,i2,j1,j2,iglo,jglo)
258 integer :: mi, mj, naux, mitot, mjtot, i1, i2,j1, j2, iglo, ighi, jglo, jghi
261 real(kind=8),
intent(in out) :: auxbig(naux,mitot,mjtot)
262 real(kind=8),
intent(in out) :: auxpatch(naux,mi,mj)
274 auxpatch(:,1:mi,1:mj) = auxbig(:,ist:ist+mi-1, jst:jst+mj-1)
subroutine patchcopyout(nvar, valpatch, mi, mj, valbig, mitot, mjtot, i1, i2, j1, j2, iglo, jglo)
recursive subroutine prefilrecur(level, nvar, valbig, auxbig, naux, time, mitot, mjtot, nrowst, ncolst, ilo, ihi, jlo, jhi, iglo, ighi, jglo, jghi, patchOnly)
integer pure function iaddscratch(n, i, j)
integer pure function iadd(ivar, i, j)
recursive subroutine filrecur(level, nvar, valbig, aux, naux, t, mitot, mjtot, nrowst, ncolst, ilo, ihi, jlo, jhi, patchOnly, msrc)
Fill a region (patch) described by:
subroutine auxcopyin(auxPatch, mi, mj, auxbig, mitot, mjtot, naux, i1, i2, j1, j2, iglo, jglo)
subroutine setaux(mbc, mx, my, xlower, ylower, dx, dy, maux, aux)