Skip to content

Commit

Permalink
killed some output bugs, improved amr.
Browse files Browse the repository at this point in the history
  • Loading branch information
pbosler committed Feb 19, 2014
1 parent a355854 commit 8b7887b
Show file tree
Hide file tree
Showing 8 changed files with 68 additions and 36 deletions.
26 changes: 23 additions & 3 deletions BVESingleGaussianVortex.f90
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
program BVESolidBody
program BVEGaussVort
!******************************************************************************
! Peter A. Bosler
! Department of Mathematics
Expand Down Expand Up @@ -90,6 +90,7 @@ program BVESolidBody
integer(kint), parameter :: BROADCAST_INT_SIZE = 5, BROADCAST_REAL_SIZE = 11
integer(kint) :: broadcastIntegers(BROADCAST_INT_SIZE)
real(kreal) :: broadcastReals(BROADCAST_REAL_SIZE)
real(kreal) :: wallClock

namelist /sphereDefine/ panelKind, initNest, AMR, tracerMaxTol, tracerVarTol, &
refineMentLimit, circMaxTol, vortVarTol, lagVarTol
Expand All @@ -105,6 +106,9 @@ program BVESolidBody
call MPI_COMM_RANK(MPI_COMM_WORLD,procRank,mpiErrCode)

call InitLogger(exeLog,procRank)

wallClock = MPI_WTIME()

!
! read user input from namelist file, broadcast to all processes
!
Expand Down Expand Up @@ -164,23 +168,33 @@ program BVESolidBody

call New(flowMapREfine,refinementLimit,100000.0_kreal,lagVarTol,FLOWMAP_REFINE)
call SetRelativeFlowMapTol(sphere,flowMapRefine)

!
! initial refinement
!
call InitialRefinement(sphere,tracerRefine,SetCosineBellTracerOnMesh, cosBell, &
vortRefine, SetSingleGaussianVortexOnMesh,gaussVort)

call LogMessage(exeLog,DEBUG_LOGGING_LEVEL,logKey,' initial refinement done.')

call SetInitialLatitudeTracerOnMesh(sphere,2)



if ( panelKind == QUAD_PANEL) then
write(amrString,'(A,I1,A,I0.2,A)') 'quadAMR_',initNest,'to',initNest+refinementLimit,'_'
endif
else
else ! uniform mesh
! nullify AMR variables
call New(tracerRefine)
call New(vortRefine)
call New(flowMapRefine)
if ( panelKind == QUAD_PANEL ) then
write(amrString,'(A,I1,A)') 'quadUnif',initNest,'_'
endif
endif

call SetInitialLatitudeTracerOnMesh(sphere,2)

!
! initialize output, output t = 0 data
!
Expand Down Expand Up @@ -227,6 +241,7 @@ program BVESolidBody
call LagrangianRemesh(sphere, SetSingleGaussianVortexOnMesh, gaussVort, vortRefine, &
SetCosineBellTracerOnMesh, cosBell, tracerRefine, &
flowMapRefine)
call SetInitialLatitudeTracerOnMesh(sphere,2)
!
! create new associated objects
!
Expand Down Expand Up @@ -264,6 +279,11 @@ program BVESolidBody
!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
! Clear memory and Finalize
!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

write(logstring,'(A, F8.2,A)') 'elapsed time = ', (MPI_WTIME() - wallClock)/60.0, ' minutes.'
call LogMessage(exelog,TRACE_LOGGING_LEVEL,'PROGRAM COMPLETE : ',trim(logstring))


call Delete(bveRK4)
if ( procRank == 0 ) call Delete(vtkOut)
call Delete(vortRefine)
Expand Down
28 changes: 17 additions & 11 deletions LatLonOutput.f90
Original file line number Diff line number Diff line change
Expand Up @@ -26,18 +26,19 @@ module LatLonOutputModule

implicit none
private
public LatLonSource
public LLSource
public New, Delete
public LatLonOutput, UpdateFilename
public LLOutput, UpdateFilename

type VTKSource
type LLSource
character(len = 256) :: filename
character(len = 128) :: title
type(STRIPACKData) :: delTri
type(SSRFPACKData) :: vectorSource
type(SSRFPACKData) :: scalarSource
integer(kint) :: nLon
real(kreal), pointer :: lats(:) => null(), lons(:)=>null()
real(kreal), pointer :: lats(:) => null(),&
lons(:) => null()
end type
!
!----------------
Expand Down Expand Up @@ -65,7 +66,7 @@ module LatLonOutputModule
end interface

