2D AMRCLAW
amr2.f90
Go to the documentation of this file.
1 !
2 ! Use adaptive mesh refinement to solve the hyperbolic 2-d equation:
3 !
4 ! u + f(u) + g(u) = 0
5 ! t x y
6 !
7 ! or the more general non-conservation law form:
8 ! u + A u + B u = 0
9 ! t x y
10 !
11 ! using the wave propagation method as in CLAWPACK in combination
12 ! with the locally uniform embedded grids of AMR.
13 !
14 ! Estimate error with Richardson extrap. (in errest.f)
15 ! + gradient checking (in errsp.f). Initial conditions set
16 ! in (qinit.f), b.c.'s in (physbd.f).
17 !
18 ! Specify rectangular domain from
19 ! (xlower,ylower) to (xupper,yupper).
20 !
21 !
22 ! =========================================================================
23 !
24 ! This software is made available for research and instructional use only.
25 ! You may copy and use this software without charge for these non-commercial
26 ! purposes, provided that the copyright notice and associated text is
27 ! reproduced on all copies. For all other uses (including distribution of
28 ! modified versions), please contact the author at the address given below.
29 !
30 ! *** This software is made available "as is" without any assurance that it
31 ! *** will work for your purposes. The software may in fact have defects, so
32 ! *** use the software at your own risk.
33 !
34 ! --------------------------------------
35 ! AMRCLAW Version 5.0, 2012
36 ! Homepage: http://www.clawpack.org
37 ! --------------------------------------
38 !
39 ! Authors:
40 !
41 ! Marsha J. Berger
42 ! Courant Institute of Mathematical Sciences
43 ! New York University
44 ! 251 Mercer St.
45 ! New York, NY 10012
46 ! berger@cims.nyu.edu
47 !
48 ! Randall J. LeVeque
49 ! Applied Mathematics
50 ! Box 352420
51 ! University of Washington,
52 ! Seattle, WA 98195-2420
53 ! rjl@uw.edu
54 !
55 ! =========================================================================
56 program amr2
57 
60  use amr_module, only: xupper, yupper, xlower, ylower
62  use amr_module, only: cfl, cflv1, cflmax, evol
63 
65  use amr_module, only: rstfile, check_a
66 
67  use amr_module, only: max1d, maxvar, maxlv
68 
72 
73  use amr_module, only: nghost, mthbc
74  use amr_module, only: xperdom, yperdom, spheredom
75 
80 
87  use amr_module, only: kcheck, iorder, lendim, lenmax
88 
90  use amr_module, only: rprint, sprint, tprint, uprint
91 
92  use amr_module, only: t0, tstart_thisrun
93 
94  use regions_module, only: set_regions
96 
97  implicit none
98 
99  ! Local variables
100  integer :: i, iaux, mw, level
101  integer :: ndim, nvar, naux, mcapa1, mindim
102  integer :: nstart, nsteps, nv1, nx, ny, lentotsave, num_gauge_SAVE
103  integer :: omp_get_max_threads, maxthreads
104  real(kind=8) :: time, ratmet, cut, dtinit, dt_max
105  logical :: vtime, rest, output_t0
106 
107  ! Timing variables
108  integer :: ttotal
109  real(kind=8) ::ttotalcpu, cpu_start,cpu_finish
110  integer :: clock_start, clock_finish, clock_rate
111 
112 
113  ! Common block variables
114  real(kind=8) :: dxmin, dymin
115 
116  common /comfine/ dxmin,dymin
117 
118  character(len=364) :: format_string
119  character(len=*), parameter :: clawfile = 'claw.data'
120  character(len=*), parameter :: amrfile = 'amr.data'
121  character(len=*), parameter :: outfile = 'fort.amr'
122  character(len=*), parameter :: dbugfile = 'fort.debug'
123  character(len=*), parameter :: matfile = 'fort.nplot'
124  character(len=*), parameter :: parmfile = 'fort.parameters'
125 
126  ! Open parameter and debug files
127  open(dbugunit,file=dbugfile,status='unknown',form='formatted')
128  open(parmunit,file=parmfile,status='unknown',form='formatted')
129 
130  maxthreads = 1 !! default, if no openmp
131 
132  ! Open AMRClaw primary parameter file
133  call opendatafile(inunit,clawfile)
134 
135  ! Number of space dimensions, not really a parameter but we read it in and
136  ! check to make sure everyone is on the same page.
137  read(inunit,"(i1)") ndim
138  if (ndim /= 2) then
139  print *,'Error *** ndim = 2 is required, ndim = ',ndim
140  print *,'*** Are you sure input has been converted'
141  print *,'*** to Clawpack 5.x form?'
142  stop
143  endif
144 
145  ! Domain variables
146  read(inunit,*) xlower, ylower
147  read(inunit,*) xupper, yupper
148  read(inunit,*) nx, ny
149  read(inunit,*) nvar ! meqn
150  read(inunit,*) mwaves
151  read(inunit,*) naux
152  read(inunit,*) t0
153 
154  ! ==========================================================================
155  ! Output Options
156  ! Output style
157  read(inunit,*) output_style
158  if (output_style == 1) then
159  read(inunit,*) nout
160  read(inunit,*) tfinal
161  read(inunit,*) output_t0
162 
163  iout = 0
164  else if (output_style == 2) then
165  read(inunit,*) nout
166  allocate(tout(nout))
167  read(inunit,*) (tout(i), i=1,nout)
168  output_t0 = (tout(1) == t0)
169  ! Move output times down one index
170  if (output_t0) then
171  nout = nout - 1
172  do i=1,nout
173  tout(i) = tout(i+1)
174  enddo
175  endif
176  iout = 0
177  tfinal = tout(nout)
178  else if (output_style == 3) then
179  read(inunit,*) iout
180  read(inunit,*) nstop
181  read(inunit,*) output_t0
182  nout = 0
183  tfinal = rinfinity
184  else
185  stop "Error *** Invalid output style."
186  endif
187 
188  ! Error checking
189  if ((output_style == 1) .and. (nout > 0)) then
190  allocate(tout(nout))
191  do i=1,nout
192  tout(i) = t0 + i * (tfinal - t0) / real(nout,kind=8)
193  enddo
194  endif
195 
196  ! What and how to output
197  read(inunit,*) output_format
198  allocate(output_q_components(nvar))
199  read(inunit,*) (output_q_components(i),i=1,nvar)
200  if (naux > 0) then
201  allocate(output_aux_components(naux))
202  read(inunit,*) (output_aux_components(i),i=1,naux)
203  read(inunit,*) output_aux_onlyonce
204  endif
205  ! ==========================================================================
206 
207  ! ==========================================================================
208  ! Algorithm parameters
209 
210  read(inunit,*) possk(1) ! dt_initial
211  read(inunit,*) dt_max ! largest allowable dt
212  read(inunit,*) cflv1 ! cfl_max
213  read(inunit,*) cfl ! clf_desired
214  read(inunit,*) nv1 ! steps_max
215 
216  if (output_style /= 3) then
217  !nstop = nv1
218  nstop = iinfinity ! basically disabled this test
219  endif
220 
221  read(inunit,*) vtime ! dt_variable
222  if (vtime) then
223  method(1) = 2
224  else
225  method(1) = 1
226  endif
227 
228  read(inunit,*) method(2) ! order
229  iorder = method(2)
230  read(inunit,*) method(3) ! order_trans
231 
232  read(inunit,*) dimensional_split
233  if (dimensional_split > 1) then
234  print *, '*** ERROR *** dimensional_split = ', dimensional_split
235  print *, ' Strang splitting not supported in amrclaw'
236  stop
237  endif
238 
239  read(inunit,*) method(4) ! verbosity
240  read(inunit,*) method(5) ! src_split
241  read(inunit,*) mcapa1
242 
243  read(inunit,*) use_fwaves
244  allocate(mthlim(mwaves))
245  read(inunit,*) (mthlim(mw), mw=1,mwaves)
246 
247  ! Boundary conditions
248  read(inunit,*) nghost
249  read(inunit,*) mthbc(1),mthbc(3)
250  read(inunit,*) mthbc(2),mthbc(4)
251 
252  ! 1 = left, 2 = right 3 = bottom 4 = top boundary
253  xperdom = (mthbc(1) == 2 .and. mthbc(2) == 2)
254  yperdom = (mthbc(3) == 2 .and. mthbc(4) == 2)
255  spheredom = (mthbc(3) == 5 .and. mthbc(4) == 5)
256 
257  if ((mthbc(1).eq.2 .and. mthbc(2).ne.2) .or. &
258  (mthbc(2).eq.2 .and. mthbc(1).ne.2)) then
259 
260  print *, '*** ERROR *** periodic boundary conditions: '
261  print *, ' mthbc(1) and mthbc(2) must BOTH be set to 2'
262  stop
263  endif
264 
265  if ((mthbc(3).eq.2 .and. mthbc(4).ne.2) .or. &
266  (mthbc(4).eq.2 .and. mthbc(3).ne.2)) then
267 
268  print *, '*** ERROR *** periodic boundary conditions: '
269  print *, ' mthbc(3) and mthbc(4) must BOTH be set to 2'
270  stop
271  endif
272 
273  if ((mthbc(3).eq.5 .and. mthbc(4).ne.5) .or. &
274  (mthbc(4).eq.5 .and. mthbc(3).ne.5)) then
275 
276  print *, '*** ERROR *** sphere bcs at top and bottom: '
277  print *, ' mthbc(3) and mthbc(4) must BOTH be set to 5'
278  stop
279  endif
280 
281  if (spheredom .and. .not. xperdom) then
282 
283  print *,'*** ERROR *** sphere bcs at top and bottom: '
284  print *,'must go with periodic bcs at left and right '
285  stop
286  endif
287 
288  ! ==========================================================================
289  ! Restart and Checkpointing
290 
291  read(inunit,*) rest
292  read(inunit,*) rstfile
293 
294  read(inunit,*) checkpt_style
295  if (checkpt_style == 0) then
296  ! Never checkpoint:
297  checkpt_interval = iinfinity
298 
299  else if (abs(checkpt_style) == 2) then
300  read(inunit,*) nchkpt
301  allocate(tchk(nchkpt))
302  read(inunit,*) (tchk(i), i=1,nchkpt)
303 
304  else if (abs(checkpt_style) == 3) then
305  ! Checkpoint every checkpt_interval steps on coarse grid
306  read(inunit,*) checkpt_interval
307  endif
308 
309  close(inunit)
310 
311  ! ==========================================================================
312  ! Refinement Control
313  call opendatafile(inunit, amrfile)
314 
315  read(inunit,*) mxnest
316  if (mxnest <= 0) then
317  stop 'Error *** mxnest (amrlevels_max) <= 0 not allowed'
318  endif
319 
320  if (mxnest > maxlv) then
321  stop 'Error *** mxnest > max. allowable levels (maxlv) in common'
322  endif
323 
324  ! Anisotropic refinement always allowed in 5.x:
325  read(inunit,*) (intratx(i),i=1,max(1,mxnest-1))
326  read(inunit,*) (intraty(i),i=1,max(1,mxnest-1))
327  read(inunit,*) (kratio(i), i=1,max(1,mxnest-1))
328  read(inunit,*)
329 
330  do i=1,mxnest-1
331  if ((intratx(i) > max1d) .or. (intraty(i) > max1d)) then
332  print *, ""
333  format_string = "(' *** Error: Refinement ratios must be no " // &
334  "larger than max1d = ',i5,/,' (set max1d" // &
335  " in amr_module.f90)')"
336  print format_string, max1d
337  stop
338  endif
339  enddo
340 
341  if (naux > 0) then
342  allocate(auxtype(naux))
343  read(inunit,*) (auxtype(iaux), iaux=1,naux)
344  endif
345  read(inunit,*)
346 
347  read(inunit,*) flag_richardson
348  read(inunit,*) tol ! for richardson
349  read(inunit,*) flag_gradient
350  read(inunit,*) tolsp ! for gradient
351  read(inunit,*) kcheck
352  read(inunit,*) ibuff
353  read(inunit,*) cut
354  read(inunit,*) verbosity_regrid
355 
356  ! read verbose/debugging flags
357  read(inunit,*) dprint
358  read(inunit,*) eprint
359  read(inunit,*) edebug
360  read(inunit,*) gprint
361  read(inunit,*) nprint
362  read(inunit,*) pprint
363  read(inunit,*) rprint
364  read(inunit,*) sprint
365  read(inunit,*) tprint
366  read(inunit,*) uprint
367 
368  close(inunit)
369  ! Finished with reading in parameters
370  ! ==========================================================================
371 
372  ! Look for capacity function via auxtypes:
373  mcapa = 0
374  do iaux = 1, naux
375  if (auxtype(iaux) == "capacity") then
376  if (mcapa /= 0) then
377  print *, " only 1 capacity allowed"
378  stop
379  else
380  mcapa = iaux
381  endif
382  endif
383 
384  ! Change to Version 4.1 terminology:
385  if (auxtype(iaux) == "leftface") auxtype(iaux) = "xleft"
386  if (auxtype(iaux) == "bottomface") auxtype(iaux) = "yleft"
387  if (.not. (auxtype(iaux) .eq."xleft" .or. &
388  auxtype(iaux) .eq. "yleft".or. &
389  auxtype(iaux) .eq. "capacity".or. &
390  auxtype(iaux) .eq. "center")) then
391  print *," unknown type for auxiliary variables"
392  print *," use xleft/yleft/center/capacity"
393  stop
394  endif
395  enddo
396 
397  ! Error checking of input data
398  if (mcapa /= mcapa1) then
399  stop 'Error *** mcapa does not agree with auxtype'
400  endif
401  if (nvar > maxvar) then
402  stop 'Error *** nvar > maxvar in common'
403  endif
404  if (2*nghost > min(nx,ny) .and. ny /= 1) then
405  mindim = 2 * nghost
406  print *, 'Error *** need finer domain >', mindim, ' cells'
407  stop
408  endif
409  if (mcapa > naux) then
410  stop 'Error *** mcapa > naux in input file'
411  endif
412 
413  if (.not. vtime .and. nout /= 0) then
414  print *, ' cannot specify output times with fixed dt'
415  stop
416  endif
417 
418 
419  ! Write out parameters
420  write(parmunit,*) ' '
421  write(parmunit,*) 'Running amrclaw with parameter values:'
422  write(parmunit,*) ' '
423 
424 
425  print *, ' '
426  print *, 'Running amrclaw ... '
427  print *, ' '
428 
429  hxposs(1) = (xupper - xlower) / nx
430  hyposs(1) = (yupper - ylower) / ny
431 
432  ! initialize frame number for output.
433  ! Note: might be reset in restrt if this is a restart
434  if (output_t0) then
435  matlabu = 0
436  else
437  matlabu = 1
438  endif
439 
440  ! Boolean check_a tells which checkpoint file to use next if alternating
441  ! between only two files via check_twofiles.f, unused otherwise.
442  ! May be reset in call to restrt, otherwise default to using aaaaa file.
443  check_a = .true.
444 
445  if (rest) then
446 
447  open(outunit, file=outfile, status='unknown', position='append', &
448  form='formatted')
449 
450  call restrt(nsteps,time,nvar,naux)
451  nstart = nsteps
452  tstart_thisrun = time
453  print *, ' '
454  print *, 'Restarting from previous run'
455  print *, ' at time = ',time
456  print *, ' '
457  ! Call user routine to set up problem parameters:
458  call setprob()
459 
460  ! Non-user data files
461  call set_regions()
462  call set_gauges(rest, nvar, naux)
463 
464  else
465 
466  open(outunit, file=outfile, status='unknown', form='formatted')
467 
469 
470  ! Call user routine to set up problem parameters:
471  call setprob()
472 
473  ! Non-user data files
474  call set_regions()
475  call set_gauges(rest, nvar, naux)
476 
477  cflmax = 0.d0 ! otherwise use previously heckpointed val
478 
479  lentot = 0
480  lenmax = 0
481  lendim = 0
482  rvol = 0.0d0
483  do i = 1, mxnest
484  rvoll(i) = 0.0d0
485  enddo
486  evol = 0.0d0
487  call stst1()
488 
489 
490  ! changed 4/24/09: store dxmin,dymin for setaux before
491  ! grids are made, in order to average up from finest grid.
492  dxmin = hxposs(mxnest)
493  dymin = hyposs(mxnest)
494 
495  call domain(nvar,vtime,nx,ny,naux,t0)
496 
497  ! Hold off on gauges until grids are set.
498  ! The fake call to advance at the very first timestep
499  ! looks at the gauge array but it is not yet built
500  num_gauge_save = num_gauges
501  num_gauges = 0
502  call setgrd(nvar,cut,naux,dtinit,t0)
503  num_gauges = num_gauge_save
504 
505 ! commented out to match 4-x version
506 !!$ if (possk(1) .gt. dtinit*cflv1/cfl .and. vtime) then
507 !!$ ! initial time step was too large. reset to dt from setgrd
508 !!$ print *, "*** Initial time step reset for desired cfl"
509 !!$ possk(1) = dtinit
510 !!$ do i = 2, mxnest-1
511 !!$ possk(i) = possk(i-1)*kratio(i-1)
512 !!$ end do
513 !!$ endif
514 
515  time = t0
516  nstart = 0
517  endif
518 
519  write(parmunit,*) ' '
520  write(parmunit,*) '--------------------------------------------'
521  write(parmunit,*) ' '
522  write(parmunit,*) ' rest = ', rest, ' (restart?)'
523  write(parmunit,*) ' start time = ',time
524  write(parmunit,*) ' '
525 
526 !$ maxthreads = omp_get_max_threads()
527  write(outunit,*)" max threads set to ",maxthreads
528  print *," max threads set to ",maxthreads
529 
530  !
531  ! print out program parameters for this run
532  !
533  format_string = "(/' amrclaw parameters:',//," // &
534  "' error tol ',e12.5,/," // &
535  "' spatial error tol ',e12.5,/," // &
536  "' order of integrator ',i9,/," // &
537  "' error checking interval ',i9,/," // &
538  "' buffer zone size ',i9,/," // &
539  "' nghost ',i9,/," // &
540  "' volume ratio cutoff ',e12.5,/," // &
541  "' max. refinement level ',i9,/," // &
542  "' user sub. calling times ',i9,/," // &
543  "' cfl # (if var. delt) ',e12.5,/)"
544  write(outunit,format_string) tol,tolsp,iorder,kcheck,ibuff,nghost,cut, &
545  mxnest,checkpt_interval,cfl
546  format_string = "(' xupper(upper corner) ',e12.5,/," // &
547  "' yupper(upper corner) ',e12.5,/," // &
548  "' xlower(lower corner) ',e12.5,/," // &
549  "' ylower(lower corner) ',e12.5,/," // &
550  "' nx = no. cells in x dir.',i9,/," // &
551  "' ny = no. cells in y dir.',i9,/," // &
552  "' refinement ratios ',6i5,/,/)"
553  write(outunit,format_string) xupper,yupper,xlower,ylower,nx,ny
554  write(outunit,"(' refinement ratios: ',6i5,/)" ) &
555  (intratx(i),i=1,mxnest)
556  write(outunit,"(' refinement ratios: ',6i5,/)" ) &
557  (intraty(i),i=1,mxnest)
558  write(outunit,"(' no. auxiliary vars. ',i9)") naux
559  write(outunit,"(' var ',i5,' of type ', a10)") &
560  (iaux,auxtype(iaux),iaux=1,naux)
561  if (mcapa > 0) write(outunit,"(' capacity fn. is aux. var',i9)") mcapa
562 
563  print *, ' '
564  print *, 'Done reading data, starting computation ... '
565  print *, ' '
566 
567 
568  call outtre (mstart,printout,nvar,naux)
569  write(outunit,*) " original total mass ..."
570  call conck(1,nvar,naux,time,rest)
571  if (output_t0) then
572  call valout(1,lfine,time,nvar,naux)
573  endif
574  close(parmunit)
575 
576  ! Timing: moved inside tick so can finish and be checkpointed
577  call cpu_time(cpu_start)
578  call system_clock(clock_start,clock_rate)
579 
580  ! --------------------------------------------------------
581  ! Tick is the main routine which drives the computation:
582  ! --------------------------------------------------------
583 
584  call tick(nvar,cut,nstart,vtime,time,naux,t0,rest,dt_max)
585  ! --------------------------------------------------------
586 
587  call cpu_time(cpu_finish)
588 
589  !output timing data
590  write(*,*)
591  write(outunit,*)
592  format_string="('============================== Timing Data ==============================')"
593  write(outunit,format_string)
594  write(*,format_string)
595 
596  write(*,*)
597  write(outunit,*)
598 
599  !Integration time
600  format_string="('Integration Time (stepgrid + BC + overhead)')"
601  write(outunit,format_string)
602  write(*,format_string)
603 
604  !Advanc time
605  format_string="('Level Wall Time (seconds) CPU Time (seconds) Total Cell Updates')"
606  write(outunit,format_string)
607  write(*,format_string)
608  ttotalcpu=0.d0
609  ttotal=0
610 
611  call system_clock(clock_finish,clock_rate) ! just to get clock_rate
612  write(*,*) "clock_rate ",clock_rate
613 
614  do level=1,mxnest
615  format_string="(i3,' ',1f15.3,' ',1f15.3,' ', e17.3)"
616  write(outunit,format_string) level, &
617  real(tvoll(level),kind=8) / real(clock_rate,kind=8), tvollCPU(level), rvoll(level)
618  write(*,format_string) level, &
619  real(tvoll(level),kind=8) / real(clock_rate,kind=8), tvollCPU(level), rvoll(level)
620  ttotalcpu=ttotalcpu+tvollcpu(level)
621  ttotal=ttotal+tvoll(level)
622  end do
623 
624  format_string="('total ',1f15.3,' ',1f15.3,' ', e17.3)"
625  write(outunit,format_string) &
626  real(ttotal,kind=8) / real(clock_rate,kind=8), ttotalCPU, rvol
627  write(*,format_string) &
628  real(ttotal,kind=8) / real(clock_rate,kind=8), ttotalCPU, rvol
629 
630  write(*,*)
631  write(outunit,*)
632 
633 
634  format_string="('All levels:')"
635  write(*,format_string)
636  write(outunit,format_string)
637 
638 
639 
640  !stepgrid
641  format_string="('stepgrid ',1f15.3,' ',1f15.3,' ',e17.3)"
642  write(outunit,format_string) &
643  real(timeStepgrid,kind=8) / real(clock_rate,kind=8), timeStepgridCPU
644  write(*,format_string) &
645  real(timeStepgrid,kind=8) / real(clock_rate,kind=8), timeStepgridCPU
646 
647  !bound
648  format_string="('BC/ghost cells',1f15.3,' ',1f15.3)"
649  write(outunit,format_string) &
650  real(timeBound,kind=8) / real(clock_rate,kind=8), timeBoundCPU
651  write(*,format_string) &
652  real(timeBound,kind=8) / real(clock_rate,kind=8), timeBoundCPU
653 
654  !regridding time
655  format_string="('Regridding ',1f15.3,' ',1f15.3,' ')"
656  write(outunit,format_string) &
657  real(timeRegridding,kind=8) / real(clock_rate,kind=8), timeRegriddingCPU
658  write(*,format_string) &
659  real(timeRegridding,kind=8) / real(clock_rate,kind=8), timeRegriddingCPU
660 
661  !output time
662  format_string="('Output (valout)',1f14.3,' ',1f15.3,' ')"
663  write(outunit,format_string) &
664  real(timeValout,kind=8) / real(clock_rate,kind=8), timeValoutCPU
665  write(*,format_string) &
666  real(timeValout,kind=8) / real(clock_rate,kind=8), timeValoutCPU
667 
668  write(*,*)
669  write(outunit,*)
670 
671  !Total Time
672  format_string="('Total time: ',1f15.3,' ',1f15.3,' ')"
673 
674 ! write(*,format_string) &
675 ! real(clock_finish - clock_start,kind=8) / real(clock_rate,kind=8), &
676 ! cpu_finish-cpu_start
677  write(*,format_string) real(timetick,kind=8)/real(clock_rate,kind=8), &
678  timetickcpu
679  write(outunit,format_string) real(timetick,kind=8)/real(clock_rate,kind=8), &
680  timetickcpu
681 
682  format_string="('Using',i3,' thread(s)')"
683  write(outunit,format_string) maxthreads
684  write(*,format_string) maxthreads
685 
686 
687  write(*,*)
688  write(outunit,*)
689 
690 
691  write(*,"('Note: The CPU times are summed over all threads.')")
692  write(outunit,"('Note: The CPU times are summed over all threads.')")
693  write(*,"(' Total time includes more than the subroutines listed above')")
694  write(outunit,"(' Total time includes more than the subroutines listed above')")
695  if (rest) then
696  write(*,"(' Times for restart runs are cumulative')")
697  write(outunit,"(' Times for restart runs are cumulative')")
698  endif
699 
700 
701  !end of timing data
702  write(*,*)
703  write(outunit,*)
704  format_string="('=========================================================================')"
705  write(outunit,format_string)
706  write(*,format_string)
707  write(*,*)
708  write(outunit,*)
709 
710  ! Done with computation, cleanup:
711  lentotsave = lentot
712  call cleanup(nvar,naux)
713  if (lentot /= 0) then
714  write(outunit,*) lentot," words not accounted for in memory cleanup"
715  print *, lentot," words not accounted for in memory cleanup"
716  endif
717 
718  !
719  ! report on statistics
720  !
721  open(matunit,file=matfile,status='unknown',form='formatted')
722  write(matunit,*) matlabu-1
723  write(matunit,*) mxnest
724  close(matunit)
725 
726  write(outunit,*)
727  write(outunit,*)
728  do i = 1, mxnest
729  if (iregridcount(i) > 0) then
730  write(outunit,801) i,avenumgrids(i)/iregridcount(i),iregridcount(i)
731  801 format("for level ",i3, " average num. grids = ",f10.2," over ",i10, &
732  " regridding steps")
733  write(outunit,802) i,numgrids(i)
734  802 format("for level ",i3," current num. grids = ",i7)
735  endif
736  end do
737 
738  write(outunit,*)
739  write(outunit,*)
740  write(outunit,"('current space usage = ',i12)") lentotsave
741  write(outunit,"('maximum space usage = ',i12)") lenmax
742  write(outunit,"('need space dimension = ',i12,/)") lendim
743 
744  write(outunit,"('number of cells advanced for time integration = ',f20.6)")&
745  rvol
746  do level = 1,mxnest
747  write(outunit,"(3x,'# cells advanced on level ',i4,' = ',f20.2)") &
748  level, rvoll(level)
749  enddo
750 
751  write(outunit,"('number of cells advanced for error estimation = ',f20.6,/)") &
752  evol
753  if (evol + rvol > 0.d0) then
754  ratmet = rvol / (evol + rvol) * 100.0d0
755  else
756  ratmet = 0.0d0
757  endif
758  write(outunit,"(' percentage of cells advanced in time = ', f10.2)") ratmet
759  write(outunit,"(' maximum Courant number seen = ', f10.2)") cflmax
760 
761  write(outunit,"(//,' ------ end of AMRCLAW integration -------- ')")
762 
763  ! Close output and debug files.
764  close(outunit)
765  close(dbugunit)
766 
767 end program amr2
integer timetick
Definition: amr_module.f90:242
integer, parameter dbugunit
Definition: amr_module.f90:293
integer, dimension(7) method
Definition: amr_module.f90:253
integer, parameter maxvar
Definition: amr_module.f90:183
integer, dimension(maxlv) kratio
Definition: amr_module.f90:198
real(kind=8) t0
Definition: amr_module.f90:272
real(kind=8), parameter rinfinity
Definition: amr_module.f90:169
logical output_aux_onlyonce
Definition: amr_module.f90:277
integer lendim
Definition: amr_module.f90:247
real(kind=8) tfinal
Definition: amr_module.f90:272
integer, parameter maxlv
Definition: amr_module.f90:174
subroutine cleanup(nvar, naux)
Definition: cleanup.f:5
subroutine stst1
Definition: stst1.f:5
real(kind=8), dimension(:), allocatable tout
Definition: amr_module.f90:271
logical sprint
Definition: amr_module.f90:297
real(kind=8) evol
Definition: amr_module.f90:237
integer timebound
Definition: amr_module.f90:241
real(kind=8) cfl
Definition: amr_module.f90:255
logical rprint
Definition: amr_module.f90:297
integer lenmax
Definition: amr_module.f90:247
subroutine restrt(nsteps, time, nvar, naux)
Definition: restrt.f:6
integer, dimension(:), allocatable mthlim
Definition: amr_module.f90:254
integer, parameter max1d
Definition: amr_module.f90:181
real(kind=8), dimension(maxlv) hyposs
Definition: amr_module.f90:193
real(kind=8) cflmax
Definition: amr_module.f90:255
real(kind=8), dimension(maxlv) hxposs
Definition: amr_module.f90:193
subroutine conck(level, nvar, naux, time, rest)
Conservation check for specified level.
Definition: conck.f:7
integer, dimension(:), allocatable output_q_components
Definition: amr_module.f90:275
program amr2
Definition: amr2.f90:56
real(kind=8) tstart_thisrun
Definition: amr_module.f90:273
integer timeflagger
Definition: amr_module.f90:242
integer checkpt_interval
Definition: amr_module.f90:280
logical use_fwaves
Definition: amr_module.f90:257
subroutine valout(lst, lend, time, nvar, naux)
Definition: valout.f:5
logical edebug
Definition: amr_module.f90:297
subroutine set_gauges(restart, num_eqn, num_aux, fname)
real(kind=8) cflv1
Definition: amr_module.f90:255
real(kind=8) xupper
Definition: amr_module.f90:231
logical gprint
Definition: amr_module.f90:297
character(len=200) rstfile
Definition: amr_module.f90:311
integer, dimension(maxlv) numgrids
Definition: amr_module.f90:198
real(kind=8) xlower
Definition: amr_module.f90:231
integer, dimension(maxlv) iregridcount
Definition: amr_module.f90:238
real(kind=8) timevaloutcpu
Definition: amr_module.f90:245
integer lentot
Definition: amr_module.f90:247
logical flag_richardson
Definition: amr_module.f90:258
subroutine set_regions(fname)
real(kind=8) tol
Definition: amr_module.f90:197
logical check_a
Definition: amr_module.f90:312
real(kind=8) tolsp
Definition: amr_module.f90:197
integer timeupdating
Definition: amr_module.f90:239
integer iout
Definition: amr_module.f90:270
logical eprint
Definition: amr_module.f90:297
real(kind=8), dimension(maxlv) avenumgrids
Definition: amr_module.f90:237
logical yperdom
Definition: amr_module.f90:230
integer matlabu
Definition: amr_module.f90:283
real(kind=8) ylower
Definition: amr_module.f90:231
real(kind=8) yupper
Definition: amr_module.f90:231
integer iorder
Definition: amr_module.f90:198
logical spheredom
Definition: amr_module.f90:230
real(kind=8) rvol
Definition: amr_module.f90:237
real(kind=8) timetickcpu
Definition: amr_module.f90:243
integer dimensional_split
Definition: amr_module.f90:253
integer, parameter iinfinity
Definition: amr_module.f90:170
integer, parameter parmunit
Definition: amr_module.f90:287
integer ibuff
Definition: amr_module.f90:198
logical printout
Definition: amr_module.f90:264
real(kind=8) timeboundcpu
Definition: amr_module.f90:244
integer mcapa
Definition: amr_module.f90:253
real(kind=8), dimension(maxlv) tvollcpu
Definition: amr_module.f90:243
integer, dimension(maxlv) intraty
Definition: amr_module.f90:198
integer timebufnst
Definition: amr_module.f90:242
logical flag_gradient
Definition: amr_module.f90:258
integer output_format
Definition: amr_module.f90:274
real(kind=8), dimension(:), allocatable tchk
Definition: amr_module.f90:281
logical nprint
Definition: amr_module.f90:297
real(kind=8) timeregriddingcpu
Definition: amr_module.f90:244
real(kind=8), dimension(maxlv) rvoll
Definition: amr_module.f90:237
subroutine opendatafile(iunit, fname)
Definition: opendatafile.f:3
integer nstop
Definition: amr_module.f90:270
integer nchkpt
Definition: amr_module.f90:280
integer, parameter outunit
Definition: amr_module.f90:290
real(kind=8), dimension(maxlv) possk
Definition: amr_module.f90:193
integer num_gauges
logical tprint
Definition: amr_module.f90:297
integer checkpt_style
Definition: amr_module.f90:280
integer, parameter inunit
Definition: amr_module.f90:289
integer timestepgrid
Definition: amr_module.f90:241
logical pprint
Definition: amr_module.f90:297
logical dprint
Definition: amr_module.f90:297
logical xperdom
Definition: amr_module.f90:230
real(kind=8) timestepgridcpu
Definition: amr_module.f90:244
integer, dimension(maxlv) intratx
Definition: amr_module.f90:198
logical uprint
Definition: amr_module.f90:297
integer, parameter matunit
Definition: amr_module.f90:294
subroutine outtre(mlev, outgrd, nvar, naux)
Output a subtree of the grids.
Definition: outtre.f:11
subroutine tick(nvar, cut, nstart, vtime, time, naux, start_time, rest, dt_max)
Definition: tick.f:6
integer mxnest
Definition: amr_module.f90:198
integer, dimension(4) mthbc
Definition: amr_module.f90:232
character(len=10), dimension(:), allocatable auxtype
Definition: amr_module.f90:252
integer, dimension(:), allocatable output_aux_components
Definition: amr_module.f90:276
subroutine domain(nvar, vtime, nx, ny, naux, start_time)
Definition: domain.f:5
integer nghost
Definition: amr_module.f90:232
integer verbosity_regrid
Definition: amr_module.f90:259
The module contains the definition of a "node descriptor" as well as other global variables used duri...
Definition: amr_module.f90:21
integer timevalout
Definition: amr_module.f90:239
integer nout
Definition: amr_module.f90:270
integer mstart
Definition: amr_module.f90:198
subroutine setprob
Definition: setprob.f90:2
integer kcheck
Definition: amr_module.f90:198
subroutine setgrd(nvar, cut, naux, dtinit, start_time)
Definition: setgrd.f:5
integer output_style
Definition: amr_module.f90:270
integer lfine
Definition: amr_module.f90:198
integer mwaves
Definition: amr_module.f90:253
integer, dimension(maxlv) tvoll
Definition: amr_module.f90:238
integer timeregridding
Definition: amr_module.f90:239