Skip to content

Commit

Permalink
Merge branch 'fix.overflow.firstSide.lastSide' into 'master.dev'
Browse files Browse the repository at this point in the history
[fix.overflow.firstSide.lastSide] Fixed overflow in firstSide/lastSide=INT(REAL(...)) statements due to large...

See merge request piclas/piclas!713
  • Loading branch information
scopplestone committed Oct 14, 2022
2 parents 815d90e + a66c57f commit 6242f6c
Show file tree
Hide file tree
Showing 10 changed files with 76 additions and 67 deletions.
4 changes: 2 additions & 2 deletions src/io_hdf5/hdf5_input_particle.f90
Original file line number Diff line number Diff line change
Expand Up @@ -92,8 +92,8 @@ SUBROUTINE ReadNodeSourceExtFromHDF5()
CALL GetVandermonde(N_Restart, NodeType, 1, NodeTypeVISU, Vdm_N_EQ, modal=.FALSE.)

! #if USE_MPI
! firstNode = INT(REAL( myComputeNodeRank *nUniqueGlobalNodes)/REAL(nComputeNodeProcessors))+1
! lastNode = INT(REAL((myComputeNodeRank+1)*nUniqueGlobalNodes)/REAL(nComputeNodeProcessors))
! firstNode = INT(REAL( myComputeNodeRank )*REAL(nUniqueGlobalNodes)/REAL(nComputeNodeProcessors))+1
! lastNode = INT(REAL((myComputeNodeRank+1))*REAL(nUniqueGlobalNodes)/REAL(nComputeNodeProcessors))
! #else
! firstNode = 1
! lastNode = nUniqueGlobalNodes
Expand Down
12 changes: 6 additions & 6 deletions src/particles/boundary/particle_boundary_init.f90
Original file line number Diff line number Diff line change
Expand Up @@ -682,8 +682,8 @@ SUBROUTINE BuildParticleBoundaryRotPeriodic(notMappedTotal)
IF (myComputeNodeRank.EQ.0) Rot2Glob_temp = -1.
CALL BARRIER_AND_SYNC(SurfSide2RotPeriodicSide_Shared_Win , MPI_COMM_SHARED)
CALL BARRIER_AND_SYNC(Rot2Glob_temp_Shared_Win , MPI_COMM_SHARED)
firstSide = INT(REAL( myComputeNodeRank *nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1)*nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))
firstSide = INT(REAL( myComputeNodeRank )*REAL(nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))
#else
firstSide = 1
lastSide = nSurfTotalSides
Expand Down Expand Up @@ -732,8 +732,8 @@ SUBROUTINE BuildParticleBoundaryRotPeriodic(notMappedTotal)
IF (myComputeNodeRank.EQ.0) RotPeriodicSideMapping_temp = 0
CALL BARRIER_AND_SYNC(NumRotPeriodicNeigh_Shared_Win , MPI_COMM_SHARED)
CALL BARRIER_AND_SYNC(RotPeriodicSideMapping_temp_Shared_Win , MPI_COMM_SHARED)
firstSide = INT(REAL( myComputeNodeRank *nRotPeriodicSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1)*nRotPeriodicSides)/REAL(nComputeNodeProcessors))
firstSide = INT(REAL( myComputeNodeRank )*REAL(nRotPeriodicSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1))*REAL(nRotPeriodicSides)/REAL(nComputeNodeProcessors))
#else
firstSide = 1
lastSide = nRotPeriodicSides
Expand Down Expand Up @@ -1086,8 +1086,8 @@ SUBROUTINE InitAdaptiveWallTemp()
END IF
BoundaryWallTemp => BoundaryWallTemp_Shared
CALL BARRIER_AND_SYNC(BoundaryWallTemp_Shared_Win,MPI_COMM_SHARED)
firstSide = INT(REAL( myComputeNodeRank *nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1)*nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))
firstSide = INT(REAL( myComputeNodeRank )*REAL(nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))
#else
ALLOCATE(BoundaryWallTemp(nSurfSample,nSurfSample,1:nComputeNodeSurfTotalSides))
BoundaryWallTemp = 0.
Expand Down
8 changes: 4 additions & 4 deletions src/particles/boundary/particle_boundary_sampling.f90
Original file line number Diff line number Diff line change
Expand Up @@ -196,8 +196,8 @@ SUBROUTINE InitParticleBoundarySampling()
! get number of BC-Sides
#if USE_MPI
! NO HALO REGION REDUCTION
firstSide = INT(REAL( myComputeNodeRank *nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1)*nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))
firstSide = INT(REAL( myComputeNodeRank )*REAL(nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1))*REAL(nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))
ALLOCATE(GlobalSide2SurfSideProc(1:3,firstSide:lastSide))
!,SurfSide2GlobalSideProc(1:3,1 :INT(nNonUniqueGlobalSides/REAL(nComputeNodeProcessors))))
#else
Expand Down Expand Up @@ -540,8 +540,8 @@ SUBROUTINE InitParticleBoundarySampling()
CALL MPI_WIN_LOCK_ALL(0,SurfSideArea_Shared_Win,IERROR)
SurfSideArea => SurfSideArea_Shared

