Skip to content

Commit

Permalink
changed two cavling solvers in ElmerIce to work with CrayCE
Browse files Browse the repository at this point in the history
  • Loading branch information
tzwinger committed Aug 19, 2024
1 parent 5aa95ac commit 50fe559
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 101 deletions.
43 changes: 9 additions & 34 deletions elmerice/Solvers/Calving3D.F90
Original file line number Diff line number Diff line change
Expand Up @@ -88,9 +88,6 @@ SUBROUTINE Find_Calving3D ( Model, Solver, dt, TransientSimulation )
CalvingValues(:), ForceVector(:)
REAL(KIND=dp), ALLOCATABLE :: STIFF(:,:), FORCE(:), HeightDirich(:), &
Rot_y_coords(:,:), Rot_z_coords(:,:)
#ifdef ELMER_BROKEN_MPI_IN_PLACE
REAL(KIND=dp) :: buffer
#endif
CHARACTER(LEN=MAX_NAME_LEN) :: SolverName, DistVarname, &
CIndexVarName, filename_root, filename,MaskName,&
FrontMaskName,TopMaskName,BotMaskName,LeftMaskName,RightMaskName, &
Expand Down Expand Up @@ -1259,37 +1256,15 @@ SUBROUTINE Find_Calving3D ( Model, Solver, dt, TransientSimulation )
END DO

