Skip to content

Commit 6e679f5

Browse files
committed
change storage identifier names
1 parent 14e9be0 commit 6e679f5

File tree

5 files changed

+26
-26
lines changed

5 files changed

+26
-26
lines changed

doc/specs/stdlib_sparse.md

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -35,9 +35,9 @@ The symmetry integer laber should be assigned from the module's internal enumera
3535

3636
```Fortran
3737
enum, bind(C)
38-
enumerator :: k_NOSYMMETRY !> Full Sparse matrix (no symmetry considerations)
39-
enumerator :: k_SYMTRIINF !> Symmetric Sparse matrix with triangular inferior storage
40-
enumerator :: k_SYMTRISUP !> Symmetric Sparse matrix with triangular supperior storage
38+
enumerator :: sparse_full !> Full Sparse matrix (no symmetry considerations)
39+
enumerator :: sparse_lower !> Symmetric Sparse matrix with triangular inferior storage
40+
enumerator :: sparse_upper !> Symmetric Sparse matrix with triangular supperior storage
4141
end enum
4242
```
4343
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.

src/stdlib_sparse_conversion.fypp

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -115,7 +115,7 @@ contains
115115
integer :: i
116116

117117
CSR%nnz = COO%nnz; CSR%nrows = COO%nrows; CSR%ncols = COO%ncols
118-
CSR%base = COO%base; CSR%sym = COO%sym
118+
CSR%base = COO%base; CSR%storage = COO%storage
119119

120120
if( allocated(CSR%col) ) then
121121
CSR%col(1:COO%nnz) = COO%index(2,1:COO%nnz)
@@ -145,7 +145,7 @@ contains
145145
integer :: i, j
146146

147147
COO%nnz = CSR%nnz; COO%nrows = CSR%nrows; COO%ncols = CSR%ncols
148-
COO%base = CSR%base; COO%sym = CSR%sym
148+
COO%base = CSR%base; COO%storage = CSR%storage
149149

150150
if( .not.allocated(COO%data) ) then
151151
allocate( COO%data(CSR%nnz) , source = CSR%data(1:CSR%nnz) )
@@ -177,7 +177,7 @@ contains
177177
if(present(chunk)) SELLC%chunk_size = chunk
178178

179179
SELLC%nrows = CSR%nrows; SELLC%ncols = CSR%ncols
180-
SELLC%base = CSR%base; SELLC%sym = CSR%sym
180+
SELLC%base = CSR%base; SELLC%storage = CSR%storage
181181
associate( nrows=>SELLC%nrows, ncols=>SELLC%ncols, nnz=>SELLC%nnz, &
182182
& chunk_size=>SELLC%chunk_size )
183183
!-------------------------------------------

src/stdlib_sparse_kinds.fypp

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,11 @@ module stdlib_sparse_kinds
1313

1414
! -- Global parameters
1515
enum, bind(C)
16-
enumerator :: k_NOSYMMETRY !> Full Sparse matrix (no symmetry considerations)
17-
enumerator :: k_SYMTRIINF !> Symmetric Sparse matrix with triangular inferior storage
18-
enumerator :: k_SYMTRISUP !> Symmetric Sparse matrix with triangular supperior storage
16+
enumerator :: sparse_full !> Full Sparse matrix (no symmetry considerations)
17+
enumerator :: sparse_lower !> Symmetric Sparse matrix with triangular inferior storage
18+
enumerator :: sparse_upper !> Symmetric Sparse matrix with triangular supperior storage
1919
end enum
20-
public :: k_NOSYMMETRY, k_SYMTRIINF, k_SYMTRISUP
20+
public :: sparse_full, sparse_lower, sparse_upper
2121

2222
#:for k1, t1, s1 in (R_KINDS_TYPES)
2323
${t1}$, parameter, public :: zero_${s1}$ = 0._${k1}$
@@ -35,7 +35,7 @@ module stdlib_sparse_kinds
3535
integer :: nrows = 0 !> number of rows
3636
integer :: ncols = 0 !> number of columns
3737
integer :: nnz = 0 !> number of non-zero values
38-
integer :: sym = k_NOSYMMETRY !> assumed storage symmetry
38+
integer :: storage = sparse_full !> assumed storage symmetry
3939
integer :: base = 1 !> index base = 0 for (C) or 1 (Fortran)
4040
end type
4141

src/stdlib_sparse_spmv.fypp

Lines changed: 14 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -54,8 +54,8 @@ contains
5454
else
5555
vec_y = zero_${s1}$
5656
endif
57-
associate( data => matrix%data, index => matrix%index, sym => matrix%sym, nnz => matrix%nnz )
58-
if( sym == k_NOSYMMETRY) then
57+
associate( data => matrix%data, index => matrix%index, storage => matrix%storage, nnz => matrix%nnz )
58+
if( storage == sparse_full) then
5959
do concurrent (k = 1:nnz)
6060
ik = index(1,k)
6161
jk = index(2,k)
@@ -101,8 +101,8 @@ contains
101101
if(present(beta)) beta_ = beta
102102