firstSide = INT(REAL( myComputeNodeRank *nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1)*nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))
firstSide = INT(REAL( myComputeNodeRank )*REAL(nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeSurfTotalSides)/REAL(nComputeNodeProcessors))
#else
ALLOCATE(SurfSideArea(1:nSurfSample,1:nSurfSample,1:nComputeNodeSurfTotalSides))

Expand Down
2 changes: 1 addition & 1 deletion src/particles/emission/particle_emission_init.f90
Original file line number Diff line number Diff line change
Expand Up @@ -907,7 +907,7 @@ SUBROUTINE DetermineInitialParticleNumber()
INT(Species(iSpec)%Init(iInit)%ParticleNumber * 2. / (RadialWeighting%PartScaleFactor),8)
END IF
#if USE_MPI
insertParticles = insertParticles + INT(REAL(Species(iSpec)%Init(iInit)%ParticleNumber)/PartMPI%nProcs,8)
insertParticles = insertParticles + INT(REAL(Species(iSpec)%Init(iInit)%ParticleNumber)/REAL(PartMPI%nProcs),8)
#else
insertParticles = insertParticles + INT(Species(iSpec)%Init(iInit)%ParticleNumber,8)
#endif
Expand Down
28 changes: 14 additions & 14 deletions src/particles/particle_mesh/particle_bgm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -230,8 +230,8 @@ SUBROUTINE BuildBGMAndIdentifyHaloRegion()
CALL Allocate_Shared((/2,3,nGlobalElems/),BoundsOfElem_Shared_Win,BoundsOfElem_Shared)
CALL MPI_WIN_LOCK_ALL(0,ElemToBGM_Shared_Win ,IERROR)
CALL MPI_WIN_LOCK_ALL(0,BoundsOfElem_Shared_Win,IERROR)
firstElem = INT(REAL( myComputeNodeRank *nGlobalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1)*nGlobalElems)/REAL(nComputeNodeProcessors))
firstElem = INT(REAL( myComputeNodeRank )*REAL(nGlobalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1))*REAL(nGlobalElems)/REAL(nComputeNodeProcessors))
! Periodic Sides
MeshHasPeriodic = MERGE(.TRUE.,.FALSE.,GEO%nPeriodicVectors.GT.0)
MeshHasRotPeriodic = GEO%RotPeriodicBC
Expand Down Expand Up @@ -642,8 +642,8 @@ SUBROUTINE BuildBGMAndIdentifyHaloRegion()

