Skip to content

Commit 3596f3f

Browse files
committed
add the _type suffix to all sparse types
1 parent 6ae038b commit 3596f3f

8 files changed

+89
-89
lines changed

doc/specs/stdlib_sparse.md

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@ enum, bind(C)
3939
enumerator :: sparse_upper !! Symmetric Sparse matrix with triangular supperior storage
4040
end enum
4141
```
42-
In the following, all sparse kinds will be presented in two main flavors: a data-less type `<matrix>_type` useful for topological graph operations. And real/complex valued types `<matrix>_<kind>` containing the `data` buffer for the matrix values. The following rectangular matrix will be used to showcase how each sparse matrix holds the data internally:
42+
In the following, all sparse kinds will be presented in two main flavors: a data-less type `<matrix>_type` useful for topological graph operations. And real/complex valued types `<matrix>_<kind>_type` containing the `data` buffer for the matrix values. The following rectangular matrix will be used to showcase how each sparse matrix holds the data internally:
4343

4444
$$ M = \begin{bmatrix}
4545
9 & 0 & 0 & 0 & -3 \\
@@ -57,7 +57,7 @@ Experimental
5757
The `COO`, triplet or `ijv` format defines all non-zero elements of the matrix by explicitly allocating the `i,j` index and the value of the matrix. While some implementations use separate `row` and `col` arrays for the index, here we use a 2D array in order to promote fast memory acces to `ij`.
5858

5959
```Fortran
60-
type(COO_sp) :: COO
60+
type(COO_sp_type) :: COO
6161
call COO%malloc(4,5,10)
6262
COO%data(:) = real([9,-3,4,7,8,-1,8,4,5,6])
6363
COO%index(1:2,1) = [1,1]
@@ -81,7 +81,7 @@ Experimental
8181
The Compressed Sparse Row or Yale format `CSR` stores the matrix structure by compressing the row indices with a counter pointer `rowptr` enabling to know the first and last non-zero column index `col` of the given row.
8282

8383
```Fortran
84-
type(CSR_sp) :: CSR
84+
type(CSR_sp_type) :: CSR
8585
call CSR%malloc(4,5,10)
8686
CSR%data(:) = real([9,-3,4,7,8,-1,8,4,5,6])
8787
CSR%col(:) = [1,5,1,2,2,3,4,1,3,4]
@@ -97,7 +97,7 @@ Experimental
9797
The Compressed Sparse Colum `CSC` is similar to the `CSR` format but values are accesed first by column, thus an index counter is given by `colptr` which enables to know the first and last non-zero row index of a given colum.
9898

9999
```Fortran
100-
type(CSC_sp) :: CSC
100+
type(CSC_sp_type) :: CSC
101101
call CSC%malloc(4,5,10)
102102
CSC%data(:) = real([9,4,4,7,8,-1,5,8,6,-3])
103103
CSC%row(:) = [1,2,4,2,3,3,4,3,4,1]
@@ -113,7 +113,7 @@ Experimental
113113
The `ELL` format stores data in a dense matrix of $nrows \times K$ in column major order. By imposing a constant number of elements per row $K$, this format will incur in additional zeros being stored, but it enables efficient vectorization as memory acces is carried out by constant sized strides.
114114

