13 subroutine filval(val, mitot, mjtot, dx, dy, level, time, mic, &
14 mjc, xleft, xright, ybot, ytop, nvar, mptr, ilo, ihi, &
17 use amr_module, only: xlower, ylower, intratx, intraty, nghost, xperdom
18 use amr_module, only: yperdom, spheredom, xupper, yupper, alloc
19 use amr_module, only: outunit, needs_to_be_set, mcapa
22 use amr_module, only: timesetaux, timesetauxcpu
27 integer,
intent(in) :: mitot, mjtot, level, mic, mjc, nvar, mptr, ilo, ihi
28 integer,
intent(in) :: jlo, jhi, naux
29 real(kind=8),
intent(in) :: dx, dy, time, xleft, xright, ybot, ytop
32 real(kind=8),
intent(in out) :: val(nvar,mitot,mjtot), aux(naux,mitot,mjtot)
35 integer :: refinement_ratio_x, refinement_ratio_y, iclo, jclo, ichi, jchi, ng
36 integer :: ivar, i, j, ico, jco, ifine, jfine, nx, ny
37 real(kind=8) :: valc(nvar,mic,mjc), auxc(naux,mic,mjc)
38 real(kind=8) :: dx_coarse, dy_coarse, xl, xr, yb, yt, area
39 real(kind=8) :: s1m, s1p, slopex, slopey, xoff, yoff
40 real(kind=8) :: fliparray((mitot+mjtot)*nghost*(nvar+naux))
41 real(kind=8) ::
setflags(mitot,mjtot),maxauxdif,aux2(naux,mitot,mjtot)
45 integer :: clock_start, clock_finish, clock_rate
46 real(kind=8) cpu_start, cpu_finish
50 real(kind=8) :: get_max_speed
52 refinement_ratio_x = intratx(level-1)
53 refinement_ratio_y = intraty(level-1)
54 dx_coarse = dx * refinement_ratio_x
55 dy_coarse = dy * refinement_ratio_y
56 xl = xleft - dx_coarse
57 xr = xright + dx_coarse
67 iclo = ilo / refinement_ratio_x - 1
68 jclo = jlo / refinement_ratio_y - 1
69 ichi = (ihi + 1) / refinement_ratio_x - 1 + 1
70 jchi = (jhi + 1) / refinement_ratio_y - 1 + 1
74 if (xperdom .or. yperdom .or. spheredom)
then
75 call
preintcopy(valc,mic,mjc,nvar,iclo,ichi,jclo,jchi,level-1,fliparray)
77 call
intcopy(valc,mic,mjc,nvar,iclo,ichi,jclo,jchi,level-1,1,1)
81 auxc(1,:,:) = needs_to_be_set
82 if (xperdom .or. yperdom .or. spheredom)
then
83 call
preicall(valc,auxc,mic,mjc,nvar,naux,iclo,ichi,jclo,jchi, &
86 call
icall(valc,auxc,mic,mjc,nvar,naux,iclo,ichi,jclo,jchi,level-1,1,1)
100 call system_clock(clock_start,clock_rate)
101 call cpu_time(cpu_start)
102 call
setaux(ng,mic,mjc,xl,yb,dx_coarse,dy_coarse,naux,auxc)
103 call system_clock(clock_finish,clock_rate)
104 call cpu_time(cpu_finish)
105 timesetaux=timesetaux+clock_finish-clock_start
106 timesetauxcpu=timesetauxcpu+cpu_finish-cpu_start
108 call
bc2amr(valc,auxc,mic,mjc,nvar,naux,dx_coarse,dy_coarse,level-1,time,xl,xr,yb, &
109 yt,xlower,ylower,xupper,yupper,xperdom,yperdom,spheredom)
120 nx = mitot - 2*nghost
121 ny = mjtot - 2*nghost
123 if (naux .gt. 0)
then
129 aux(1,:,:) = needs_to_be_set
131 if (xperdom .or. yperdom .or. spheredom)
then
132 call
preicall(val,aux,mitot,mjtot,nvar,naux,ilo-nghost,ihi+nghost, &
133 jlo-nghost,jhi+nghost,level,1,1,fliparray)
135 call
icall(val,aux,mitot,mjtot,nvar,naux,ilo-nghost,ihi+nghost, &
136 jlo-nghost,jhi+nghost,level,1,1)
142 call system_clock(clock_start,clock_rate)
143 call cpu_time(cpu_start)
144 call
setaux(nghost,nx,ny,xleft,ybot,dx,dy,naux,aux)
145 call system_clock(clock_finish,clock_rate)
146 call cpu_time(cpu_finish)
147 timesetaux=timesetaux+clock_finish-clock_start
148 timesetauxcpu=timesetauxcpu+cpu_finish-cpu_start
155 val(1,:,:) = needs_to_be_set
156 if (xperdom .or. yperdom .or. spheredom)
then
157 call
preintcopy(val,mitot,mjtot,nvar,ilo-nghost,ihi+nghost, &
158 jlo-nghost,jhi+nghost,level,fliparray)
160 call
intcopy(val,mitot,mjtot,nvar,ilo-nghost,ihi+nghost, &
161 jlo-nghost,jhi+nghost,level,1,1)
173 s1p = valc(ivar,i+1,j) - valc(ivar,i,j)
174 s1m = valc(ivar,i,j) - valc(ivar,i-1,j)
175 slopex = min(abs(s1p), abs(s1m)) &
176 * sign(1.d0,valc(ivar,i+1,j) - valc(ivar,i-1,j))
178 if ( s1m*s1p <= 0.d0) slopex = 0.d0
180 s1p = valc(ivar,i,j+1) - valc(ivar,i,j)
181 s1m = valc(ivar,i,j) - valc(ivar,i,j-1)
182 slopey = min(abs(s1p), abs(s1m)) &
183 * sign(1.0d0, valc(ivar,i,j+1) - valc(ivar,i,j-1))
184 if ( s1m*s1p <= 0.d0) slopey = 0.d0
187 do jco = 1,refinement_ratio_y
188 yoff = (
real(jco,kind=8) - 0.5d0) / refinement_ratio_y - 0.5d0
189 jfine = (j-2) * refinement_ratio_y + nghost + jco
191 do ico = 1,refinement_ratio_x
192 xoff = (
real(ico,kind=8) - 0.5d0) / refinement_ratio_x - 0.5d0
193 ifine = (i-2) * refinement_ratio_x + nghost + ico
195 if (
setflags(ifine,jfine) .eq. needs_to_be_set)
then
196 val(ivar,ifine,jfine) = valc(ivar,i,j) + xoff*slopex + yoff*slopey
208 if (mcapa .ne. 0)
then
209 call
fixcapaq(val,aux,mitot,mjtot,valc,auxc,mic,mjc,nvar,naux,level-1,
setflags)
240 real(kind=8) :: aux(naux,mitot,mjtot)
241 integer :: naux,mitot,mjtot,i,j,iaux
245 write(*,444) i,j,(aux(iaux,i,j),iaux=1,naux)
246 444
format(2i4,5e12.5)
subroutine bc2amr(val, aux, nrow, ncol, meqn, naux,
Take a grid patch with mesh widths hx,hy, of dimensions nrow by ncol, and set the values of any piece...
subroutine filval(val, mitot, mjtot, dx, dy, level, time, mic, mjc, xleft, xright, ybot, ytop, nvar, mptr, ilo, ihi, jlo, jhi, aux, naux)
subroutine setflags(iflags, isize, jsize, rctold, idim3, mitot, mjtot, mptr)
subroutine icall(val, aux, nrow, ncol, nvar, naux, ilo, ihi, jlo, jhi, level, iputst, jputst)
subroutine intcopy(val, mitot, mjtot, nvar, ilo, ihi, jlo, jhi, level, iputst, jputst)
subroutine fixcapaq(val, aux, mitot, mjtot, valc, auxc, mic, mjc, nvar, naux, levc, setflags)
subroutine preintcopy(val, mitot, mjtot, nvar, ilo, ihi, jlo, jhi, level, fliparray)
subroutine dumpaux(aux, naux, mitot, mjtot)
subroutine preicall(val, aux, nrow, ncol, nvar, naux, ilo, ihi, jlo, jhi, level, fliparray)
subroutine setaux(mbc, mx, my, xlower, ylower, dx, dy, maux, aux)