! Distribute nHaloElements evenly on compute-node procs
IF (nHaloElems.GT.nComputeNodeProcessors) THEN
firstHaloElem = INT(REAL( myComputeNodeRank *nHaloElems)/REAL(nComputeNodeProcessors))+1
lastHaloElem = INT(REAL((myComputeNodeRank+1)*nHaloElems)/REAL(nComputeNodeProcessors))
firstHaloElem = INT(REAL( myComputeNodeRank )*REAL(nHaloElems)/REAL(nComputeNodeProcessors))+1
lastHaloElem = INT(REAL((myComputeNodeRank+1))*REAL(nHaloElems)/REAL(nComputeNodeProcessors))
ELSE
firstHaloElem = myComputeNodeRank + 1
IF (myComputeNodeRank.LT.nHaloElems) THEN
Expand Down Expand Up @@ -720,8 +720,8 @@ SUBROUTINE BuildBGMAndIdentifyHaloRegion()
nMPIProcHalo = COUNT(MPIProcHalo)

IF (nMPIProcHalo.GT.nComputeNodeProcessors) THEN
firstProcHalo = INT(REAL( myComputeNodeRank *nMPIProcHalo)/REAL(nComputeNodeProcessors))+1
lastProcHalo = INT(REAL((myComputeNodeRank+1)*nMPIProcHalo)/REAL(nComputeNodeProcessors))
firstProcHalo = INT(REAL( myComputeNodeRank )*REAL(nMPIProcHalo)/REAL(nComputeNodeProcessors))+1
lastProcHalo = INT(REAL((myComputeNodeRank+1))*REAL(nMPIProcHalo)/REAL(nComputeNodeProcessors))
ELSE
firstProcHalo = myComputeNodeRank + 1
IF (myComputeNodeRank.LT.nMPIProcHalo) THEN
Expand Down Expand Up @@ -959,8 +959,8 @@ SUBROUTINE BuildBGMAndIdentifyHaloRegion()
END DO ! iElem = firstHaloElem, lastHaloElem

IF (EnlargeBGM) THEN
firstElem = INT(REAL( myComputeNodeRank *nGlobalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1)*nGlobalElems)/REAL(nComputeNodeProcessors))
firstElem = INT(REAL( myComputeNodeRank )*REAL(nGlobalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1))*REAL(nGlobalElems)/REAL(nComputeNodeProcessors))
DO ElemID = firstElem, lastElem
! Only add peri halo elems
IF (ElemInfo_Shared(ELEM_HALOFLAG,ElemID).NE.3) CYCLE
Expand Down Expand Up @@ -1164,8 +1164,8 @@ SUBROUTINE BuildBGMAndIdentifyHaloRegion()
GETTIME(StartT)

#if USE_MPI
firstElem = INT(REAL( myComputeNodeRank *nGlobalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1)*nGlobalElems)/REAL(nComputeNodeProcessors))
firstElem = INT(REAL( myComputeNodeRank )*REAL(nGlobalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1))*REAL(nGlobalElems)/REAL(nComputeNodeProcessors))

! Flag each FIBGM element proc positive
BGMiglobDelta = BGMimaxglob - BGMiminglob
Expand Down Expand Up @@ -1623,8 +1623,8 @@ SUBROUTINE CheckPeriodicSides(EnlargeBGM)
REAL :: BoundsOfElemCenter(1:4),LocalBoundsOfElemCenter(1:4)
!===================================================================================================================================

firstElem = INT(REAL( myComputeNodeRank *nGlobalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1)*nGlobalElems)/REAL(nComputeNodeProcessors))
firstElem = INT(REAL( myComputeNodeRank )*REAL(nGlobalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1))*REAL(nGlobalElems)/REAL(nComputeNodeProcessors))

! The code below changes ElemInfo_Shared, identification of periodic elements must complete before
CALL MPI_BARRIER(MPI_COMM_SHARED,IERROR)
Expand Down Expand Up @@ -1814,8 +1814,8 @@ SUBROUTINE CheckRotPeriodicSides(EnlargeBGM)
INTEGER :: iPeriodicDir,iLocElem
!===================================================================================================================================

firstElem = INT(REAL( myComputeNodeRank *nGlobalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1)*nGlobalElems)/REAL(nComputeNodeProcessors))
firstElem = INT(REAL( myComputeNodeRank )*REAL(nGlobalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1))*REAL(nGlobalElems)/REAL(nComputeNodeProcessors))

