Skip to content

Commit

Permalink
Remove unnecessary use of c types (#158)
Browse files Browse the repository at this point in the history
  • Loading branch information
william-dawson authored Oct 14, 2020
1 parent eee5d7e commit d7d0193
Show file tree
Hide file tree
Showing 7 changed files with 40 additions and 46 deletions.
17 changes: 8 additions & 9 deletions Source/Fortran/MatrixMemoryPoolModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@
MODULE MatrixMemoryPoolModule
USE DataTypesModule, ONLY: NTREAL, NTCOMPLEX
USE TripletModule, ONLY : Triplet_r, Triplet_c
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int
IMPLICIT NONE
PRIVATE
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Expand Down Expand Up @@ -86,9 +85,9 @@ SUBROUTINE ConstructMatrixMemoryPoolSub_lr(this, columns, rows, sparsity_in)
!> The matrix to construct.
TYPE(MatrixMemoryPool_lr), TARGET :: this
!> Number of columns in the matrix.
INTEGER(kind=c_int), INTENT(IN) :: columns
INTEGER, INTENT(IN) :: columns
!> Number of rows in the matrix.
INTEGER(kind=c_int), INTENT(IN) :: rows
INTEGER, INTENT(IN) :: rows
!> Estimated sparsity (optional).
REAL(NTREAL), INTENT(IN), OPTIONAL :: sparsity_in

Expand All @@ -104,9 +103,9 @@ SUBROUTINE ConstructMatrixMemoryPoolSub_lc(this, columns, rows, sparsity_in)
!> The matrix to construct.
TYPE(MatrixMemoryPool_lc), TARGET :: this
!> Number of columns in the matrix.
INTEGER(kind=c_int), INTENT(IN) :: columns
INTEGER, INTENT(IN) :: columns
!> Number of rows in the matrix.
INTEGER(kind=c_int), INTENT(IN) :: rows
INTEGER, INTENT(IN) :: rows
!> Estimated sparsity (optional).
REAL(NTREAL), INTENT(IN), OPTIONAL :: sparsity_in

Expand All @@ -122,9 +121,9 @@ FUNCTION ConstructMatrixMemoryPool_lr(columns, rows, sparsity_in) RESULT(this)
!> The matrix to construct.
TYPE(MatrixMemoryPool_lr), TARGET :: this
!> Number of columns in the matrix.
INTEGER(kind=c_int), INTENT(IN) :: columns
INTEGER, INTENT(IN) :: columns
!> Number of rows in the matrix.
INTEGER(kind=c_int), INTENT(IN) :: rows
INTEGER, INTENT(IN) :: rows
!> Estimated sparsity (optional).
REAL(NTREAL), INTENT(IN), OPTIONAL :: sparsity_in

Expand All @@ -137,9 +136,9 @@ FUNCTION ConstructMatrixMemoryPool_lc(columns, rows, sparsity_in) RESULT(this)
!> The matrix to construct.
TYPE(MatrixMemoryPool_lc), TARGET :: this
!> Number of columns in the matrix.
INTEGER(kind=c_int), INTENT(IN) :: columns
INTEGER, INTENT(IN) :: columns
!> Number of rows in the matrix.
INTEGER(kind=c_int), INTENT(IN) :: rows
INTEGER, INTENT(IN) :: rows
!> Estimated sparsity (optional).
REAL(NTREAL), INTENT(IN), OPTIONAL :: sparsity_in

Expand Down
1 change: 0 additions & 1 deletion Source/Fortran/PSMatrixAlgebraModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ MODULE PSMatrixAlgebraModule
USE TimerModule, ONLY : StartTimer, StopTimer
USE TripletListModule, ONLY : TripletList_r, TripletList_c
USE NTMPIModule
USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
PRIVATE
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Expand Down
1 change: 0 additions & 1 deletion Source/Fortran/PSMatrixModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,6 @@ MODULE PSMatrixModule
& SymmetrizeTripletList, GetTripletAt, RedistributeTripletLists, &
& ShiftTripletList
USE NTMPIModule
USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
PRIVATE
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Expand Down
31 changes: 15 additions & 16 deletions Source/Fortran/ProcessGridModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@ MODULE ProcessGridModule
USE LoggingModule, ONLY : ActivateLogger, EnterSubLog, ExitSubLog, &
& WriteHeader, WriteListElement
USE NTMPIModule
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int, c_bool
#ifdef _OPENMP
USE omp_lib, ONLY : omp_get_num_threads
#endif
Expand Down Expand Up @@ -81,15 +80,15 @@ MODULE ProcessGridModule
SUBROUTINE ConstructProcessGrid_full(world_comm_, process_rows_, &
& process_columns_, process_slices_, be_verbose_in)
!> A communicator that every process in the grid is a part of.
INTEGER(kind=c_int), INTENT(IN) :: world_comm_
INTEGER, INTENT(IN) :: world_comm_
!> The number of grid rows.
INTEGER(kind=c_int), INTENT(IN) :: process_rows_
INTEGER, INTENT(IN) :: process_rows_
!> The number of grid columns.
INTEGER(kind=c_int), INTENT(IN) :: process_columns_
INTEGER, INTENT(IN) :: process_columns_
!> The number of grid slices.
INTEGER(kind=c_int), INTENT(IN) :: process_slices_
INTEGER, INTENT(IN) :: process_slices_
!> Set true to print process grid info.
LOGICAL(kind=c_bool), INTENT(IN), OPTIONAL :: be_verbose_in
LOGICAL, INTENT(IN), OPTIONAL :: be_verbose_in
!! Local Data
LOGICAL :: be_verbose

Expand Down Expand Up @@ -129,13 +128,13 @@ END SUBROUTINE ConstructProcessGrid_full
SUBROUTINE ConstructProcessGrid_onlyslice(world_comm_, process_slices_in, &
& be_verbose_in)
!> A communicator that every process in the grid is a part of.
INTEGER(kind=c_int), INTENT(IN) :: world_comm_
INTEGER, INTENT(IN) :: world_comm_
!> The number of grid slices.
INTEGER(kind=c_int), INTENT(IN), OPTIONAL :: process_slices_in
INTEGER, INTENT(IN), OPTIONAL :: process_slices_in
!> Set true to print process grid info.
LOGICAL(kind=c_bool), INTENT(IN), OPTIONAL :: be_verbose_in
LOGICAL, INTENT(IN), OPTIONAL :: be_verbose_in
!! Local Data
LOGICAL(kind=c_bool) :: be_verbose
LOGICAL :: be_verbose
INTEGER :: process_rows, process_columns, process_slices
INTEGER :: total_processors
INTEGER :: ierr
Expand Down Expand Up @@ -170,13 +169,13 @@ SUBROUTINE ConstructNewProcessGrid_full(grid, world_comm_, process_rows_, &
!> The grid to construct
TYPE(ProcessGrid_t), INTENT(INOUT) :: grid
!> A communicator that every process in the grid is a part of.
INTEGER(kind=c_int), INTENT(IN) :: world_comm_
INTEGER, INTENT(IN) :: world_comm_
!> The number of grid rows.
INTEGER(kind=c_int), INTENT(IN) :: process_rows_
INTEGER, INTENT(IN) :: process_rows_
!> The number of grid columns.
INTEGER(kind=c_int), INTENT(IN) :: process_columns_
INTEGER, INTENT(IN) :: process_columns_
!> The number of grid slices.
INTEGER(kind=c_int), INTENT(IN) :: process_slices_
INTEGER, INTENT(IN) :: process_slices_
!! Local Data
INTEGER :: column_block_multiplier
INTEGER :: row_block_multiplier
Expand Down Expand Up @@ -303,9 +302,9 @@ SUBROUTINE ConstructNewProcessGrid_onlyslice(grid, world_comm_, &
!> The grid to construct
TYPE(ProcessGrid_t), INTENT(INOUT) :: grid
!> A communicator that every process in the grid is a part of.
INTEGER(kind=c_int), INTENT(IN) :: world_comm_
INTEGER, INTENT(IN) :: world_comm_
!> The number of grid slices.
INTEGER(kind=c_int), INTENT(IN), OPTIONAL :: process_slices_in
INTEGER, INTENT(IN), OPTIONAL :: process_slices_in
!! Local Data
INTEGER :: process_rows, process_columns, process_slices
INTEGER :: total_processors
Expand Down
21 changes: 10 additions & 11 deletions Source/Fortran/TripletListModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ MODULE TripletListModule
& ConvertTripletType
USE MatrixMarketModule, ONLY : MM_SYMMETRIC, MM_SKEW_SYMMETRIC, MM_HERMITIAN
USE NTMPIModule
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int
IMPLICIT NONE
PRIVATE
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Expand Down Expand Up @@ -106,7 +105,7 @@ PURE SUBROUTINE ConstructTripletListSup_r(this, size_in)
!> The triplet list to construct.
TYPE(TripletList_r), INTENT(INOUT) :: this
!> The length of the triplet list (default=0).
INTEGER(kind=c_int), INTENT(IN), OPTIONAL :: size_in
INTEGER, INTENT(IN), OPTIONAL :: size_in

IF (PRESENT(size_in)) THEN
this = ConstructTripletList_r(size_in)
Expand All @@ -120,7 +119,7 @@ PURE SUBROUTINE ConstructTripletListSup_c(this, size_in)
!> The triplet list to construct.
TYPE(TripletList_c), INTENT(INOUT) :: this
!> The length of the triplet list (default=0).
INTEGER(kind=c_int), INTENT(IN), OPTIONAL :: size_in
INTEGER, INTENT(IN), OPTIONAL :: size_in

IF (PRESENT(size_in)) THEN
this = ConstructTripletList_c(size_in)
Expand All @@ -134,7 +133,7 @@ PURE FUNCTION ConstructTripletList_r(size_in) RESULT(this)
!> The triplet list to construct.
TYPE(TripletList_r) :: this
!> The length of the triplet list (default=0).
INTEGER(kind=c_int), INTENT(IN), OPTIONAL :: size_in
INTEGER, INTENT(IN), OPTIONAL :: size_in

INCLUDE "triplet_includes/ConstructTripletList.f90"

Expand All @@ -145,7 +144,7 @@ PURE FUNCTION ConstructTripletList_c(size_in) RESULT(this)
!> The triplet list to construct.
TYPE(TripletList_c) :: this
!> The length of the triplet list (default=0).
INTEGER(kind=c_int), INTENT(IN), OPTIONAL :: size_in
INTEGER, INTENT(IN), OPTIONAL :: size_in

INCLUDE "triplet_includes/ConstructTripletList.f90"

Expand Down Expand Up @@ -174,7 +173,7 @@ PURE SUBROUTINE ResizeTripletList_r(this, size)
!> The triplet list to resize.
TYPE(TripletList_r), INTENT(INOUT) :: this
!> Size to resize to.
INTEGER(KIND=c_int), INTENT(IN) :: size
INTEGER, INTENT(IN) :: size
!! Local Data
TYPE(Triplet_r), DIMENSION(:), ALLOCATABLE :: temporary_data

Expand All @@ -187,7 +186,7 @@ PURE SUBROUTINE ResizeTripletList_c(this, size)
!> The triplet list to resize.
TYPE(TripletList_c), INTENT(INOUT) :: this
!> Size to resize to.
INTEGER(KIND=c_int), INTENT(IN) :: size
INTEGER, INTENT(IN) :: size
!! Local Data
TYPE(Triplet_c), DIMENSION(:), ALLOCATABLE :: temporary_data

Expand Down Expand Up @@ -222,7 +221,7 @@ PURE SUBROUTINE SetTripletAt_r(this,index,triplet_value)
!> The triplet list to set.
TYPE(TripletList_r), INTENT(INOUT) :: this
!> The index at which to set the triplet.
INTEGER(KIND=c_int), INTENT(IN) :: index
INTEGER, INTENT(IN) :: index
!> The value of the triplet to set.
TYPE(Triplet_r), INTENT(IN) :: triplet_value

Expand All @@ -234,7 +233,7 @@ PURE SUBROUTINE SetTripletAt_c(this,index,triplet_value)
!> The triplet list to set.
TYPE(TripletList_c), INTENT(INOUT) :: this
!> The index at which to set the triplet.
INTEGER(KIND=c_int), INTENT(IN) :: index
INTEGER, INTENT(IN) :: index
!> The value of the triplet to set.
TYPE(Triplet_c), INTENT(IN) :: triplet_value

Expand All @@ -246,7 +245,7 @@ PURE SUBROUTINE GetTripletAt_r(this,index,triplet_value)
!> The triplet list to get the value from.
TYPE(TripletList_r), INTENT(IN) :: this
!> The index from which to get the triplet.
INTEGER(kind=c_int), INTENT(IN) :: index
INTEGER, INTENT(IN) :: index
!> The extracted triplet value.
TYPE(Triplet_r), INTENT(OUT) :: triplet_value

Expand All @@ -258,7 +257,7 @@ PURE SUBROUTINE GetTripletAt_c(this,index,triplet_value)
!> The triplet list to get the value from.
TYPE(TripletList_c), INTENT(IN) :: this
!> The index from which to get the triplet.
INTEGER(kind=c_int), INTENT(IN) :: index
INTEGER, INTENT(IN) :: index
!> The extracted triplet value.
TYPE(Triplet_c), INTENT(OUT) :: triplet_value

Expand Down
9 changes: 4 additions & 5 deletions Source/Fortran/TripletModule.F90
Original file line number Diff line number Diff line change
Expand Up @@ -4,25 +4,24 @@ MODULE TripletModule
USE DataTypesModule, ONLY: NTREAL, MPINTREAL, NTCOMPLEX, MPINTCOMPLEX, &
& MPINTINTEGER
USE NTMPIModule
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int
IMPLICIT NONE
PRIVATE
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> A data type for a triplet of integer, integer, double.
!> As this is related to matrix multiplication, the referencing indices are
!> rows and columns.
TYPE, PUBLIC :: Triplet_r
INTEGER(kind=c_int) :: index_column !< column value.
INTEGER(kind=c_int) :: index_row !< row value.
INTEGER :: index_column !< column value.
INTEGER :: index_row !< row value.
REAL(NTREAL) :: point_value !< actual value at those indices.
END TYPE Triplet_r
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> A data type for a triplet of integer, integer, complex.
!> As this is related to matrix multiplication, the referencing indices are
!> rows and columns.
TYPE, PUBLIC :: Triplet_c
INTEGER(kind=c_int) :: index_column !< column value.
INTEGER(kind=c_int) :: index_row !< row value.
INTEGER :: index_column !< column value.
INTEGER :: index_row !< row value.
COMPLEX(NTCOMPLEX) :: point_value !< actual value at those indices.
END TYPE Triplet_c
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Expand Down
6 changes: 3 additions & 3 deletions Source/Wrapper/ProcessGridModule_wrp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ SUBROUTINE ConstructGlobalProcessGrid_wrp(world_comm_, process_rows_, &
INTEGER(kind=c_int), INTENT(IN) :: process_slices_
LOGICAL(kind=c_bool), INTENT(IN) :: be_verbose
CALL ConstructProcessGrid(world_comm_, process_rows_, process_columns_, &
& process_slices_, be_verbose)
& process_slices_, LOGICAL(be_verbose))
END SUBROUTINE ConstructGlobalProcessGrid_wrp
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Wrap the process grid construction routine.
Expand All @@ -58,15 +58,15 @@ SUBROUTINE ConstructGlobalProcessGrid_onlyslice_wrp(world_comm_, &
INTEGER(kind=c_int), INTENT(IN) :: process_slices_
LOGICAL(kind=c_bool), INTENT(IN) :: be_verbose
CALL ConstructProcessGrid(world_comm_, process_slices_in=process_slices_, &
& be_verbose_in=be_verbose)
& be_verbose_in=LOGICAL(be_verbose))
END SUBROUTINE ConstructGlobalProcessGrid_onlyslice_wrp
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Wrap the process grid construction routine.
SUBROUTINE ConstructGlobalProcessGrid_default_wrp(world_comm_, be_verbose) &
& BIND(c,name="ConstructGlobalProcessGrid_default_wrp")
INTEGER(kind=c_int), INTENT(IN) :: world_comm_
LOGICAL(kind=c_bool), INTENT(IN) :: be_verbose
CALL ConstructProcessGrid(world_comm_, be_verbose_in=be_verbose)
CALL ConstructProcessGrid(world_comm_, be_verbose_in=LOGICAL(be_verbose))
END SUBROUTINE ConstructGlobalProcessGrid_default_wrp
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!> Get the slice of the current process.
Expand Down

0 comments on commit d7d0193

Please sign in to comment.