!Pass to other partitions
#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer = Rot_y_coords(i,1)
CALL MPI_AllReduce(buffer, &
#else
CALL MPI_AllReduce(MPI_IN_PLACE, &
#endif
Rot_y_coords(i,1), 1, MPI_DOUBLE_PRECISION, MPI_MIN, ELMER_COMM_WORLD,ierr)

#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer = Rot_y_coords(i,2)
CALL MPI_AllReduce(buffer, &
#else
CALL MPI_AllReduce(MPI_IN_PLACE, &
#endif
Rot_y_coords(i,2), 1, MPI_DOUBLE_PRECISION, MPI_MAX, ELMER_COMM_WORLD,ierr)
CALL MPI_AllReduce(MPI_IN_PLACE, Rot_y_coords(i,1), &
1, MPI_DOUBLE_PRECISION, MPI_MIN, ELMER_COMM_WORLD,ierr)
CALL MPI_AllReduce(MPI_IN_PLACE, Rot_y_coords(i,2), &
1, MPI_DOUBLE_PRECISION, MPI_MAX, ELMER_COMM_WORLD,ierr)

#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer = Rot_z_coords(i,1)
CALL MPI_AllReduce(buffer, &
#else
CALL MPI_AllReduce(MPI_IN_PLACE, &
#endif
Rot_z_coords(i,1), 1, MPI_DOUBLE_PRECISION, MPI_MIN, ELMER_COMM_WORLD,ierr)

#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer = Rot_z_coords(i,2)
CALL MPI_AllReduce(buffer, &
#else
CALL MPI_AllReduce(MPI_IN_PLACE, &
#endif
Rot_z_coords(i,2), 1, MPI_DOUBLE_PRECISION, MPI_MAX, ELMER_COMM_WORLD,ierr)
CALL MPI_AllReduce(MPI_IN_PLACE, Rot_z_coords(i,1), &
1, MPI_DOUBLE_PRECISION, MPI_MIN, ELMER_COMM_WORLD,ierr)
CALL MPI_AllReduce(MPI_IN_PLACE, Rot_z_coords(i,2), &
1, MPI_DOUBLE_PRECISION, MPI_MAX, ELMER_COMM_WORLD,ierr)

IF(Boss .AND. Debug) PRINT *,'Debug, rot_y_coords: ',i,rot_y_coords(i,:)
IF(Boss .AND. Debug) PRINT *,'Debug, rot_z_coords: ',i,rot_z_coords(i,:)
Expand Down Expand Up @@ -2068,7 +2043,7 @@ SUBROUTINE CalvingStats(MaxBergVol)
END DO

IF(Visited) THEN
OPEN( UNIT=FileUnit, FILE=filename, STATUS='UNKNOWN', ACCESS='APPEND')
OPEN( UNIT=FileUnit, FILE=filename, STATUS='UNKNOWN', POSITION='APPEND')
ELSE
OPEN( UNIT=FileUnit, FILE=filename, STATUS='UNKNOWN')
WRITE(FileUnit, '(A,ES20.11,ES20.11,ES20.11)') "FrontOrientation: ",FrontOrientation
Expand Down
74 changes: 7 additions & 67 deletions elmerice/Solvers/Calving3D_lset.F90
Original file line number Diff line number Diff line change
Expand Up @@ -69,9 +69,6 @@ SUBROUTINE Find_Calving3D_LSet ( Model, Solver, dt, TransientSimulation )
PolyStart(:), PolyEnd(:), EdgeLine(:,:), EdgeCount(:), Nodes(:), StartNodes(:,:),&
WorkInt(:), WorkInt2D(:,:), PartCount(:), ElemsToAdd(:), PartElemsToAdd(:), &
EdgeLineNodes(:), NodePositions(:), FrontToLateralConstraint(:), UnfoundConstraints(:)
#ifdef ELMER_BROKEN_MPI_IN_PLACE
INTEGER, ALLOCATABLE :: buffer2(:)
#endif
REAL(KIND=dp) :: FrontOrientation(3), &
RotationMatrix(3,3), UnRotationMatrix(3,3), NodeHolder(3), MaxMeshDist,&
y_coord(2), TempDist,MinDist, xl,xr,yl, yr, xx,yy,&
Expand Down Expand Up @@ -993,9 +990,6 @@ SUBROUTINE Find_Calving3D_LSet ( Model, Solver, dt, TransientSimulation )

ALLOCATE(IMBdryConstraint(IMBdryCount))
IMBdryConstraint = 0
#ifdef ELMER_BROKEN_MPI_IN_PLACE
ALLOCATE(buffer2(IMBdryCount))
#endif

!Now cycle elements: for those with a node either side
!of domain boundary, cycle 3d mesh boundary elements
Expand Down Expand Up @@ -1057,13 +1051,7 @@ SUBROUTINE Find_Calving3D_LSet ( Model, Solver, dt, TransientSimulation )

!Send info back to boss
IF(Boss) THEN
#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer2 = IMBdryConstraint
CALL MPI_Reduce(buffer2, &
#else
CALL MPI_Reduce(MPI_IN_PLACE, &
#endif
IMBdryConstraint, IMBdryCount, MPI_INTEGER, &
CALL MPI_Reduce(MPI_IN_PLACE, IMBdryConstraint, IMBdryCount, MPI_INTEGER, &
MPI_MAX, 0, ELMER_COMM_WORLD, ierr)
ELSE
CALL MPI_Reduce(IMBdryConstraint, IMBdryConstraint, IMBdryCount, MPI_INTEGER, &
Expand Down Expand Up @@ -1145,13 +1133,7 @@ SUBROUTINE Find_Calving3D_LSet ( Model, Solver, dt, TransientSimulation )
END DO

IF(Boss) THEN
#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer2 = IMBdryConstraint
CALL MPI_Reduce(buffer2, &
#else
CALL MPI_Reduce(MPI_IN_PLACE, &
#endif
IMBdryConstraint, IMBdryCount, MPI_INTEGER, &
CALL MPI_Reduce(MPI_IN_PLACE, IMBdryConstraint, IMBdryCount, MPI_INTEGER, &
MPI_MAX, 0, ELMER_COMM_WORLD, ierr)
ELSE
CALL MPI_Reduce(IMBdryConstraint, IMBdryConstraint, IMBdryCount, MPI_INTEGER, &
Expand Down Expand Up @@ -1710,9 +1692,6 @@ FUNCTION GetFrontExtent(Mesh, RotationMatrix, DistVar, SearchDist, Buffer) RESUL
TYPE(Mesh_t), POINTER :: Mesh
TYPE(Variable_t), POINTER :: DistVar
REAL(KIND=dp) :: SearchDist, RotationMatrix(3,3), Extent(4), Buffer
#ifdef ELMER_BROKEN_MPI_IN_PLACE
REAL(KIND=dp) :: buffer2
#endif
!------------------------------
REAL(KIND=dp) :: NodeHolder(3)
INTEGER :: i,ierr
Expand All @@ -1739,37 +1718,10 @@ FUNCTION GetFrontExtent(Mesh, RotationMatrix, DistVar, SearchDist, Buffer) RESUL

END DO

#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer2 = extent(1)
CALL MPI_AllReduce(buffer2, &
#else
CALL MPI_AllReduce(MPI_IN_PLACE, &
#endif
extent(1), 1, MPI_DOUBLE_PRECISION, MPI_MIN, ELMER_COMM_WORLD, ierr)

#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer2 = extent(2)
CALL MPI_AllReduce(buffer2, &
#else
CALL MPI_AllReduce(MPI_IN_PLACE, &
#endif
extent(2), 1, MPI_DOUBLE_PRECISION, MPI_MAX, ELMER_COMM_WORLD, ierr)

#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer2 = extent(3)
CALL MPI_AllReduce(buffer2, &
#else
CALL MPI_AllReduce(MPI_IN_PLACE, &
#endif
extent(3), 1, MPI_DOUBLE_PRECISION, MPI_MIN, ELMER_COMM_WORLD, ierr)

#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer2 = extent(4)
CALL MPI_AllReduce(buffer2, &
#else
CALL MPI_AllReduce(MPI_IN_PLACE, &
#endif
extent(4), 1, MPI_DOUBLE_PRECISION, MPI_MAX, ELMER_COMM_WORLD, ierr)
CALL MPI_AllReduce(MPI_IN_PLACE, extent(1), 1, MPI_DOUBLE_PRECISION, MPI_MIN, ELMER_COMM_WORLD, ierr)
CALL MPI_AllReduce(MPI_IN_PLACE, extent(2), 1, MPI_DOUBLE_PRECISION, MPI_MAX, ELMER_COMM_WORLD, ierr)
CALL MPI_AllReduce(MPI_IN_PLACE, extent(3), 1, MPI_DOUBLE_PRECISION, MPI_MIN, ELMER_COMM_WORLD, ierr)
CALL MPI_AllReduce(MPI_IN_PLACE, extent(4), 1, MPI_DOUBLE_PRECISION, MPI_MAX, ELMER_COMM_WORLD, ierr)

extent(1) = extent(1) - buffer
extent(2) = extent(2) + buffer
Expand Down Expand Up @@ -1802,9 +1754,6 @@ SUBROUTINE CheckLateralCalving(Mesh, SolverParams, FrontPerm, CrevX,CrevY,CrevSt
REAL(KIND=dp), ALLOCATABLE :: PathPoly(:,:),xL(:),yL(:),xR(:),yR(:),WorkReal(:),WorkReal2(:,:)
LOGICAL :: inside,does_intersect,FoundIntersect
LOGICAL, ALLOCATABLE :: RemoveCrev(:), WorkLogical(:)
#ifdef ELMER_BROKEN_MPI_IN_PLACE
LOGICAL, ALLOCATABLE :: buffer(:)
#endif
CHARACTER(MAX_NAME_LEN) :: FuncName="CheckLateralCalving", Adv_EqName, LeftRailFName, RightRailFName
INTEGER, PARAMETER :: io=20

Expand Down Expand Up @@ -1933,9 +1882,6 @@ SUBROUTINE CheckLateralCalving(Mesh, SolverParams, FrontPerm, CrevX,CrevY,CrevSt
CLOSE(io)

ALLOCATE(RemoveCrev(NoPaths))
#ifdef ELMER_BROKEN_MPI_IN_PLACE
ALLOCATE(buffer(NoPaths))
#endif
RemoveCrev = .FALSE.
DO i=1, Mesh % NumberOfNodes

Expand Down Expand Up @@ -2040,13 +1986,7 @@ SUBROUTINE CheckLateralCalving(Mesh, SolverParams, FrontPerm, CrevX,CrevY,CrevSt
END IF
END DO

#ifdef ELMER_BROKEN_MPI_IN_PLACE
buffer = RemoveCrev
CALL MPI_ALLREDUCE(buffer, &
#else
CALL MPI_ALLREDUCE(MPI_IN_PLACE, &
#endif
RemoveCrev, NoPaths, MPI_LOGICAL, MPI_LOR, ELMER_COMM_WORLD, ierr)
CALL MPI_AllReduce(MPI_IN_PLACE, RemoveCrev, NoPaths, MPI_LOGICAL, MPI_LOR, ELMER_COMM_WORLD, ierr)

DO WHILE(ANY(RemoveCrev))
DO i=1, NoPaths
Expand Down

0 comments on commit 50fe559

Please sign in to comment.