! The code below changes ElemInfo_Shared, identification of periodic elements must complete before
CALL MPI_BARRIER(MPI_COMM_SHARED,IERROR)
Expand Down
4 changes: 2 additions & 2 deletions src/particles/particle_mesh/particle_mesh.f90
Original file line number Diff line number Diff line change
Expand Up @@ -380,8 +380,8 @@ SUBROUTINE InitParticleMesh()
CALL MPI_WIN_LOCK_ALL(0,SideSlabIntervals_Shared_Win,IERROR)
CALL Allocate_Shared((/nComputeNodeTotalSides/),BoundingBoxIsEmpty_Shared_Win,BoundingBoxIsEmpty_Shared)
CALL MPI_WIN_LOCK_ALL(0,BoundingBoxIsEmpty_Shared_Win,IERROR)
firstSide = INT(REAL (myComputeNodeRank *nComputeNodeTotalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1)*nComputeNodeTotalSides)/REAL(nComputeNodeProcessors))
firstSide = INT(REAL (myComputeNodeRank )*REAL(nComputeNodeTotalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeTotalSides)/REAL(nComputeNodeProcessors))
SideSlabNormals => SideSlabNormals_Shared
SideSlabIntervals => SideSlabIntervals_Shared
BoundingBoxIsEmpty => BoundingBoxIsEmpty_Shared
Expand Down
53 changes: 31 additions & 22 deletions src/particles/particle_mesh/particle_mesh_build.f90
Original file line number Diff line number Diff line change
Expand Up @@ -95,8 +95,8 @@ SUBROUTINE BuildElementRadiusTria()
#endif /* USE_MPI*/

