2D AMRCLAW
baseCheck.f
Go to the documentation of this file.
1 c
2 c ----------------------------------------------------------------
3 c
4  logical function basecheck(mnew,lbase,ilo,ihi,jlo,jhi,
5  . nvar,naux,thisbuff)
6 
7  use amr_module
8  implicit double precision (a-h, o-z)
9 
10  logical debug/.true./
11  integer ist(3),iend(3),jst(3),jend(3),ishift(3),jshift(3)
12  logical borderx, bordery
13  integer thisbuff
14 
15 c index into alloc from iclo:ichi and jclo:jchi, not 0..leni/j.
16  iadd(i,j) = locm + i - iclo + leni*(j-jclo)
17 
18 c ::::::::::::::::::: baseCheck :::::::::::::::::::::::::::
19 c
20 c baseCheck - check that potential grid mnew is completely contained
21 c in coarser grids at level 'lbase' (>1) that will
22 c stay fixed during this regridding step
23 c
24 c this version tries to do it without using domflags
25 c slower but better if cant afford memory over entire domain
26 c
27 c mcheck is one bigger since for proper nesting, cell must be
28 c at least one away from boundary of a parent grid, unless
29 c on a domain boundary
30 c :::::::::::::::::::::::::::::::::::::::::::::::::::::::::
31 
32 
33 
34  levnew = node(nestlevel,mnew)
35  borderx = (ilo .eq. 0 .or. ihi .eq. iregsz(levnew)-1)
36  bordery = (jlo .eq. 0 .or. jhi .eq. jregsz(levnew)-1)
37 
38 
39  if (debug) write(outunit,100) mnew,lbase,ilo,ihi,jlo,jhi,levnew
40  100 format("NESTCK2 testing grid ",i5," base level ",i5,/,
41  . " new grid from ilo:hi: ",2i12," to ",2i12," at level ",i4)
42 c
43 c on to initializing for the given grid and its nest checking
44  levratx = 1
45  levraty = 1
46  do 5 lev = lbase, levnew-1
47  levratx = levratx * intratx(lev)
48  levraty = levraty * intraty(lev)
49  5 continue
50 
51 c widen by 1 cell (proper nesting), then project to lbase
52 c this might stick out of domain, fix later
53 c figure out size for scratch storage on base grid for testing
54  iclo = ilo
55  ichi = ihi
56  jclo = jlo
57  jchi = jhi
58  do lev = levnew-1,lbase,-1
59  iclo = iclo/intratx(lev)
60  ichi = ichi/intratx(lev)
61  jclo = jclo/intraty(lev)
62  jchi = jchi/intraty(lev)
63  iclo = iclo - 1
64  ichi = ichi + 1
65  jclo = jclo - 1
66  jchi = jchi + 1
67  if (debug) then
68  write(outunit,111) lev, iclo,ichi,jclo,jchi
69 111 format(10x,"at level",i5," projected coords ilo:hi:",2i10,
70  . " jlo:hi:",2i10)
71  endif
72  end do
73 c high end of integer grid index truncates during the divide
74 c if it were exactly lined up with coarser grid it would
75 c not be properly nested, but since we added one to the index
76 c space, we took care of that already.
77  if (debug) then
78  write(outunit,108) ilo-1,ihi+1,jlo-1,jhi+1
79  write(outunit,109) levratx,levraty
80  108 format(" enlarged (by 1) fine grid from ilo:hi:",2i12,
81  . " to jlo:hi:", 2i12)
82  109 format(" refinement factors to base grid of ", 2i12)
83  write(outunit,101) iclo,ichi,jclo,jchi
84  101 format("coarsened to lbase, grid from iclo:hi: ",2i12,
85  . " to jclo:hi:",2i12)
86  endif
87 
88  if (.not. (xperdom .and. borderx) .and.
89  . .not. (yperdom .and. bordery)) then
90  iclo = max(iclo,0) ! make sure in domain boundary when checking nesting
91  jclo = max(jclo,0)
92  ichi = min(ichi,iregsz(lbase)-1) ! subtract 1 since regsz is number of cells, so -1 is highest index
93  jchi = min(jchi,jregsz(lbase)-1)
94  endif
95 
96 
97  leni = ichi - iclo + 1
98  lenj = jchi - jclo + 1
99  lenrect = leni * lenj
100  locm = igetsp(lenrect)
101  alloc(locm:locm+lenrect-1) = 0.
102 c
103 c if mnew on domain boundary fix flags so ok.
104 c fix extra border, and first/last real edge
105  if (ilo .eq. 0 .and. .not. xperdom) then
106  do j = jclo,jchi
107  alloc(iadd(iclo,j)) = 1.
108  alloc(iadd(iclo+1,j)) = 1.
109  end do
110 
111  endif
112  if (ihi .eq. iregsz(levnew)-1 .and. .not. xperdom) then
113  do j = jclo, jchi
114  alloc(iadd(ichi,j)) = 1.
115  alloc(iadd(ichi-1,j)) = 1.
116  end do
117  endif
118  if (jlo .eq. 0 .and. .not. yperdom) then
119  do i = iclo,ichi
120  alloc(iadd(i,jclo)) = 1.
121  alloc(iadd(i,jclo+1)) = 1.
122  end do
123  endif
124  if (jhi .eq. jregsz(levnew)-1 .and. .not. yperdom) then
125  do i = iclo, ichi
126  alloc(iadd(i,jchi)) = 1.
127  alloc(iadd(i,jchi-1)) = 1.
128  end do
129  endif
130 
131  mptr = lstart(lbase)
132  20 iblo = node(ndilo, mptr) - thisbuff
133  ibhi = node(ndihi, mptr) + thisbuff
134  jblo = node(ndjlo, mptr) - thisbuff
135  jbhi = node(ndjhi, mptr) + thisbuff
136 c
137  ! non periodic case, base level coordinates, just mark if nested.
138  if ((.not. (xperdom .and. borderx)) .and.
139  . .not. (yperdom .and. bordery)) then
140  ixlo = max(iclo,iblo)
141  ixhi = min(ichi,ibhi)
142  jxlo = max(jclo,jblo)
143  jxhi = min(jchi,jbhi)
144  if (.not.((ixlo.le.ixhi) .and. (jxlo.le.jxhi))) go to 30
145  do jx = jxlo, jxhi
146  do ix = ixlo, ixhi
147  alloc(iadd(ix,jx))=1.
148  end do
149  end do
150  go to 30
151  endif
152 c
153 c periodic case: initialize for potential periodicity
154 c each patch divided into 9 regions (some may be empty)
155 c e.g. i from (ilo,-1), (0,iregsz(level)-1),(iregsz(level),ihi)
156 c except using enlarged grid (ilo-1 to ihi+1)
157 c
158  call setindices(ist,iend,jst,jend,iclo,ichi,jclo,jchi,
159  . ishift,jshift,lbase)
160 
161 c compare all regions of coarsened patch with one lbase grid at a time
162  do 25 i = 1, 3
163  i1 = max(iclo,ist(i))
164  i2 = min(ichi, iend(i))
165  do 25 j = 1, 3
166  j1 = max(jclo, jst(j))
167  j2 = min(jchi, jend(j))
168 
169  if (.not. ((i1 .le. i2) .and. (j1 .le. j2))) go to 25
170 c
171 c patch (possibly periodically wrapped) not empty.
172 c see if intersects base grid. wrap coords for periodicity
173  i1_shifted = i1 + ishift(i)
174  i2_shifted = i2 + ishift(i)
175  j1_shifted = j1 + jshift(j)
176  j2_shifted = j2 + jshift(j)
177 
178  ixlo = max(i1_shifted,iblo)
179  ixhi = min(i2_shifted,ibhi)
180  jxlo = max(j1_shifted,jblo)
181  jxhi = min(j2_shifted,jbhi)
182 
183  if (.not.((ixlo.le.ixhi) .and. (jxlo.le.jxhi))) go to 25
184 c mark intersected regions with 1
185  do jx = jxlo, jxhi
186  do ix = ixlo, ixhi
187 c need to mark nesting of orig coords, not coarsened shifted indices
188  ix_unshifted = (ix - ishift(i)) ! back to unshifted coords
189  jx_unshifted = (jx - jshift(j)) ! to mark base grid nesting ok
190  alloc(iadd(ix_unshifted,jx_unshifted)) = 1.
191  end do
192  end do
193 
194  25 continue
195 
196  30 mptr = node(levelptr, mptr)
197  if (mptr .ne. 0) go to 20
198 
199 c output for debugging
200  if (debug) then
201  do 34 jj = jclo, jchi
202  j = jchi + jclo - jj
203  write(outunit,344)(int(alloc(iadd(i,j))), i=iclo,ichi)
204  344 format(110i1)
205  34 continue
206  endif
207 
208 c
209 c if any zeroes left mnew not nested
210 c
211  do 40 j = jclo, jchi
212  do 40 i = iclo, ichi
213  if (alloc(iadd(i,j)) .eq. 0) then
214  basecheck = .false.
215  go to 99
216  endif
217  40 continue
218 
219 c if made it here then grid is nested
220  basecheck = .true.
221 
222  99 call reclam(locm, lenrect)
223 
224  return
225  end
function igetsp(nwords)
Definition: igetsp.f:4
subroutine reclam(index, nwords)
Definition: reclam.f:4
logical function basecheck(mnew, lbase, ilo, ihi, jlo, jhi, nvar, naux, thisBuff)
Definition: baseCheck.f:4
integer pure function iadd(ivar, i, j)
Definition: intfil.f90:293
subroutine setindices(ist, iend, jst, jend, ilo, ihi, jlo, jhi, ishift, jshift, level)
Definition: setIndices.f:4