Skip to content

Commit

Permalink
Gather on all (#144)
Browse files Browse the repository at this point in the history
* Gather matrix to all processes.

* Bug fix.

* Forgot a file.
  • Loading branch information
william-dawson authored Apr 14, 2020
1 parent b95cfa4 commit 3c06b9a
Show file tree
Hide file tree
Showing 4 changed files with 95 additions and 18 deletions.
60 changes: 47 additions & 13 deletions Source/Fortran/PSMatrixModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ MODULE PSMatrixModule
USE SMatrixModule, ONLY : Matrix_lsr, Matrix_lsc, DestructMatrix, &
& PrintMatrix, TransposeMatrix, ConjugateMatrix, SplitMatrix, &
& ComposeMatrix, ConvertMatrixType, MatrixToTripletList, &
& ConstructMatrixFromTripletList
& ConstructMatrixFromTripletList, ConstructEmptyMatrix
USE TimerModule, ONLY : StartTimer, StopTimer
USE TripletModule, ONLY : Triplet_r, Triplet_c, GetMPITripletType_r, &
& GetMPITripletType_c
Expand Down Expand Up @@ -175,8 +175,10 @@ MODULE PSMatrixModule
MODULE PROCEDURE CommSplitMatrix_ps
END INTERFACE
INTERFACE GatherMatrixToProcess
MODULE PROCEDURE GatherMatrixToProcess_psr
MODULE PROCEDURE GatherMatrixToProcess_psc
MODULE PROCEDURE GatherMatrixToProcess_psr_id
MODULE PROCEDURE GatherMatrixToProcess_psr_all
MODULE PROCEDURE GatherMatrixToProcess_psc_id
MODULE PROCEDURE GatherMatrixToProcess_psc_all
END INTERFACE
CONTAINS!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Construct an empty sparse, distributed, matrix.
Expand Down Expand Up @@ -1684,37 +1686,69 @@ SUBROUTINE ResizeMatrix_psc(this, new_size)
END SUBROUTINE ResizeMatrix_psc
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> This subroutine gathers the entire matrix into a local matrix on the
!> given process. This routine is used when printing, but also is useful for
!> debugging.
SUBROUTINE GatherMatrixToProcess_psr(this, local_mat, proc_id)
!> given process. The process id is a within_slice id, so the data will
!> still be replicated across slices.
SUBROUTINE GatherMatrixToProcess_psr_id(this, local_mat, within_slice_id)
!> The matrix to gather.
TYPE(Matrix_ps), INTENT(INOUT) :: this
!> The full matrix, stored in a local matrix.
TYPE(Matrix_lsr), INTENT(INOUT) :: local_mat
!> Which process to gather on.
INTEGER, INTENT(IN) :: proc_id
INTEGER, INTENT(IN) :: within_slice_id
!! Local Variables
TYPE(TripletList_r) :: tlist, sorted
TYPE(TripletList_r), DIMENSION(:), ALLOCATABLE :: slist

INCLUDE "distributed_includes/GatherMatrixToProcess.f90"
END SUBROUTINE GatherMatrixToProcess_psr
END SUBROUTINE GatherMatrixToProcess_psr_id
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> This subroutine gathers the entire matrix into a local matrix on to
!> every process.
SUBROUTINE GatherMatrixToProcess_psr_all(this, local_mat)
!> The matrix to gather.
TYPE(Matrix_ps), INTENT(INOUT) :: this
!> The full matrix, stored in a local matrix.
TYPE(Matrix_lsr), INTENT(INOUT) :: local_mat
!! Local Variables
TYPE(Matrix_lsr) :: local, localT
TYPE(Matrix_lsr) :: merged_columns
TYPE(Matrix_lsr) :: merged_columnsT
TYPE(Matrix_lsr) :: gathered

INCLUDE "distributed_includes/GatherMatrixToAll.f90"
END SUBROUTINE GatherMatrixToProcess_psr_all
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> This subroutine gathers the entire matrix into a local matrix on the
!> given process. This routine is used when printing, but also is useful for
!> debugging.
SUBROUTINE GatherMatrixToProcess_psc(this, local_mat, proc_id)
!> given process. The process id is a within_slice id, so the data will
!> still be replicated across slices.
SUBROUTINE GatherMatrixToProcess_psc_id(this, local_mat, within_slice_id)
!> The matrix to gather.
TYPE(Matrix_ps), INTENT(INOUT) :: this
!> The full matrix, stored in a local matrix.
TYPE(Matrix_lsc), INTENT(INOUT) :: local_mat
!> Which process to gather on.
INTEGER, INTENT(IN) :: proc_id
INTEGER, INTENT(IN) :: within_slice_id
!! Local Variables
TYPE(TripletList_c) :: tlist, sorted
TYPE(TripletList_c), DIMENSION(:), ALLOCATABLE :: slist

INCLUDE "distributed_includes/GatherMatrixToProcess.f90"
END SUBROUTINE GatherMatrixToProcess_psc
END SUBROUTINE GatherMatrixToProcess_psc_id
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> This subroutine gathers the entire matrix into a local matrix on to
!> every process.
SUBROUTINE GatherMatrixToProcess_psc_all(this, local_mat)
!> The matrix to gather.
TYPE(Matrix_ps), INTENT(INOUT) :: this
!> The full matrix, stored in a local matrix.
TYPE(Matrix_lsc), INTENT(INOUT) :: local_mat
!! Local Variables
TYPE(Matrix_lsc) :: local, localT
TYPE(Matrix_lsc) :: merged_columns
TYPE(Matrix_lsc) :: merged_columnsT
TYPE(Matrix_lsc) :: gathered

INCLUDE "distributed_includes/GatherMatrixToAll.f90"
END SUBROUTINE GatherMatrixToProcess_psc_all
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
END MODULE PSMatrixModule
43 changes: 43 additions & 0 deletions Source/Fortran/distributed_includes/GatherMatrixToAll.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
!! Local Data
TYPE(ReduceHelper_t) :: row_helper
TYPE(ReduceHelper_t) :: column_helper

CALL MergeMatrixLocalBlocks(this, local)

!! Merge Columns
CALL TransposeMatrix(local, localT)
CALL ReduceAndComposeMatrixSizes(localT, this%process_grid%column_comm, &
& merged_columns, column_helper)
DO WHILE(.NOT. TestReduceSizeRequest(column_helper))
END DO
CALL ReduceAndComposeMatrixData(localT, this%process_grid%column_comm, &
& merged_columns, column_helper)
DO WHILE(.NOT. TestReduceInnerRequest(column_helper))
END DO
DO WHILE(.NOT. TestReduceDataRequest(column_helper))
END DO
CALL ReduceAndComposeMatrixCleanup(localT, merged_columns, column_helper)

!! Merge Rows
CALL TransposeMatrix(merged_columns, merged_columnsT)
CALL ReduceAndComposeMatrixSizes(merged_columnsT, &
& this%process_grid%row_comm, gathered, row_helper)
DO WHILE(.NOT. TestReduceSizeRequest(row_helper))
END DO
CALL ReduceAndComposeMatrixData(merged_columnsT, &
& this%process_grid%row_comm, gathered, row_helper)
DO WHILE(.NOT. TestReduceInnerRequest(row_helper))
END DO
DO WHILE(.NOT. TestReduceDataRequest(row_helper))
END DO
CALL ReduceAndComposeMatrixCleanup(merged_columnsT, gathered, &
& row_helper)

!! Remove the excess rows and columns that come from the logical size.
CALL ConstructEmptyMatrix(local_mat, this%actual_matrix_dimension, &
& this%actual_matrix_dimension)
local_mat%outer_index = gathered%outer_index(:this%actual_matrix_dimension+1)
ALLOCATE(local_mat%inner_index(SIZE(gathered%inner_index)))
local_mat%inner_index = gathered%inner_index
ALLOCATE(local_mat%values(SIZE(gathered%values)))
local_mat%values = gathered%values
8 changes: 4 additions & 4 deletions Source/Fortran/distributed_includes/GatherMatrixToProcess.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,17 +12,17 @@

!! Send this to the target
ALLOCATE(slist(this%process_grid%slice_size))
CALL ConstructTripletList(slist(proc_id+1), tlist%CurrentSize)
DO II = 2, this%process_grid%slice_size
DO II = 1, this%process_grid%slice_size
CALL ConstructTripletList(slist(II))
END DO
slist(proc_id+1)%data(:list_size) = tlist%data(:list_size)
CALL ConstructTripletList(slist(within_slice_id+1), list_size)
slist(within_slice_id+1)%data(:list_size) = tlist%data(:list_size)
CALL DestructTripletList(tlist)
CALL RedistributeTripletLists(slist, this%process_grid%within_slice_comm, &
& tlist)

!! Create the local matrix
IF (this%process_grid%within_slice_rank .EQ. proc_id) THEN
IF (this%process_grid%within_slice_rank .EQ. within_slice_id) THEN
CALL SortTripletList(tlist, mat_dim, mat_dim, sorted, .TRUE.)
CALL ConstructMatrixFromTripletList(local_mat, sorted, &
& mat_dim, mat_dim)
Expand Down
2 changes: 1 addition & 1 deletion Source/Fortran/distributed_includes/PrintMatrix.f90
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
CALL GatherMatrixToProcess(this, local_mat, 0)
CALL GatherMatrixToProcess(this, local_mat, this%process_grid%RootID)

IF (IsRoot(this%process_grid)) THEN
IF (PRESENT(file_name_in)) THEN
Expand Down

0 comments on commit 3c06b9a

Please sign in to comment.