Skip to content

Commit

Permalink
Remove the offending pattern
Browse files Browse the repository at this point in the history
  • Loading branch information
william-dawson committed Apr 7, 2023
1 parent de6067f commit 835d7b5
Show file tree
Hide file tree
Showing 5 changed files with 16 additions and 31 deletions.
14 changes: 4 additions & 10 deletions Source/Fortran/MatrixMemoryPoolModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -91,11 +91,8 @@ SUBROUTINE ConstructMatrixMemoryPoolSub_lr(this, columns, rows, sparsity_in)
!> Estimated sparsity (optional).
REAL(NTREAL), INTENT(IN), OPTIONAL :: sparsity_in

IF (PRESENT(sparsity_in)) THEN
this = MatrixMemoryPool_lr(columns, rows, sparsity_in)
ELSE
this = MatrixMemoryPool_lr(columns, rows)
END IF
#include "dense_includes/ConstructMatrixMemoryPool.f90"

END SUBROUTINE ConstructMatrixMemoryPoolSub_lr
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Subroutine wrapper for the constructor.
Expand All @@ -109,11 +106,8 @@ SUBROUTINE ConstructMatrixMemoryPoolSub_lc(this, columns, rows, sparsity_in)
!> Estimated sparsity (optional).
REAL(NTREAL), INTENT(IN), OPTIONAL :: sparsity_in

IF (PRESENT(sparsity_in)) THEN
this = MatrixMemoryPool_lc(columns, rows, sparsity_in)
ELSE
this = MatrixMemoryPool_lc(columns, rows)
END IF
#include "dense_includes/ConstructMatrixMemoryPool.f90"

END SUBROUTINE ConstructMatrixMemoryPoolSub_lc
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Construct Matrix Memory Pool object.
Expand Down
14 changes: 4 additions & 10 deletions Source/Fortran/SMatrixModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -145,11 +145,8 @@ PURE SUBROUTINE ConstructEmptyMatrixSub_lsr(this, rows, columns, zero_in)
!> Whether to set the matrix to zero.
LOGICAL, INTENT(IN), OPTIONAL :: zero_in

IF (PRESENT(zero_in)) THEN
this = ConstructEmptyMatrix_lsr(rows, columns, zero_in)
ELSE
this = ConstructEmptyMatrix_lsr(rows, columns)
ENDIF
CALL DestructMatrix(this)
#include "sparse_includes/ConstructEmptyMatrix.f90"

END SUBROUTINE ConstructEmptyMatrixSub_lsr
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Expand All @@ -164,11 +161,8 @@ PURE SUBROUTINE ConstructEmptyMatrixSub_lsc(this, rows, columns, zero_in)
!> Whether to set the matrix to zero.
LOGICAL, INTENT(IN), OPTIONAL :: zero_in

IF (PRESENT(zero_in)) THEN
this = ConstructEmptyMatrix_lsc(rows, columns, zero_in)
ELSE
this = ConstructEmptyMatrix_lsc(rows, columns)
ENDIF
CALL DestructMatrix(this)
#include "sparse_includes/ConstructEmptyMatrix.f90"

END SUBROUTINE ConstructEmptyMatrixSub_lsc
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Expand Down
14 changes: 4 additions & 10 deletions Source/Fortran/TripletListModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -107,11 +107,8 @@ PURE SUBROUTINE ConstructTripletListSup_r(this, size_in)
!> The length of the triplet list (default=0).
INTEGER, INTENT(IN), OPTIONAL :: size_in

IF (PRESENT(size_in)) THEN
this = ConstructTripletList_r(size_in)
ELSE
this = ConstructTripletList_r()
END IF
#include "triplet_includes/ConstructTripletList.f90"

END SUBROUTINE ConstructTripletListSup_r
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Subroutine wrapper for constructing a triplet list.
Expand All @@ -121,11 +118,8 @@ PURE SUBROUTINE ConstructTripletListSup_c(this, size_in)
!> The length of the triplet list (default=0).
INTEGER, INTENT(IN), OPTIONAL :: size_in

IF (PRESENT(size_in)) THEN
this = ConstructTripletList_c(size_in)
ELSE
this = ConstructTripletList_c()
END IF
#include "triplet_includes/ConstructTripletList.f90"

END SUBROUTINE ConstructTripletListSup_c
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Construct a triplet list.
Expand Down
2 changes: 2 additions & 0 deletions Source/Fortran/dense_includes/ConstructMatrixMemoryPool.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@
INTEGER :: alloc_stat
INTEGER :: num_buckets

CALL DestructMatrixMemoryPool(this)

this%columns = columns
this%rows = rows

Expand Down
3 changes: 2 additions & 1 deletion Source/Fortran/triplet_includes/ConstructTripletList.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@
size = 0
END IF

IF (ALLOCATED(this%DATA)) DEALLOCATE(this%DATA)
CALL DestructTripletList(this)

this%CurrentSize = size

ALLOCATE(this%DATA(size))

0 comments on commit 835d7b5

Please sign in to comment.