2D AMRCLAW
setdomflags.f
Go to the documentation of this file.
1 c
19 
20 c -----------------------------------------------------------------------------------
21 c
22  subroutine setdomflags(mptr,igridflags,ilo,ihi,jlo,jhi,
23  . mbuff,lbase,lcheck,mibuff,mjbuff)
24 
25  use amr_module
26 
27  integer*1 igridflags(ilo-mbuff:ihi+mbuff,jlo-mbuff:jhi+mbuff)
28 c icopy is dimensioned large enough, but will be used at several sizes
29 c and accessed using lo_i-mbuff:hi_i+mbuff, etc.
30 c
31  integer*1 icopy(mibuff,mjbuff)
32  dimension ist(3), iend(3), jst(3), jend(3), ishift(3), jshift(3)
33  dimension igridst(lcheck), igridend(lcheck)
34  dimension jgridst(lcheck), jgridend(lcheck)
35  logical borderx, bordery
36 
37 c
38 c set domain flags for this grid only, enlarged by buffer zone. check if any other base grids
39 c are in exterior or first interior border cell and mark ok.
40 c note that interior of base grids 1 away from edge are automatically ok for proper nesting
41 c will shrink gridflags after setting to get proper nesting region
42 c
43 c 1. initialize this grids domain flags to 0, at lcheck
44  igridflags = 0
45 c
46 c ... if lbase coarse than lcheck, set initial indices, before upscaling, for base transfer
47 c so that dont have entire base grid upscaled
48  igridst(lcheck) = ilo
49  igridend(lcheck) = ihi
50  jgridst(lcheck) = jlo
51  jgridend(lcheck) = jhi
52  do lc = lcheck-1,lbase,-1 !NB: may be a 0 trip do loop, not old fortran
53  ilo_coarse = floor(dfloat(igridst(lc+1))/intratx(lc))
54  jlo_coarse = floor(dfloat(jgridst(lc+1))/intraty(lc))
55  ihi_coarse = ceiling(dfloat(igridend(lc+1))/intratx(lc)) - 1
56  jhi_coarse = ceiling(dfloat(jgridend(lc+1))/intraty(lc)) - 1
57  if (ihi_coarse*intratx(lc) .lt. igridend(lc+1))
58  . ihi_coarse = ihi_coarse+1
59  if (jhi_coarse*intraty(lc) .lt. jgridend(lc+1))
60  . jhi_coarse = jhi_coarse+1
61  igridend(lc) = ihi_coarse
62  jgridend(lc) = jhi_coarse
63  igridst(lc) = ilo_coarse
64  jgridst(lc) = jlo_coarse
65  end do
66 ! get out coarsened indices in case level lbase == lcheck (zero trip loop)
67  ilo_coarse = igridst(lbase)
68  ihi_coarse = igridend(lbase)
69  jlo_coarse = jgridst(lbase)
70  jhi_coarse = jgridend(lbase)
71  ! If we project grid mptr to level "lbase" to get a grid on that
72  ! level, ilo_coarse is global index of its left border and similarly
73  ! for other three
74 
75 c
76 c 3. loop over all intersecting grids at base level staying fixed
77 c to make the proper nesting dodmain.
78 c set the buffer zone in igridflags to 1 if nested
79 c this is so when shrink by one you dont lose too much area.
80 c
81  mbase = lstart(lbase)
82  20 continue
83 
84  iblo = node(ndilo,mbase) ! if base grid coarser, need to scale up
85  ibhi = node(ndihi,mbase) ! if same grid will just mark interior cells as 1
86  jblo = node(ndjlo,mbase)
87  jbhi = node(ndjhi,mbase)
88 c
89 c 3.5 if periodic bcs, then if grids buffer sticks out, will have to wrap the
90 c coordinates and flag any intersecting base grids for wrapped buffer.
91 c do here instead of above since cant coarsen mbuff same way you can for regular grid
92 c also grid itself (without enlarged mbuff zone) doesnt stick out
93 
94  borderx = (ilo_coarse.le. 0 .or. ihi_coarse.ge.iregsz(lbase)-1)
95  bordery = (jlo_coarse.le. 0 .or. jhi_coarse.ge.jregsz(lbase)-1)
96  if ((xperdom .and. borderx) .or. (yperdom .and. bordery)) then
97  call setindices(ist,iend,jst,jend,
98  . ilo_coarse-mbuff,ihi_coarse+mbuff,
99  . jlo_coarse-mbuff,jhi_coarse+mbuff,
100  . ishift,jshift,lbase)
101 
102  do 25 i = 1, 3
103  i1 = max(ilo_coarse-mbuff,ist(i))
104  i2 = min(ihi_coarse+mbuff,iend(i))
105  do 24 j = 1, 3
106  j1 = max(jlo_coarse-mbuff,jst(j))
107  j2 = min(jhi_coarse+mbuff, jend(j))
108 
109  if (.not. ((i1 .le. i2) .and. (j1 .le. j2))) go to 24 ! part of patch in this region
110 c
111 c part of patch is in this region [i,j]
112 c periodically wrap and fill if it intersects with grid mbase
113 c note: this is done in two steps in hopes of greater clarity
114 
115 
116 c usual check would be -> if ((i1 .gt. i2) .or. (j1 .gt. j2)) go to 24 ! no patch
117 c cant do that since have not yet included buffer zone - which is the part that would get wrapped
118 
119 c patch exist. does it intersect with mbase grid?
120 c use wrapped coords of this grid to test if intersects with base grid
121  ixlo = max(iblo,i1+ishift(i))
122  ixhi = min(ibhi,i2+ishift(i))
123  jxlo = max(jblo,j1+jshift(j))
124  jxhi = min(jbhi,j2+jshift(j))
125 c
126  if ((ixlo .gt. ixhi) .or. (jxlo .gt. jxhi)) go to 24 !this grid doesnt intersect
127 c
128 c if wrapped region does intersect, be careful to set the INTERSECTED part of
129 c the UNWRAPPED region of original enlarged grid
130  ixlo_unwrapped = ixlo - ishift(i)
131  ixhi_unwrapped = ixhi - ishift(i)
132  jxlo_unwrapped = jxlo - jshift(j)
133  jxhi_unwrapped = jxhi - jshift(j)
134  call coarsegridflagset(igridflags,
135  . ixlo_unwrapped,ixhi_unwrapped,
136  . jxlo_unwrapped,jxhi_unwrapped,
137  . ilo_coarse,ihi_coarse,
138  . jlo_coarse,jhi_coarse,mbuff)
139 
140  24 continue
141  25 continue
142 
143  else
144  ixlo = max(iblo,ilo_coarse-mbuff)
145  ixhi = min(ibhi,ihi_coarse+mbuff)
146  jxlo = max(jblo,jlo_coarse-mbuff)
147  jxhi = min(jbhi,jhi_coarse+mbuff)
148 c
149 c does this patch intersect mbase grid?
150  if (.not.((ixlo .le. ixhi) .and. (jxlo .le. jxhi))) go to 30 !this grid doesnt intersect
151 c
152 c use subroutine call since dimension of igridflags not same as above declaration
153 c when on coarser grids
154  call coarsegridflagset(igridflags,ixlo,ixhi,jxlo,jxhi,
155  . ilo_coarse,ihi_coarse,
156  . jlo_coarse,jhi_coarse,mbuff)
157  endif
158 
159  30 mbase = node(levelptr,mbase)
160  if (mbase .ne. 0) go to 20
161 c
162 c 3.5 set any part of grid buffer zone to 1 that is at physical boundary
163  call setphysbndryflags(igridflags,ilo_coarse,ihi_coarse,
164  . jlo_coarse,jhi_coarse,mbuff,lbase)
165 
166 c 4. done setting flags on base level. next step is to transfer the
167 c properly nested domain flags to lcheck - i.e. upscale to level needed
168 c first shrink by 1 for actual nested region.
169 c always shrink once - so works if lcheck same as lbase
170 c if going up 1 level each one needs to be nested, so still shrink first before upsizing
171 c
172 c after loop above, dom flags in igridflags, copy to icopy (in subr for dimensioning reasons)
173  call griddomcopy(icopy,igridflags,ilo_coarse,ihi_coarse,
174  . jlo_coarse,jhi_coarse,mbuff)
175 c
176 c shrink from icopy to dom2 flag array. This is where shrinking occurs if
177 c lbase = lcheck, for proper nesting
178  call griddomshrink(icopy,ilo_coarse,ihi_coarse,jlo_coarse,
179  . jhi_coarse,mbuff,
180  . alloc(node(domflags2,mptr)),lbase)
181 
182  do 40 lev = lbase+1, lcheck
183 c ### for each level that upsize, calculate new coords starting from
184 c ### actual fine grid and recoarsening down to needed level
185 c ### cant take previous coarse coords and refine, since may be
186 c ### too large. grid prob. not anchored at base grid corner.
187  ilo_fine = igridst(lev)
188  ihi_fine = igridend(lev)
189  jlo_fine = jgridst(lev)
190  jhi_fine = jgridend(lev)
191 c
192 c flags in dom2, upsize to icopy array with finer dimensions
193  call griddomup(alloc(node(domflags2,mptr)),icopy,
194  . ilo_coarse,ihi_coarse,jlo_coarse,jhi_coarse,
195  . mbuff,lev-1,
196  . ilo_fine,ihi_fine,jlo_fine,jhi_fine)
197 c flags in icopy, shrink one back to dom2
198  call griddomshrink(icopy,ilo_fine,ihi_fine,jlo_fine,jhi_fine,
199  . mbuff,alloc(node(domflags2,mptr)),lev)
200  ilo_coarse = ilo_fine
201  ihi_coarse = ihi_fine
202  jlo_coarse = jlo_fine
203  jhi_coarse = jhi_fine
204 40 continue
205 c
206  return
207  end
208 
subroutine griddomup(iflags, iflags2, ilo, ihi, jlo, jhi, mbuff, lev, ilofine, ihifine, jlofine, jhifine)
iflags described flagged cells in a rectangular region described by ilo, ihi, jlo, jhi in level lev index space This subroutine projects iflags to iflag, which has flagging information in a rectangular region described by ilofine, ihifine, jlofine, jhifine in level lev+1 index space
Definition: griddomup.f:18
subroutine setphysbndryflags(iflags, ilo, ihi, jlo, jhi, mbuff, level)
If grid borders the physical domain then set domain flags to 1 in buffer zone (which is outside the p...
integer, dimension(maxlv) iregsz
Definition: amr_module.f90:198
subroutine griddomshrink(iflags2, ilo, ihi, jlo, jhi, mbuff, iflags, level)
Shrink domain flags one cell for allowable properly nested domain This is needed even for lcheck = lb...
Definition: griddomshrink.f:26
integer, parameter ndihi
global i index of right border of this grid
Definition: amr_module.f90:111
integer, dimension(maxlv) jregsz
Definition: amr_module.f90:198
integer, dimension(nsize, maxgr) node
Definition: amr_module.f90:198
logical yperdom
Definition: amr_module.f90:230
integer, parameter domflags2
domain flags, indexed within level-of-this-grid level index space
Definition: amr_module.f90:132
integer, parameter ndilo
global i index of left border of this grid
Definition: amr_module.f90:108
integer, parameter ndjlo
global j index of lower border of this grid
Definition: amr_module.f90:114
integer, dimension(maxlv) lstart
Definition: amr_module.f90:198
subroutine coarsegridflagset(iflags, ixlo, ixhi, jxlo, jxhi, ilo_coarse, ihi_coarse, jlo_coarse, jhi_coarse, mbuff)
Flag a whole subregion from (ixlo,ixhi) to (jxlo, jxhi) with integer.
integer, dimension(maxlv) intraty
Definition: amr_module.f90:198
subroutine setindices(ist, iend, jst, jend, ilo, ihi, jlo, jhi, ishift, jshift, level)
Definition: setIndices.f:6
integer, parameter ndjhi
global j index of upper border of this grid
Definition: amr_module.f90:117
logical xperdom
Definition: amr_module.f90:230
integer, dimension(maxlv) intratx
Definition: amr_module.f90:198
integer, parameter levelptr
node number (index) of next grid on the same level
Definition: amr_module.f90:35
subroutine setdomflags(mptr, igridflags, ilo, ihi, jlo, jhi, mbuff, lbase, lcheck, mibuff, mjbuff)
set domain flags (not AMR flags) for grid mptr (only), enlarged by buffer zone.
Definition: setdomflags.f:24
subroutine griddomcopy(i1, i2, ilo, ihi, jlo, jhi, mbuff)
Definition: griddomcopy.f:5
The module contains the definition of a "node descriptor" as well as other global variables used duri...
Definition: amr_module.f90:21
real(kind=8), dimension(:), allocatable alloc
Definition: amr_module.f90:218