#if USE_MPI
firstElem=INT(REAL(myComputeNodeRank* nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem =INT(REAL((myComputeNodeRank+1)*nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
firstElem=INT(REAL(myComputeNodeRank )*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem =INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
#else
firstElem=1
lastElem=nElems
Expand Down Expand Up @@ -207,8 +207,8 @@ SUBROUTINE BuildElemTypeAndBasisTria()
#endif /*USE_MPI*/

#if USE_MPI
firstElem = INT(REAL( myComputeNodeRank* nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1)*nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
firstElem = INT(REAL( myComputeNodeRank )*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
#else
firstElem = 1
lastElem = nElems
Expand Down Expand Up @@ -309,10 +309,14 @@ SUBROUTINE BuildEpsOneCell()

INTEGER :: ElemLocID
#endif /*USE_MPI*/
REAL :: StartT,EndT
!===================================================================================================================================

LBWRITE(UNIT_StdOut,'(132("-"))')
LBWRITE(UNIT_StdOut,'(A)') ' Building EpsOneCell for all elements ...'
IF(MPIRoot)THEN
LBWRITE(UNIT_StdOut,'(132("-"))')
LBWRITE(UNIT_StdOut,'(A)') ' Building EpsOneCell for all elements ...'
GETTIME(StartT)
END IF ! MPIRoot

! build sJ for all elements not on local proc
#if USE_MPI
Expand All @@ -326,8 +330,8 @@ SUBROUTINE BuildEpsOneCell()

CALL BARRIER_AND_SYNC(ElemsJ_Shared_Win,MPI_COMM_SHARED)

firstElem = INT(REAL( myComputeNodeRank *nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1)*nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
firstElem = INT(REAL( myComputeNodeRank )*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
#else
firstElem = 1
lastElem = nElems
Expand Down Expand Up @@ -411,6 +415,11 @@ SUBROUTINE BuildEpsOneCell()
!IF(CalcMeshInfo)THEN
! CALL AddToElemData(ElementOut,'epsOneCell',RealArray=epsOneCell(1:nElems))
!END IF
IF(MPIRoot)THEN
GETTIME(EndT)
LBWRITE(UNIT_stdOut,'(A,F0.3,A)') ' Building EpsOneCell for all elements ... DONE [',EndT-StartT,'s]'
LBWRITE(UNIT_StdOut,'(132("-"))')
END IF ! MPIRoot

END SUBROUTINE BuildEpsOneCell

Expand Down Expand Up @@ -512,8 +521,8 @@ SUBROUTINE BuildBCElemDistance()

CALL BARRIER_AND_SYNC(ElemToBCSides_Shared_Win,MPI_COMM_SHARED)

firstElem = INT(REAL( myComputeNodeRank *nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1)*nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
firstElem = INT(REAL( myComputeNodeRank )*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))

! if running on one node, halo_eps is meaningless. Get a representative BC_halo_eps for BC side identification
fullMesh = .FALSE.
Expand Down Expand Up @@ -798,8 +807,8 @@ SUBROUTINE BuildBCElemDistance()
#if USE_MPI
CALL BARRIER_AND_SYNC(SideBCMetrics_Shared_Win,MPI_COMM_SHARED)

firstSide = INT(REAL( myComputeNodeRank *nComputeNodeBCSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1)*nComputeNodeBCSides)/REAL(nComputeNodeProcessors))
firstSide = INT(REAL( myComputeNodeRank )*REAL(nComputeNodeBCSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeBCSides)/REAL(nComputeNodeProcessors))
#else
firstSide = 1
lastSide = nComputeNodeBCSides
Expand Down Expand Up @@ -1021,8 +1030,8 @@ SUBROUTINE BuildNodeNeighbourhood()
! 5. Fill ElemToElemMapping = [offset, Nbr of CN elements]
! Note that the number of elements stored in ElemToElemMapping(2,iElem) must be shifted after communication with other procs
#if USE_MPI
firstElem = INT(REAL( myComputeNodeRank *nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1)*nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
firstElem = INT(REAL( myComputeNodeRank )*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
#else
firstElem = 1
lastElem = nElems
Expand Down Expand Up @@ -1189,8 +1198,8 @@ SUBROUTINE BuildElementOriginShared()
ASSOCIATE(XCL_NGeo => XCL_NGeo_Shared)

! Set ranges
firstElem = INT(REAL( myComputeNodeRank *nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1)*nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
firstElem = INT(REAL( myComputeNodeRank )*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem = INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
#else
ALLOCATE(ElemBaryNGeo(1:3,nComputeNodeElems))
firstElem = 1
Expand Down Expand Up @@ -1317,8 +1326,8 @@ SUBROUTINE BuildElementBasisAndRadius()
#endif /*USE_MPI*/

#if USE_MPI
firstElem=INT(REAL( myComputeNodeRank* nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem =INT(REAL((myComputeNodeRank+1)*nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
firstElem=INT(REAL( myComputeNodeRank )*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))+1
lastElem =INT(REAL((myComputeNodeRank+1))*REAL(nComputeNodeTotalElems)/REAL(nComputeNodeProcessors))
#else
firstElem=1
lastElem=nElems
Expand Down Expand Up @@ -1418,8 +1427,8 @@ SUBROUTINE BuildSideOriginAndRadius()
!===================================================================================================================================

#if USE_MPI
firstSide = INT(REAL( myComputeNodeRank *nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1)*nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))
firstSide = INT(REAL( myComputeNodeRank )*REAL(nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1))*REAL(nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))
#else
firstSide = 1
lastSide = nNonUniqueGlobalSides
Expand Down Expand Up @@ -1577,8 +1586,8 @@ SUBROUTINE BuildLinearSideBaseVectors()
BaseVectors3 => BaseVectors3_Shared
BaseVectorsScale => BaseVectorsScale_Shared

firstSide = INT(REAL (myComputeNodeRank *nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1)*nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))
firstSide = INT(REAL (myComputeNodeRank )*REAL(nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))+1
lastSide = INT(REAL((myComputeNodeRank+1))*REAL(nNonUniqueGlobalSides)/REAL(nComputeNodeProcessors))
#else
ALLOCATE( BaseVectors0(1:3,1:nNonUniqueGlobalSides),&
BaseVectors1(1:3,1:nNonUniqueGlobalSides),&
Expand Down
Loading

0 comments on commit 6242f6c

Please sign in to comment.