interface UpdateFilename
module procedure
module procedure UpdateFilenameLL
end interface

contains
Expand All @@ -76,14 +77,14 @@ module LatLonOutputModule
!

subroutine NewPrivate(self,aMesh,filename,nLon)
type(LatLonSource), intent(out) :: self
type(LLSource), intent(out) :: self
type(SphereMesh), intent(in) :: aMesh
character(len=*), intent(in) :: filename
integer(kint), intent(in), optional :: nLon
! local variables
real(kreal) :: dLambda
integer(kint) :: j

if (.not. logInit) call InitLogger(log,procRank)
if ( present(nLon) ) then
dLambda = 2.0_kreal*PI/real(nLon,kreal)
Expand All @@ -94,7 +95,7 @@ subroutine NewPrivate(self,aMesh,filename,nLon)
allocate(self%lats(nLon/2 + 1))
do j=1,nLon
self%lons(j) = (j-1)*dLambda
enddo
enddo
do j=1,nLon/2+1
self%lats(j) = -PI/2.0_kreal + (j-1)*dLambda
enddo
Expand All @@ -103,19 +104,24 @@ subroutine NewPrivate(self,aMesh,filename,nLon)
end subroutine

subroutine DeletePrivate(self)
type(LatLonSource), intent(inout) :: self
type(LLSource), intent(inout) :: self
deallocate(self%lats)
deallocate(self%lons)
call Delete(self%deltri)
call Delete(self%scalar
call Delete(self%scalarSource)
call Delete(self%vectorSource)
end subroutine

!
!----------------
! Public functions
!----------------
!

subroutine UpdateFileNameLL(self,filename)
type(LLSource), intent(inout) ::: self
character(len=*), intent(in) :: filename
self%filename = trim(filename)
end subroutine


!
Expand Down
2 changes: 1 addition & 1 deletion NumberKinds3.f90
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ module NumberKindsModule
WRITE_UNIT_2 = 13, &
WRITE_UNIT_3 = 14, &
MAX_STRING_LENGTH = 256
! Mesh constants
! Mesh & application constants
integer(KINT), parameter :: QUAD_PANEL = 4, &
TRI_PANEL = 3, &
ADVECTION_SOLVER = 90, &
Expand Down
4 changes: 2 additions & 2 deletions OutputWriter2.f90
Original file line number Diff line number Diff line change
Expand Up @@ -146,10 +146,10 @@ subroutine WriteReal(self,key,val)
character(len=*), intent(in) :: key
real(kreal), intent(in) :: val
character(len=32) :: form
if ( val >= 1.0d9 ) then
if ( abs(val) >= 1.0d7 ) then
form = FormatWithIndent(self,'(A,2X,E24.8)')
else
form = FormatWithIndent(self,'(A,2X,F24.15)')
form = FormatWithIndent(self,'(A,2X,F24.12)')
endif
write(self%fileUnit,form) trim(key), val
end subroutine
Expand Down
6 changes: 3 additions & 3 deletions Panels.f90
Original file line number Diff line number Diff line change
Expand Up @@ -516,7 +516,7 @@ subroutine ScatterPanels(self,activePanels,activeMap,passivePanels,passiveMap)
passivePanels
integer(kint), intent(in) :: activeMap(:), &
passiveMap(:)
! local variables
! local variables
integer(kint) :: j

call LogMessage(log,DEBUG_LOGGING_LEVEL,logKey,'Entering ScatterPanels...')
Expand Down Expand Up @@ -594,8 +594,8 @@ subroutine LogPanelStats(self,aLog,message)
call LogMessage(aLog,TRACE_LOGGING_LEVEL,key,self%N_Max)
key = 'MaxNest = '
call LogMessage(aLog,TRACE_LOGGING_LEVEL,key,maxval(self%nest(1:self%N)))
key = 'Surface Area = '
call LogMessage(aLog,TRACE_LOGGING_LEVEL,key,sum(self%area(1:self%N)))
key = 'Surface Area error = '
call LogMessage(aLog,TRACE_LOGGING_LEVEL,key,abs(sum(self%area(1:self%N)) - 4.0_kreal*PI*EARTH_RADIUS*EARTH_RADIUS) )
maxU = 0.0_kreal
minU = 0.0_kreal
do j=1,self%N
Expand Down
29 changes: 17 additions & 12 deletions RefineRemesh2.f90
Original file line number Diff line number Diff line change
Expand Up @@ -211,7 +211,7 @@ subroutine InitialRefinement(aMesh, refineTracer, updateTracerOnMesh, tracerDef,
call FlagPanelsForCirculationRefinement(refineFlag,aMesh,refineRelVort,startIndex)
counter1 = count(refineFlag) - counter1
call FlagPanelsForRelVortVariationRefinement(refineFlag,aMesh,refineRelVort,startIndex)
counter2 = count(refineFlag) - counter2
counter2 = count(refineFlag) - counter1
write(formatString,'(A)') '(A,I8,A)'
write(logString,formatString) 'circMax criterion triggered ', counter1, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
Expand All @@ -235,7 +235,7 @@ subroutine InitialRefinement(aMesh, refineTracer, updateTracerOnMesh, tracerDef,
! check for memory, exit if insufficient
!
if ( spaceLeft/4 < refineCount ) then
call LogMessage(log,WARNING_LOGGING_LEVEL,'InitRefine : ',' insufficient memory for AMR.')
call LogMessage(log,WARNING_LOGGING_LEVEL,'InitRefine : WARNING ',' insufficient memory for AMR.')
deallocate(refineFlag)
return
endif
Expand Down Expand Up @@ -275,7 +275,7 @@ subroutine InitialRefinement(aMesh, refineTracer, updateTracerOnMesh, tracerDef,
!
! Prevent too much refinement
!
if ( amrLoopCounter + 1 >= limit ) then
if ( amrLoopCounter >= limit ) then
keepGoing = .FALSE.
call LogMessage(log,WARNING_LOGGING_LEVEL,'InitRefine WARNING : ',' refinement limit reached.')
endif
Expand Down Expand Up @@ -307,6 +307,9 @@ subroutine InitialRefinement(aMesh, refineTracer, updateTracerOnMesh, tracerDef,
write(logString,formatString) 'relVortVar criterion triggered ', counter2, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
endif

refineCount = count(refineFlag)

!
! exit if refinement is not needed
!
Expand Down Expand Up @@ -449,7 +452,7 @@ subroutine LagrangianRemesh(aMesh, setVorticity, vortDef, vortRefine, &
write(logString,formatString) 'tracerMax criterion triggered ', counter1, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
write(logString,formatString) 'tracerVar criterion triggered ', counter2, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
call LogMessage(log,TRACE_LOGGING_LEVEL,'LagRemesh AMR : ',logString)
endif
if ( refineVort) then
limit = max(limit,vortRefine%limit)
Expand All @@ -462,7 +465,7 @@ subroutine LagrangianRemesh(aMesh, setVorticity, vortDef, vortRefine, &
write(logString,formatString) 'circMax criterion triggered ', counter1, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
write(logString,formatString) 'relVortVar criterion triggered ', counter2, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
call LogMessage(log,TRACE_LOGGING_LEVEL,'LagRemesh AMR : ',logString)
endif
if ( refineFlowMap ) then
limit = max(limit,flowMapRefine%limit)
Expand All @@ -471,6 +474,7 @@ subroutine LagrangianRemesh(aMesh, setVorticity, vortDef, vortRefine, &
counter1 = count(refineFlag) - counter1
write(formatString,'(A)') '(A,I8,A)'
write(logString,formatString) 'flowMap variation criterion triggered ', counter1, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'LagRemesh AMR : ',logString)
endif

refineCount = count(refineFlag)
Expand All @@ -495,7 +499,7 @@ subroutine LagrangianRemesh(aMesh, setVorticity, vortDef, vortRefine, &
amrLoopCounter = amrLoopCounter + 1

write(logString,'(A,I3,A,I8,A)') 'AMR loop ',amrLoopCounter,' : refining ',refineCount,' panels.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
call LogMessage(log,TRACE_LOGGING_LEVEL,'LagRemesh AMR : ',logString)
!
! divide flagged panels
!
Expand Down Expand Up @@ -537,7 +541,7 @@ subroutine LagrangianRemesh(aMesh, setVorticity, vortDef, vortRefine, &
!
! prevent too much refinement
!
if ( amrLoopCounter + 1 >= limit ) then
if ( amrLoopCounter >= limit ) then
keepGoing = .FALSE.
call LogMessage(log,WARNING_LOGGING_LEVEL,'LagRemesh WARNING :',' refinement limit reached.')
endif
Expand All @@ -555,9 +559,9 @@ subroutine LagrangianRemesh(aMesh, setVorticity, vortDef, vortRefine, &
counter2 = count(refineFlag) - counter1
write(formatString,'(A)') '(A,I8,A)'
write(logString,formatString) 'tracerMax criterion triggered ', counter1, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
call LogMessage(log,TRACE_LOGGING_LEVEL,'LagRemesh AMR : ',logString)
write(logString,formatString) 'tracerVar criterion triggered ', counter2, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
call LogMessage(log,TRACE_LOGGING_LEVEL,'LagRemesh AMR : ',logString)
endif
if ( refineVort) then
limit = max(limit,vortRefine%limit)
Expand All @@ -568,9 +572,9 @@ subroutine LagrangianRemesh(aMesh, setVorticity, vortDef, vortRefine, &
counter2 = count(refineFlag) - counter1
write(formatString,'(A)') '(A,I8,A)'
write(logString,formatString) 'circMax criterion triggered ', counter1, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
call LogMessage(log,TRACE_LOGGING_LEVEL,'LagRemesh AMR : ',logString)
write(logString,formatString) 'relVortVar criterion triggered ', counter2, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'InitRefine : ',logString)
call LogMessage(log,TRACE_LOGGING_LEVEL,'LagRemesh AMR : ',logString)
endif
if ( refineFlowMap ) then
limit = max(limit,flowMapRefine%limit)
Expand All @@ -579,6 +583,7 @@ subroutine LagrangianRemesh(aMesh, setVorticity, vortDef, vortRefine, &
counter1 = count(refineFlag) - counter1
write(formatString,'(A)') '(A,I8,A)'
write(logString,formatString) 'flowMap variation criterion triggered ', counter1, ' times.'
call LogMessage(log,TRACE_LOGGING_LEVEL,'LagRemesh AMR : ',logString)
endif

refineCount = count(refineFlag)
Expand All @@ -591,7 +596,7 @@ subroutine LagrangianRemesh(aMesh, setVorticity, vortDef, vortRefine, &
call LogMessage(log,TRACE_LOGGING_LEVEL,'LagRemesh : ','refinement comverged.')
keepGoing = .FALSE.
elseif ( spaceLeft/4 < refineCount ) then
call LogMessage(log,WARNING_LOGGING_LEVEL,'LagRemesh : ','insufficient memory to continue AMR.')
call LogMessage(log,WARNING_LOGGING_LEVEL,'LagRemesh : WARNING ','insufficient memory to continue AMR.')
keepGoing = .FALSE.
else
keepGoing = .TRUE.
Expand Down
1 change: 1 addition & 0 deletions SSRFPACKInterface2.f90
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ module SSRFPACKInterfaceModule
public SetSourceLagrangianParameter
public SetSourceAbsVort, SetSourceRelVort
public SetSourceTracer
public SetSourceVelocity
public SetSigmaTol
public SIGMA_FLAG, GRAD_FLAG
public InterpolateVector, InterpolateScalar
Expand Down
8 changes: 4 additions & 4 deletions gaussianVortex.namelist
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@
tracerVarTol = 100000.0
refinementLimit = 3
circMaxTol = 0.08
vortVarTol = 10000.0
lagVarTol = 1.0
vortVarTol = 0.4
lagVarTol = 1000.0
/

& vorticityDefine
Expand All @@ -18,13 +18,13 @@
/

& timeStepping
tfinal = 0.5 ! days
tfinal = 1.0 ! days
dt = 0.01 ! days
remeshInterval = 30 ! timesteps
/

& fileIO
outputDir = '.'
jobPrefix = 'bveGaussVort_rm30'
jobPrefix = 'bveGaussVort_rm30_vortAMR'
frameOut = 1
/

0 comments on commit 8b7887b

Please sign in to comment.