Skip to content

Commit

Permalink
Put the overset code on a memory diet. Removed the storage of gInd, m…
Browse files Browse the repository at this point in the history
…yI, myJ,

myK, dI, dJ, dK. This reduces the peak memory usage during overset assembly.
Currently the gInd required for the adjoint is disabled so the solve WILL NOT
WORK.
  • Loading branch information
gkenway committed Nov 30, 2016
1 parent b4e6f69 commit b32cfb4
Show file tree
Hide file tree
Showing 11 changed files with 554 additions and 299 deletions.
4 changes: 2 additions & 2 deletions src/adjoint/adjointUtils.F90
Original file line number Diff line number Diff line change
Expand Up @@ -398,7 +398,7 @@ subroutine setupStateResidualMatrix(matrix, useAD, usePC, useTranspose, &
else
fInd = fringePtr(1, i, j, k)
do m=1,8
cols(m) = flowDoms(nn, level, sps)%fringes(fInd)%gInd(m)
!cols(m) = flowDoms(nn, level, sps)%fringes(fInd)%gInd(m)
end do
call fracToWeights(flowDoms(nn, level, sps)%fringes(fInd)%donorFrac, &
weights)
Expand Down Expand Up @@ -1543,7 +1543,7 @@ subroutine statePreAllocation(onProc, offProc, wSize, stencil, N_stencil, &
overset = .True.
fInd = fringePtr(1, iii, jjj, kkk)
do kk=1,8
gc = fringes(fInd)%gInd(kk)
!gc = fringes(fInd)%gInd(kk)
if (gc >= 0) then
n = n + 1
cellBuffer(n) = gc
Expand Down
272 changes: 155 additions & 117 deletions src/modules/block.F90
Original file line number Diff line number Diff line change
Expand Up @@ -169,17 +169,12 @@ module block
real(kind=realType) :: quality

! This is the information regarding where the cell came from.
integer(kind=intType) :: myBlock, myI, myJ, myK
integer(kind=intType) :: myBlock, myIndex

! This is the information about the donor that was found. Note we
! use dI, dJ, dK, short for donorI, etc.
integer(kind=intType) :: donorProc, donorBlock, dI, dJ, dK
! This is the information about the donor that was found
integer(kind=intType) :: donorProc, donorBlock, dIndex
real(kind=realType) :: donorFrac(3)

! gInd are the global indices of the donor cells. We will need
! these for forming the PC for the Newton Krylov solver
integer(kind=intType), dimension(8) :: gInd

end type fringeType

interface operator(<=)
Expand All @@ -190,6 +185,20 @@ module block
module procedure lessFringeType
end interface operator(<)

type interpPtType
integer(kind=intType) :: donorProc, donorBlock, dI, dJ, dK, myBlock
real(kind=realType) :: donorFrac(3)
end type interpPtType

interface operator(<=)
module procedure lessEqualinterpPtType
end interface operator(<=)

interface operator(<)
module procedure lessInterpPtType
end interface operator(<)



! The definition of the derived data type block_type, which
! stores dimensions, coordinates, solution, etc.
Expand Down Expand Up @@ -310,6 +319,7 @@ module block
integer(kind=intType), dimension(:,:,:), pointer :: forcedRecv
type(fringeType) , dimension(:), pointer :: fringes=>null()
integer(kind=intType), dimension(:, :, :, :), pointer :: fringePtr=>null()
integer(kind=intType), dimension(:, :), pointer :: fringeGInd=>null()
integer(kind=intType), pointer :: nDonors
integer(kind=intType) :: nDonorsOnOwnedCells

Expand Down Expand Up @@ -819,59 +829,27 @@ logical function lessEqualFringeType(g1, g2)
! Compare the indices of the halo. First k, then j and
! finally i.

if(g1%dK < g2%dK) then
lessEqualfringeType = .true.
return
else if(g1%dK > g2%dK) then
lessEqualfringeType = .false.
return
endif

if(g1%dJ < g2%dJ) then
if(g1%dIndex < g2%dIndex) then
lessEqualfringeType = .true.
return
else if(g1%dJ > g2%dJ) then
else if(g1%dindex > g2%dIndex) then
lessEqualfringeType = .false.
return
endif

if(g1%dI < g2%dI) then
lessEqualfringeType = .true.
return
else if(g1%dI > g2%dI) then
lessEqualfringeType = .false.
return
endif

else if (fringeSortType == sortByReceiver) then


! Compare my indices

if(g1%myK < g2%myK) then
if(g1%myIndex < g2%myIndex) then
lessEqualfringeType = .true.
return
else if(g1%myK > g2%myK) then
else if(g1%myIndex > g2%myIndex) then
lessEqualfringeType = .false.
return
endif

if(g1%myJ < g2%myJ) then
lessEqualfringeType = .true.
return
else if(g1%myJ > g2%myJ) then
lessEqualfringeType = .false.
return
endif

if(g1%myI < g2%myI) then
lessEqualfringeType = .true.
return
else if(g1%myI > g2%myI) then
lessEqualfringeType = .false.
return
endif

! Now compare the donor information:

if(g1%donorProc < g2%donorProc) then
Expand All @@ -895,26 +873,10 @@ logical function lessEqualFringeType(g1, g2)
! Compare the indices of the halo. First k, then j and
! finally i.

if(g1%dK < g2%dK) then
lessEqualfringeType = .true.
return
else if(g1%dK > g2%dK) then
lessEqualfringeType = .false.
return
endif

if(g1%dJ < g2%dJ) then
lessEqualfringeType = .true.
return
else if(g1%dJ > g2%dJ) then
lessEqualfringeType = .false.
return
endif

if(g1%dI < g2%dI) then
if(g1%dIndex < g2%dIndex) then
lessEqualfringeType = .true.
return
else if(g1%dI > g2%dI) then
else if(g1%dIndex > g2%dIndex) then
lessEqualfringeType = .false.
return
endif
Expand Down Expand Up @@ -962,59 +924,26 @@ logical function lessFringeType(g1, g2)
! Compare the indices of the halo. First k, then j and
! finally i.

if(g1%dK < g2%dK) then
lessfringeType = .true.
return
else if(g1%dK > g2%dK) then
lessfringeType = .false.
return
endif

if(g1%dJ < g2%dJ) then
lessfringeType = .true.
return
else if(g1%dJ > g2%dJ) then
lessfringeType = .false.
return
endif

if(g1%dI < g2%dI) then
if(g1%dIndex < g2%dIndex) then
lessfringeType = .true.
return
else if(g1%dI > g2%dI) then
else if(g1%dIndex > g2%dIndex) then
lessfringeType = .false.
return
endif

else if (fringeSortType == sortByReceiver) then


! Compare my indices

if(g1%myK < g2%myK) then
lessfringeType = .true.
return
else if(g1%myK > g2%myK) then
lessfringeType = .false.
return
endif

if(g1%myJ < g2%myJ) then
if(g1%myIndex < g2%myIndex) then
lessfringeType = .true.
return
else if(g1%myJ > g2%myJ) then
else if(g1%myIndex > g2%myIndex) then
lessfringeType = .false.
return
endif

if(g1%myI < g2%myI) then
lessfringeType = .true.
return
else if(g1%myI > g2%myI) then
lessfringeType = .false.
return
endif

! Now compare the donor information:

if(g1%donorProc < g2%donorProc) then
Expand All @@ -1038,26 +967,10 @@ logical function lessFringeType(g1, g2)
! Compare the indices of the halo. First k, then j and
! finally i.

if(g1%dK < g2%dK) then
lessfringeType = .true.
return
else if(g1%dK > g2%dK) then
lessfringeType = .false.
return
endif

if(g1%dJ < g2%dJ) then
lessfringeType = .true.
return
else if(g1%dJ > g2%dJ) then
lessfringeType = .false.
return
endif

if(g1%dI < g2%dI) then
if(g1%dIndex < g2%dIndex) then
lessfringeType = .true.
return
else if(g1%dI > g2%dI) then
else if(g1%dIndex > g2%dIndex) then
lessfringeType = .false.
return
endif
Expand All @@ -1069,4 +982,129 @@ logical function lessFringeType(g1, g2)

end function lessFringeType


logical function lessEqualInterpPtType(g1, g2)

! lessEqual returns .true. if g1 <= g2 and .false. otherwise.
! The comparison is firstly based on the processor ID of the
! donor, then the block, then then the I, J, K
!
implicit none
!
! Function arguments.
!
type(interpPtType), intent(in) :: g1, g2
!

if(g1%donorProc < g2%donorProc) then
lessEqualinterpPtType = .true.
return
else if(g1%donorProc > g2%donorProc) then
lessEqualinterpPtType = .false.
return
endif

! Donor processors are identical. Now we check the block

if(g1%donorBlock < g2%donorBlock) then
lessEqualinterpPtType = .true.
return
else if(g1%donorBlock > g2%donorBlock) then
lessEqualinterpPtType = .false.
return
endif

! Compare the indices of the halo. First k, then j and
! finally i.

if(g1%dK < g2%dK) then
lessEqualinterpPtType = .true.
return
else if(g1%dK > g2%dK) then
lessEqualinterpPtType = .false.
return
endif

if(g1%dJ < g2%dJ) then
lessEqualinterpPtType = .true.
return
else if(g1%dJ > g2%dJ) then
lessEqualinterpPtType = .false.
return
endif

if(g1%dI < g2%dI) then
lessEqualinterpPtType = .true.
return
else if(g1%dI > g2%dI) then
lessEqualinterpPtType = .false.
return
endif

! Both entities are identical. So set lessEqual to .true.

lessEqualinterpPtType = .true.

end function lessEqualInterpPtType

logical function lessInterpPtType(g1, g2)

implicit none
!
! Function arguments.
!
type(interpPtType), intent(in) :: g1, g2
!
if(g1%donorProc < g2%donorProc) then
lessInterpPtType = .true.
return
else if(g1%donorProc > g2%donorProc) then
lessInterpPtType = .false.
return
endif

! Donor processors are identical. Now we check the block

if(g1%donorBlock < g2%donorBlock) then
lessInterpPtType = .true.
return
else if(g1%donorBlock > g2%donorBlock) then
lessInterpPtType = .false.
return
endif

! Compare the indices of the halo. First k, then j and
! finally i.

if(g1%dK < g2%dK) then
lessInterpPtType = .true.
return
else if(g1%dK > g2%dK) then
lessInterpPtType = .false.
return
endif

if(g1%dJ < g2%dJ) then
lessInterpPtType = .true.
return
else if(g1%dJ > g2%dJ) then
lessInterpPtType = .false.
return
endif

if(g1%dI < g2%dI) then
lessInterpPtType = .true.
return
else if(g1%dI > g2%dI) then
lessInterpPtType = .false.
return
endif

! Both entities are identical. So set less to .False.

lessInterpPtType = .False.

end function lessInterpPtType


end module block
Loading

0 comments on commit b32cfb4

Please sign in to comment.