Skip to content

Commit

Permalink
Optimizations related to matrix conversion (#148)
Browse files Browse the repository at this point in the history
* First work on in place.

* Optimization of the code related to conversion.

This also incldues some code reduction work.

* Something wrong with the CI?

* Noticed a linting error.
  • Loading branch information
william-dawson authored May 21, 2020
1 parent f972047 commit 40b2433
Show file tree
Hide file tree
Showing 12 changed files with 207 additions and 158 deletions.
4 changes: 1 addition & 3 deletions .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,4 @@ jobs:
TESTEXAMPLES: ${{ matrix.testexamples }}
- name: lint
run: |
cd UnitTests
bash lint.sh
cd ../
bash UnitTests/lint.sh
29 changes: 10 additions & 19 deletions Source/Fortran/MatrixConversionModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,11 @@
!> to data structures used in other programs.
MODULE MatrixConversionModule
USE DataTypesModule, ONLY : NTREAL
USE MatrixMapsModule, ONLY : MapMatrix_psr
USE PSMatrixModule, ONLY : Matrix_ps, ConvertMatrixToReal, CopyMatrix, &
& DestructMatrix
& DestructMatrix, MergeMatrixLocalBlocks, SplitMatrixToLocalBlocks
USE PSMatrixAlgebraModule, ONLY : PairwiseMultiplyMatrix, ScaleMatrix, &
& IncrementMatrix
USE SMatrixModule, ONLY : Matrix_lsr, DestructMatrix
IMPLICIT NONE
PRIVATE
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Expand All @@ -27,16 +27,17 @@ SUBROUTINE SnapMatrixToSparsityPattern(mat, pattern)
TYPE(Matrix_ps) :: filtered
TYPE(Matrix_ps) :: pattern_1s
TYPE(Matrix_ps) :: pattern_0s
TYPE(Matrix_ps) :: pattern_real
INTEGER :: II
TYPE(Matrix_lsr) :: local_mat

!! First we need to make sure that the sparsity pattern is all 1s.
IF (pattern%is_complex) THEN
CALL ConvertMatrixToReal(pattern, pattern_real)
CALL ConvertMatrixToReal(pattern, pattern_1s)
ELSE
CALL CopyMatrix(pattern, pattern_real)
CALL CopyMatrix(pattern, pattern_1s)
END IF
CALL MapMatrix_psr(pattern_real, pattern_1s, SetMatrixToOne)
CALL MergeMatrixLocalBlocks(pattern_1s, local_mat)
local_mat%values = 1.0_NTREAL
CALL SplitMatrixToLocalBlocks(pattern_1s, local_mat)

!! Then all zeros
CALL CopyMatrix(pattern_1s, pattern_0s)
Expand All @@ -54,19 +55,9 @@ SUBROUTINE SnapMatrixToSparsityPattern(mat, pattern)
!! Cleanup
CALL DestructMatrix(pattern_1s)
CALL DestructMatrix(pattern_0s)
CALL DestructMatrix(pattern_real)
CALL DestructMatrix(filtered)
CALL DestructMatrix(local_mat)

END SUBROUTINE SnapMatrixToSparsityPattern
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
FUNCTION SetMatrixToOne(row, column, val) RESULT(valid)
INTEGER, INTENT(INOUT), OPTIONAL :: row
INTEGER, INTENT(INOUT), OPTIONAL :: column
REAL(NTREAL), INTENT(INOUT), OPTIONAL :: val
LOGICAL :: valid

val = 1.0_NTREAL
valid = .TRUE.
END FUNCTION SetMatrixToOne
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
END MODULE
END MODULE
76 changes: 76 additions & 0 deletions Source/Fortran/MatrixReduceModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -41,10 +41,12 @@ MODULE MatrixReduceModule
PUBLIC :: ReduceAndComposeMatrixSizes
PUBLIC :: ReduceAndComposeMatrixData
PUBLIC :: ReduceAndComposeMatrixCleanup
PUBLIC :: ReduceAndComposeMatrix
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
PUBLIC :: ReduceAndSumMatrixSizes
PUBLIC :: ReduceAndSumMatrixData
PUBLIC :: ReduceAndSumMatrixCleanup
PUBLIC :: ReduceAndSumMatrix
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
PUBLIC :: TestReduceSizeRequest
PUBLIC :: TestReduceInnerRequest
Expand All @@ -62,6 +64,10 @@ MODULE MatrixReduceModule
MODULE PROCEDURE ReduceAndComposeMatrixCleanup_lsr
MODULE PROCEDURE ReduceAndComposeMatrixCleanup_lsc
END INTERFACE
INTERFACE ReduceAndComposeMatrix
MODULE PROCEDURE ReduceAndComposeMatrix_lsr
MODULE PROCEDURE ReduceAndComposeMatrix_lsc
END INTERFACE
INTERFACE ReduceAndSumMatrixSizes
MODULE PROCEDURE ReduceAndSumMatrixSizes_lsr
MODULE PROCEDURE ReduceAndSumMatrixSizes_lsc
Expand All @@ -74,6 +80,10 @@ MODULE MatrixReduceModule
MODULE PROCEDURE ReduceAndSumMatrixCleanup_lsr
MODULE PROCEDURE ReduceAndSumMatrixCleanup_lsc
END INTERFACE
INTERFACE ReduceAndSumMatrix
MODULE PROCEDURE ReduceAndSumMatrix_lsr
MODULE PROCEDURE ReduceAndSumMatrix_lsc
END INTERFACE
CONTAINS!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> The first routine to call, gathers the sizes of the data to be sent.
SUBROUTINE ReduceAndComposeMatrixSizes_lsr(matrix, communicator, &
Expand Down Expand Up @@ -249,6 +259,38 @@ PURE SUBROUTINE ReduceAndComposeMatrixCleanup_lsc(matrix, gathered_matrix, &
#endif

END SUBROUTINE ReduceAndComposeMatrixCleanup_lsc
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Reduce and sum the matrices in one step. If you use this method, you
!> lose the opportunity for overlapping communication.
SUBROUTINE ReduceAndComposeMatrix_lsr(matrix, gathered_matrix, comm)
!> The matrix to send.
TYPE(Matrix_lsr), INTENT(IN) :: matrix
!> The matrix we are gathering.
TYPE(Matrix_lsr), INTENT(INOUT) :: gathered_matrix
!> The communicator to send along.
INTEGER, INTENT(INOUT) :: comm
!! Local Variables
TYPE(ReduceHelper_t) :: helper

INCLUDE "comm_includes/ReduceAndComposeMatrix.f90"

END SUBROUTINE ReduceAndComposeMatrix_lsr
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Reduce and sum the matrices in one step. If you use this method, you
!> lose the opportunity for overlapping communication.
SUBROUTINE ReduceAndComposeMatrix_lsc(matrix, gathered_matrix, comm)
!> The matrix to send.
TYPE(Matrix_lsc), INTENT(IN) :: matrix
!> The matrix we are gathering.
TYPE(Matrix_lsc), INTENT(INOUT) :: gathered_matrix
!> The communicator to send along.
INTEGER, INTENT(INOUT) :: comm
!! Local Variables
TYPE(ReduceHelper_t) :: helper

INCLUDE "comm_includes/ReduceAndComposeMatrix.f90"

END SUBROUTINE ReduceAndComposeMatrix_lsc
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> The first routine to call, gathers the sizes of the data to be sent.
SUBROUTINE ReduceAndSumMatrixSizes_lsr(matrix, communicator, &
Expand Down Expand Up @@ -425,6 +467,40 @@ PURE SUBROUTINE ReduceAndSumMatrixCleanup_lsc(matrix, gathered_matrix, &
END IF
#endif
END SUBROUTINE ReduceAndSumMatrixCleanup_lsc
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Reduce and sum the matrices in one step. If you use this method, you
!> lose the opportunity for overlapping communication.
SUBROUTINE ReduceAndSumMatrix_lsr(matrix, gathered_matrix, threshold, comm)
!> The matrix to send.
TYPE(Matrix_lsr), INTENT(IN) :: matrix
!> The gathered_matrix the matrix being gathered.
TYPE(Matrix_lsr), INTENT(INOUT) :: gathered_matrix
!> The threshold the threshold for flushing values.
REAL(NTREAL), INTENT(IN) :: threshold
!> The communicator to send along.
INTEGER, INTENT(INOUT) :: comm
!! Local Data
TYPE(ReduceHelper_t) :: helper

INCLUDE "comm_includes/ReduceAndSumMatrix.f90"
END SUBROUTINE ReduceAndSumMatrix_lsr
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Reduce and sum the matrices in one step. If you use this method, you
!> lose the opportunity for overlapping communication.
SUBROUTINE ReduceAndSumMatrix_lsc(matrix, gathered_matrix, threshold, comm)
!> The matrix to send.
TYPE(Matrix_lsc), INTENT(IN) :: matrix
!> The threshold the threshold for flushing values.
TYPE(Matrix_lsc), INTENT(INOUT) :: gathered_matrix
!> The threshold the threshold for flushing values.
REAL(NTREAL), INTENT(IN) :: threshold
!> The communicator to send along.
INTEGER, INTENT(INOUT) :: comm
!! Local Data
TYPE(ReduceHelper_t) :: helper

INCLUDE "comm_includes/ReduceAndSumMatrix.f90"
END SUBROUTINE ReduceAndSumMatrix_lsc
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Test if a request for the size of the matrices is complete.
FUNCTION TestReduceSizeRequest(helper) RESULT(request_completed)
Expand Down
39 changes: 18 additions & 21 deletions Source/Fortran/PSMatrixModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,11 +9,8 @@ MODULE PSMatrixModule
& WriteListElement, WriteHeader
USE MatrixMarketModule, ONLY : ParseMMHeader, MM_COMPLEX, WriteMMSize, &
& WriteMMLine, MAX_LINE_LENGTH
USE MatrixReduceModule, ONLY : ReduceHelper_t, ReduceAndComposeMatrixSizes, &
& ReduceAndComposeMatrixData, ReduceAndComposeMatrixCleanup, &
& ReduceANdSumMatrixSizes, ReduceAndSumMatrixData, &
& ReduceAndSumMatrixCleanup, TestReduceSizeRequest, &
& TestReduceInnerRequest, TestReduceDataRequest
USE MatrixReduceModule, ONLY : ReduceHelper_t, ReduceAndComposeMatrix, &
& ReduceAndSumMatrix
USE PermutationModule, ONLY : Permutation_t, ConstructDefaultPermutation
USE ProcessGridModule, ONLY : ProcessGrid_t, global_grid, IsRoot, &
& SplitProcessGrid
Expand Down Expand Up @@ -773,23 +770,29 @@ END SUBROUTINE WriteMatrixToMatrixMarket_psc
!> This routine fills in a matrix based on local triplet lists. Each process
!> should pass in triplet lists with global coordinates. It does not matter
!> where each triplet is stored, as long as global coordinates are given.
SUBROUTINE FillMatrixFromTripletList_psr(this,triplet_list,preduplicated_in)
!> However, if you explicitly set prepartitioned_in to True, all data must be
!> on the correct process. In that case, there is no communication required.
SUBROUTINE FillMatrixFromTripletList_psr(this, triplet_list, &
& preduplicated_in, prepartitioned_in)
!> The matrix to fill.
TYPE(Matrix_ps) :: this
!> The triplet list of values.
TYPE(TripletList_r) :: triplet_list
!> If lists are preduplicated across slices set this to true.
LOGICAL, INTENT(IN), OPTIONAL :: preduplicated_in
!> If all lists only contain local matrix elements set this to true.
LOGICAL, INTENT(IN), OPTIONAL :: prepartitioned_in
!! Local Data
TYPE(Matrix_ps) :: temp_matrix
TYPE(TripletList_r) :: shifted
TYPE(TripletList_r) :: sorted_triplet_list
TYPE(Matrix_lsr) :: local_matrix
TYPE(Matrix_lsr) :: gathered_matrix
!! Local Data
TYPE(Permutation_t) :: basic_permutation
TYPE(ReduceHelper_t) :: gather_helper
REAL(NTREAL), PARAMETER :: threshold = 0.0_NTREAL
LOGICAL :: preduplicated
LOGICAL :: prepartitioned

IF (this%is_complex) THEN
CALL ConvertMatrixToReal(this, temp_matrix)
Expand All @@ -803,23 +806,29 @@ END SUBROUTINE FillMatrixFromTripletList_psr
!> This routine fills in a matrix based on local triplet lists. Each process
!> should pass in triplet lists with global coordinates. It does not matter
!> where each triplet is stored, as long as global coordinates are given.
SUBROUTINE FillMatrixFromTripletList_psc(this,triplet_list,preduplicated_in)
!> However, if you explicitly set prepartitioned_in to True, all data must be
!> on the correct process. In that case, there is no communication required.
SUBROUTINE FillMatrixFromTripletList_psc(this, triplet_list, &
& preduplicated_in, prepartitioned_in)
!> The matrix to fill.
TYPE(Matrix_ps) :: this
!> The triplet list of values.
TYPE(TripletList_c) :: triplet_list
!> If lists are preduplicated across slices set this to true.
LOGICAL, INTENT(IN), OPTIONAL :: preduplicated_in
!> If all lists only contain local matrix elements set this to true.
LOGICAL, INTENT(IN), OPTIONAL :: prepartitioned_in
!! Local Data
TYPE(TripletList_c) :: shifted
TYPE(TripletList_c) :: sorted_triplet_list
TYPE(Matrix_lsc) :: local_matrix
TYPE(Matrix_lsc) :: gathered_matrix
!! Local Data
TYPE(Matrix_ps) :: temp_matrix
TYPE(Permutation_t) :: basic_permutation
TYPE(ReduceHelper_t) :: gather_helper
REAL(NTREAL), PARAMETER :: threshold = 0.0_NTREAL
LOGICAL :: preduplicated
LOGICAL :: prepartitioned

IF (.NOT. this%is_complex) THEN
CALL ConvertMatrixToComplex(this, temp_matrix)
Expand Down Expand Up @@ -849,9 +858,6 @@ SUBROUTINE FillMatrixIdentity_psr(this)
TYPE(Matrix_ps), INTENT(INOUT) :: this
!! Local Data
TYPE(TripletList_r) :: triplet_list
TYPE(TripletList_r) :: unsorted_triplet_list
TYPE(TripletList_r) :: sorted_triplet_list
TYPE(Matrix_lsr) :: local_matrix

INCLUDE "distributed_includes/FillMatrixIdentity.f90"

Expand All @@ -863,9 +869,6 @@ SUBROUTINE FillMatrixIdentity_psc(this)
TYPE(Matrix_ps), INTENT(INOUT) :: this
!! Local Data
TYPE(TripletList_c) :: triplet_list
TYPE(TripletList_c) :: unsorted_triplet_list
TYPE(TripletList_c) :: sorted_triplet_list
TYPE(Matrix_lsc) :: local_matrix

INCLUDE "distributed_includes/FillMatrixIdentity.f90"

Expand Down Expand Up @@ -908,9 +911,6 @@ SUBROUTINE FillMatrixPermutation_psr(this, permutation_vector, rows)
LOGICAL, INTENT(IN) :: rows
!! Local Data
TYPE(TripletList_r) :: triplet_list
TYPE(TripletList_r) :: unsorted_triplet_list
TYPE(TripletList_r) :: sorted_triplet_list
TYPE(Matrix_lsr) :: local_matrix

INCLUDE "distributed_includes/FillMatrixPermutation.f90"

Expand All @@ -926,9 +926,6 @@ SUBROUTINE FillMatrixPermutation_psc(this, permutation_vector, rows)
LOGICAL, INTENT(IN) :: rows
!! Local Data
TYPE(TripletList_c) :: triplet_list
TYPE(TripletList_c) :: unsorted_triplet_list
TYPE(TripletList_c) :: sorted_triplet_list
TYPE(Matrix_lsc) :: local_matrix

INCLUDE "distributed_includes/FillMatrixPermutation.f90"

Expand Down
11 changes: 11 additions & 0 deletions Source/Fortran/comm_includes/ReduceAndComposeMatrix.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
CALL ReduceAndComposeMatrixSizes(matrix, comm, gathered_matrix, helper)
DO WHILE(.NOT. TestReduceSizeRequest(helper))
END DO

CALL ReduceAndComposeMatrixData(matrix, comm, gathered_matrix, helper)
DO WHILE(.NOT. TestReduceInnerRequest(helper))
END DO
DO WHILE(.NOT. TestReduceDataRequest(helper))
END DO

CALL ReduceAndComposeMatrixCleanup(matrix, gathered_matrix, helper)
11 changes: 11 additions & 0 deletions Source/Fortran/comm_includes/ReduceAndSumMatrix.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
CALL ReduceAndSumMatrixSizes(matrix, comm, gathered_matrix, helper)
DO WHILE(.NOT. TestReduceSizeRequest(helper))
END DO

CALL ReduceAndSumMatrixData(matrix, gathered_matrix, comm, helper)
DO WHILE(.NOT. TestReduceInnerRequest(helper))
END DO
DO WHILE(.NOT. TestReduceDataRequest(helper))
END DO

CALL ReduceAndSumMatrixCleanup(matrix, gathered_matrix, threshold, helper)
Loading

0 comments on commit 40b2433

Please sign in to comment.