103103
associate( data => matrix%data, col => matrix%col, rowptr => matrix%rowptr, &
104-
& nnz => matrix%nnz, nrows => matrix%nrows, ncols => matrix%ncols, sym => matrix%sym )
105-
if( sym == k_NOSYMMETRY) then
104+
& nnz => matrix%nnz, nrows => matrix%nrows, ncols => matrix%ncols, storage => matrix%storage )
105+
if( storage == sparse_full) then
106106
do i = 1, nrows
107107
aux = zero_${k1}$
108108
do j = rowptr(i), rowptr(i+1)-1
@@ -115,7 +115,7 @@ contains
115115
end if
116116
end do
117117

118-
else if( sym == k_SYMTRIINF )then
118+
else if( storage == sparse_lower )then
119119
do i = 1 , nrows
120120
aux = zero_${s1}$
121121
aux2 = alpha_ * vec_x(${rksfx2(rank-1)}$i)
@@ -132,7 +132,7 @@ contains
132132
end if
133133
end do
134134

135-
else if( sym == k_SYMTRISUP )then
135+
else if( storage == sparse_upper )then
136136
do i = 1 , nrows
137137
aux = vec_x(${rksfx2(rank-1)}$i) * data(rowptr(i))
138138
aux2 = alpha_ * vec_x(${rksfx2(rank-1)}$i)
@@ -184,15 +184,15 @@ contains
184184
endif
185185

186186
associate( data => matrix%data, colptr => matrix%colptr, row => matrix%row, &
187-
& nnz => matrix%nnz, nrows => matrix%nrows, ncols => matrix%ncols, sym => matrix%sym )
188-
if( sym == k_NOSYMMETRY) then
187+
& nnz => matrix%nnz, nrows => matrix%nrows, ncols => matrix%ncols, storage => matrix%storage )
188+
if( storage == sparse_full) then
189189
do concurrent(j=1:ncols)
190190
do i = colptr(j), colptr(j+1)-1
191191
vec_y(${rksfx2(rank-1)}$row(i)) = vec_y(${rksfx2(rank-1)}$row(i)) + alpha_ * data(i) * vec_x(${rksfx2(rank-1)}$j)
192192
end do
193193
end do
194194

195-
else if( sym == k_SYMTRIINF )then
195+
else if( storage == sparse_lower )then
196196
! NOT TESTED
197197
do j = 1 , ncols
198198
aux = vec_x(${rksfx2(rank-1)}$j) * data(colptr(j))
@@ -203,7 +203,7 @@ contains
203203
vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_ * aux
204204
end do
205205

206-
else if( sym == k_SYMTRISUP )then
206+
else if( storage == sparse_upper )then
207207
! NOT TESTED
208208
do j = 1 , ncols
209209
aux = zero_${s1}$
@@ -242,8 +242,8 @@ contains
242242
vec_y = zero_${s1}$
243243
endif
244244
associate( data => matrix%data, index => matrix%index, MNZ_P_ROW => matrix%K, &
245-
& nnz => matrix%nnz, nrows => matrix%nrows, ncols => matrix%ncols, sym => matrix%sym )
246-
if( sym == k_NOSYMMETRY) then
245+
& nnz => matrix%nnz, nrows => matrix%nrows, ncols => matrix%ncols, storage => matrix%storage )
246+
if( storage == sparse_full) then
247247
do concurrent (i = 1:nrows, k = 1:MNZ_P_ROW)
248248
j = index(i,k)
249249
if(j>0) vec_y(${rksfx2(rank-1)}$i) = vec_y(${rksfx2(rank-1)}$i) + alpha_*data(i,k) * vec_x(${rksfx2(rank-1)}$j)
@@ -277,10 +277,10 @@ contains
277277
vec_y = zero_${s1}$
278278
endif
279279
associate( data => matrix%data, ia => matrix%rowptr , ja => matrix%col, cs => matrix%chunk_size, &
280-
& nnz => matrix%nnz, nrows => matrix%nrows, ncols => matrix%ncols, sym => matrix%sym )
280+
& nnz => matrix%nnz, nrows => matrix%nrows, ncols => matrix%ncols, storage => matrix%storage )
281281
num_chunks = nrows / cs
282282
rm = nrows - num_chunks * cs
283-
if( sym == k_NOSYMMETRY) then
283+
if( storage == sparse_full) then
284284

285285
select case(cs)
286286
#:for chunk in CHUNKS

test/linalg/test_sparse_spmv.fypp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -204,7 +204,7 @@ contains
204204
0,0,2,1],kind=wp),[4,4]) )
205205

206206
call dense2coo( dense , COO )
207-
COO%sym = k_SYMTRISUP
207+
COO%storage = sparse_upper
208208
call coo2csr(COO, CSR)
209209

210210
dense(2,1) = 2._wp; dense(3,2) = 2._wp; dense(4,3) = 2._wp

0 commit comments

Comments
 (0)