115115
```Fortran
116-
type(ELL_sp) :: ELL
116+
type(ELL_sp_type) :: ELL
117117
call ELL%malloc(num_rows=4,num_cols=5,num_nz_row=3)
118118
ELL%data(1,1:3) = real([9,-3,0])
119119
ELL%data(2,1:3) = real([4,7,0])

example/linalg/example_sparse_data_accessors.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,8 @@ program example_sparse_data_accessors
55

66
real(dp) :: mat(2,2)
77
real(dp), allocatable :: dense(:,:)
8-
type(CSR_dp) :: CSR
9-
type(COO_dp) :: COO
8+
type(CSR_dp_type) :: CSR
9+
type(COO_dp_type) :: COO
1010
integer :: i, j, locdof(2)
1111

1212
! Initial data

example/linalg/example_sparse_from_ijv.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,9 +5,9 @@ program example_sparse_from_ijv
55

66
integer :: row(10), col(10)
77
real(dp) :: data(10)
8-
type(COO_dp) :: COO
9-
type(CSR_dp) :: CSR
10-
type(ELL_dp) :: ELL
8+
type(COO_dp_type) :: COO
9+
type(CSR_dp_type) :: CSR
10+
type(ELL_dp_type) :: ELL
1111
integer :: i, j
1212

1313
! Initial data

example/linalg/example_sparse_spmv.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,8 +7,8 @@ program example_sparse_spmv
77
real(dp) :: A(m,n), x(n)
88
real(dp) :: y_dense(m), y_coo(m), y_csr(m)
99
real(dp) :: alpha, beta
10-
type(COO_dp) :: COO
11-
type(CSR_dp) :: CSR
10+
type(COO_dp_type) :: COO
11+
type(CSR_dp_type) :: CSR
1212

1313
call random_number(A)
1414
! Convert from dense to COO and CSR matrices

src/stdlib_sparse_conversion.fypp

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ contains
2323
#:for k1, t1, s1 in (KINDS_TYPES)
2424
module subroutine dense2coo_${s1}$(dense,COO)
2525
${t1}$, intent(in) :: dense(:,:)
26-
type(COO_${s1}$), intent(out) :: COO
26+
type(COO_${s1}$_type), intent(out) :: COO
2727
integer(ilp) :: num_rows, num_cols, nnz
2828
integer(ilp) :: i, j, idx
2929

@@ -50,7 +50,7 @@ contains
5050

5151
#:for k1, t1, s1 in (KINDS_TYPES)
5252
module subroutine coo2dense_${s1}$(COO,dense)
53-
type(COO_${s1}$), intent(in) :: COO
53+
type(COO_${s1}$_type), intent(in) :: COO
5454
${t1}$, allocatable, intent(out) :: dense(:,:)
5555
integer(ilp) :: idx
5656

@@ -64,8 +64,8 @@ contains
6464

6565
#:for k1, t1, s1 in (KINDS_TYPES)
6666
module subroutine coo2csr_${s1}$(COO,CSR)
67-
type(COO_${s1}$), intent(in) :: COO
68-
type(CSR_${s1}$), intent(out) :: CSR
67+
type(COO_${s1}$_type), intent(in) :: COO
68+
type(CSR_${s1}$_type), intent(out) :: CSR
6969
integer(ilp) :: i
7070

7171
CSR%nnz = COO%nnz; CSR%nrows = COO%nrows; CSR%ncols = COO%ncols
@@ -94,7 +94,7 @@ contains
9494

9595
#:for k1, t1, s1 in (KINDS_TYPES)
9696
module subroutine csr2dense_${s1}$(CSR,dense)
97-
type(CSR_${s1}$), intent(in) :: CSR
97+
type(CSR_${s1}$_type), intent(in) :: CSR
9898
${t1}$, allocatable, intent(out) :: dense(:,:)
9999
integer(ilp) :: i, j
100100

@@ -120,8 +120,8 @@ contains
120120

121121
#:for k1, t1, s1 in (KINDS_TYPES)
122122
module subroutine csr2coo_${s1}$(CSR,COO)
123-
type(CSR_${s1}$), intent(in) :: CSR
124-
type(COO_${s1}$), intent(out) :: COO
123+
type(CSR_${s1}$_type), intent(in) :: CSR
124+
type(COO_${s1}$_type), intent(out) :: COO
125125
integer(ilp) :: i, j
126126

127127
COO%nnz = CSR%nnz; COO%nrows = CSR%nrows; COO%ncols = CSR%ncols
@@ -146,8 +146,8 @@ contains
146146

147147
#:for k1, t1, s1 in (KINDS_TYPES)
148148
module subroutine csr2ell_${s1}$(CSR,ELL,num_nz_rows)
149-
type(CSR_${s1}$), intent(in) :: CSR
150-
type(ELL_${s1}$), intent(out) :: ELL
149+
type(CSR_${s1}$_type), intent(in) :: CSR
150+
type(ELL_${s1}$_type), intent(out) :: ELL
151151
integer, intent(in), optional :: num_nz_rows !! number of non zeros per row
152152

153153
integer(ilp) :: i, j, num_nz_rows_, adr1, adr2
@@ -178,8 +178,8 @@ contains
178178
module subroutine csr2sellc_${s1}$(CSR,SELLC,chunk)
179179
!! csr2sellc: This function enables transfering data from a CSR matrix to a SELL-C matrix
180180
!! This algorithm was gracefully provided by Ivan Privec and adapted by Jose Alves
181-
type(CSR_${s1}$), intent(in) :: CSR
182-
type(SELLC_${s1}$), intent(out) :: SELLC
181+
type(CSR_${s1}$_type), intent(in) :: CSR
182+
type(SELLC_${s1}$_type), intent(out) :: SELLC
183183
integer, intent(in), optional :: chunk
184184
${t1}$, parameter :: zero = zero_${s1}$
185185
integer(ilp) :: i, j, num_chunks
@@ -402,7 +402,7 @@ contains
402402
type is( COO_type )
403403
call sort_coo(COO%index, COO%nnz, COO%nrows, COO%ncols)
404404
#:for k1, t1, s1 in (KINDS_TYPES)
405-
type is( COO_${s1}$ )
405+
type is( COO_${s1}$_type )
406406
block
407407
${t1}$, allocatable :: temp(:)
408408
if( sort_data_ ) then

0 commit comments

Comments
 (0)