58 use amr_module, only: dbugunit, parmunit, outunit, inunit, matunit
59 use amr_module, only: mxnest, rinfinity, iinfinity
60 use amr_module, only: xupper, yupper, xlower, ylower
61 use amr_module, only: hxposs, hyposs, intratx, intraty, kratio
64 use amr_module, only: checkpt_style, checkpt_interval, tchk, nchkpt
69 use amr_module, only: method, mthlim, use_fwaves, numgrids
70 use amr_module, only: nghost, mwaves, mcapa, auxtype, dimensional_split
71 use amr_module, only: tol, tolsp, flag_richardson, flag_gradient
74 use amr_module, only: xperdom, yperdom, spheredom
76 use amr_module, only: nstop, nout, iout, tfinal, tout, output_style
77 use amr_module, only: output_format, printout, verbosity_regrid
78 use amr_module, only: output_q_components, output_aux_components
79 use amr_module, only: output_aux_onlyonce, matlabu
81 use amr_module, only: lfine, lentot, iregridcount, avenumgrids
82 use amr_module, only: tvoll, tvollcpu, rvoll, rvol, mstart, possk, ibuff
83 use amr_module, only: timeregridding,timeupdating, timevalout
84 use amr_module, only: timebound,timestepgrid, timeflagger,timebufnst
85 use amr_module, only: timeboundcpu,timestepgridcpu,timeregriddingcpu
86 use amr_module, only: timevaloutcpu,timetick,timetickcpu
87 use amr_module, only: kcheck, iorder, lendim, lenmax
89 use amr_module, only: dprint, eprint, edebug, gprint, nprint, pprint
90 use amr_module, only: rprint, sprint, tprint, uprint
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
109 real(kind=8) ::ttotalcpu, cpu_start,cpu_finish
110 integer :: clock_start, clock_finish, clock_rate
114 real(kind=8) :: dxmin, dymin
116 common /comfine/ dxmin,dymin
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'
127 open(dbugunit,file=dbugfile,status=
'unknown',form=
'formatted')
128 open(parmunit,file=parmfile,status=
'unknown',form=
'formatted')
137 read(inunit,
"(i1)") ndim
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?'
146 read(inunit,*) xlower, ylower
147 read(inunit,*) xupper, yupper
148 read(inunit,*) nx, ny
150 read(inunit,*) mwaves
157 read(inunit,*) output_style
158 if (output_style == 1)
then
160 read(inunit,*) tfinal
161 read(inunit,*) output_t0
164 else if (output_style == 2)
then
167 read(inunit,*) (tout(i), i=1,nout)
168 output_t0 = (tout(1) == t0)
178 else if (output_style == 3)
then
181 read(inunit,*) output_t0
185 stop
"Error *** Invalid output style."
189 if ((output_style == 1) .and. (nout > 0))
then
192 tout(i) = t0 + i * (tfinal - t0) /
real(nout,kind=8)
197 read(inunit,*) output_format
198 allocate(output_q_components(nvar))
199 read(inunit,*) (output_q_components(i),i=1,nvar)
201 allocate(output_aux_components(naux))
202 read(inunit,*) (output_aux_components(i),i=1,naux)
203 read(inunit,*) output_aux_onlyonce
210 read(inunit,*) possk(1)
211 read(inunit,*) dt_max
216 if (output_style /= 3)
then
228 read(inunit,*) method(2)
230 read(inunit,*) method(3)
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'
239 read(inunit,*) method(4)
240 read(inunit,*) method(5)
241 read(inunit,*) mcapa1
243 read(inunit,*) use_fwaves
244 allocate(mthlim(mwaves))
245 read(inunit,*) (mthlim(mw), mw=1,mwaves)
248 read(inunit,*) nghost
249 read(inunit,*) mthbc(1),mthbc(3)
250 read(inunit,*) mthbc(2),mthbc(4)
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)
257 if ((mthbc(1).eq.2 .and. mthbc(2).ne.2) .or. &
258 (mthbc(2).eq.2 .and. mthbc(1).ne.2))
then
260 print *,
'*** ERROR *** periodic boundary conditions: '
261 print *,
' mthbc(1) and mthbc(2) must BOTH be set to 2'
265 if ((mthbc(3).eq.2 .and. mthbc(4).ne.2) .or. &
266 (mthbc(4).eq.2 .and. mthbc(3).ne.2))
then
268 print *,
'*** ERROR *** periodic boundary conditions: '
269 print *,
' mthbc(3) and mthbc(4) must BOTH be set to 2'
273 if ((mthbc(3).eq.5 .and. mthbc(4).ne.5) .or. &
274 (mthbc(4).eq.5 .and. mthbc(3).ne.5))
then
276 print *,
'*** ERROR *** sphere bcs at top and bottom: '
277 print *,
' mthbc(3) and mthbc(4) must BOTH be set to 5'
281 if (spheredom .and. .not. xperdom)
then
283 print *,
'*** ERROR *** sphere bcs at top and bottom: '
284 print *,
'must go with periodic bcs at left and right '
292 read(inunit,*) rstfile
294 read(inunit,*) checkpt_style
295 if (checkpt_style == 0)
then
297 checkpt_interval = iinfinity
299 else if (abs(checkpt_style) == 2)
then
300 read(inunit,*) nchkpt
301 allocate(tchk(nchkpt))
302 read(inunit,*) (tchk(i), i=1,nchkpt)
304 else if (abs(checkpt_style) == 3)
then
306 read(inunit,*) checkpt_interval
315 read(inunit,*) mxnest
316 if (mxnest <= 0)
then
317 stop
'Error *** mxnest (amrlevels_max) <= 0 not allowed'
320 if (mxnest > maxlv)
then
321 stop
'Error *** mxnest > max. allowable levels (maxlv) in common'
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))
331 if ((intratx(i) > max1d) .or. (intraty(i) > max1d))
then
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
342 allocate(auxtype(naux))
343 read(inunit,*) (auxtype(iaux), iaux=1,naux)
347 read(inunit,*) flag_richardson
349 read(inunit,*) flag_gradient
351 read(inunit,*) kcheck
354 read(inunit,*) verbosity_regrid
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
375 if (auxtype(iaux) ==
"capacity")
then
377 print *,
" only 1 capacity allowed"
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"
398 if (mcapa /= mcapa1)
then
399 stop
'Error *** mcapa does not agree with auxtype'
401 if (nvar > maxvar)
then
402 stop
'Error *** nvar > maxvar in common'
404 if (2*nghost > min(nx,ny) .and. ny /= 1)
then
406 print *,
'Error *** need finer domain >', mindim,
' cells'
409 if (mcapa > naux)
then
410 stop
'Error *** mcapa > naux in input file'
413 if (.not. vtime .and. nout /= 0)
then
414 print *,
' cannot specify output times with fixed dt'
420 write(parmunit,*)
' '
421 write(parmunit,*)
'Running amrclaw with parameter values:'
422 write(parmunit,*)
' '
426 print *,
'Running amrclaw ... '
429 hxposs(1) = (xupper - xlower) / nx
430 hyposs(1) = (yupper - ylower) / ny
447 open(outunit, file=outfile, status=
'unknown', position=
'append', &
450 call
restrt(nsteps,time,nvar,naux)
452 tstart_thisrun = time
454 print *,
'Restarting from previous run'
455 print *,
' at time = ',time
466 open(outunit, file=outfile, status=
'unknown', form=
'formatted')
492 dxmin = hxposs(mxnest)
493 dymin = hyposs(mxnest)
495 call
domain(nvar,vtime,nx,ny,naux,t0)
500 num_gauge_save = num_gauges
502 call
setgrd(nvar,cut,naux,dtinit,t0)
503 num_gauges = num_gauge_save
519 write(parmunit,*)
' '
520 write(parmunit,*)
'--------------------------------------------'
521 write(parmunit,*)
' '
522 write(parmunit,*)
' rest = ', rest,
' (restart?)'
523 write(parmunit,*)
' start time = ',time
524 write(parmunit,*)
' '
527 write(outunit,*)
" max threads set to ",maxthreads
528 print *,
" max threads set to ",maxthreads
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
564 print *,
'Done reading data, starting computation ... '
568 call
outtre(mstart,printout,nvar,naux)
569 write(outunit,*)
" original total mass ..."
570 call
conck(1,nvar,naux,time,rest)
572 call
valout(1,lfine,time,nvar,naux)
577 call cpu_time(cpu_start)
578 call system_clock(clock_start,clock_rate)
584 call
tick(nvar,cut,nstart,vtime,time,naux,t0,rest,dt_max)
587 call cpu_time(cpu_finish)
592 format_string=
"('============================== Timing Data ==============================')"
593 write(outunit,format_string)
594 write(*,format_string)
600 format_string=
"('Integration Time (stepgrid + BC + overhead)')"
601 write(outunit,format_string)
602 write(*,format_string)
605 format_string=
"('Level Wall Time (seconds) CPU Time (seconds) Total Cell Updates')"
606 write(outunit,format_string)
607 write(*,format_string)
611 call system_clock(clock_finish,clock_rate)
612 write(*,*)
"clock_rate ",clock_rate
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)
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
634 format_string=
"('All levels:')"
635 write(*,format_string)
636 write(outunit,format_string)
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
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
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
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
672 format_string=
"('Total time: ',1f15.3,' ',1f15.3,' ')"
677 write(*,format_string)
real(timetick,kind=8)/
real(clock_rate,kind=8), &
679 write(outunit,format_string)
real(timetick,kind=8)/
real(clock_rate,kind=8), &
682 format_string=
"('Using',i3,' thread(s)')"
683 write(outunit,format_string) maxthreads
684 write(*,format_string) maxthreads
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')")
696 write(*,
"(' Times for restart runs are cumulative')")
697 write(outunit,
"(' Times for restart runs are cumulative')")
704 format_string=
"('=========================================================================')"
705 write(outunit,format_string)
706 write(*,format_string)
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"
721 open(matunit,file=matfile,status=
'unknown',form=
'formatted')
722 write(matunit,*) matlabu-1
723 write(matunit,*) 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, &
733 write(outunit,802) i,numgrids(i)
734 802
format(
"for level ",i3,
" current num. grids = ",i7)
740 write(outunit,
"('current space usage = ',i12)") lentotsave
741 write(outunit,
"('maximum space usage = ',i12)") lenmax
742 write(outunit,
"('need space dimension = ',i12,/)") lendim
744 write(outunit,
"('number of cells advanced for time integration = ',f20.6)")&
747 write(outunit,
"(3x,'# cells advanced on level ',i4,' = ',f20.2)") &
751 write(outunit,
"('number of cells advanced for error estimation = ',f20.6,/)") &
753 if (evol + rvol > 0.d0)
then
754 ratmet = rvol / (evol + rvol) * 100.0d0
758 write(outunit,
"(' percentage of cells advanced in time = ', f10.2)") ratmet
759 write(outunit,
"(' maximum Courant number seen = ', f10.2)") cflmax
761 write(outunit,
"(//,' ------ end of AMRCLAW integration -------- ')")
subroutine cleanup(nvar, naux)
subroutine restrt(nsteps, time, nvar, naux)
subroutine conck(level, nvar, naux, time, rest)
subroutine valout(lst, lend, time, nvar, naux)
subroutine set_regions(fname)
subroutine opendatafile(iunit, fname)
subroutine set_gauges(restart, num_eqn, num_aux, fname)
subroutine outtre(mlev, outgrd, nvar, naux)
subroutine tick(nvar, cut, nstart, vtime, time, naux, start_time, rest, dt_max)
subroutine domain(nvar, vtime, nx, ny, naux, start_time)
subroutine setgrd(nvar, cut, naux, dtinit, start_time)