Skip to content

Commit dde88a7

Browse files
committed
refactor spmv as submodule to keep parameters private, rework specs
1 parent 9879a9c commit dde88a7

File tree

5 files changed

+248
-178
lines changed

5 files changed

+248
-178
lines changed

doc/specs/stdlib_sparse.md

Lines changed: 55 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -24,19 +24,19 @@ The parent `sparse_type` is as an abstract derived type holding the basic common
2424
```Fortran
2525
type, public, abstract :: sparse_type
2626
integer :: nrows !! number of rows
27-
integer :: ncols !> number of columns
28-
integer :: nnz !> number of non-zero values
29-
integer :: storage !> assumed storage symmetry
27+
integer :: ncols !! number of columns
28+
integer :: nnz !! number of non-zero values
29+
integer :: storage !! assumed storage symmetry
3030
end type
3131
```
3232

3333
The storage integer label should be assigned from the module's internal enumerator containing the following three enums:
3434

3535
```Fortran
3636
enum, bind(C)
37-
enumerator :: sparse_full !> Full Sparse matrix (no symmetry considerations)
38-
enumerator :: sparse_lower !> Symmetric Sparse matrix with triangular inferior storage
39-
enumerator :: sparse_upper !> Symmetric Sparse matrix with triangular supperior storage
37+
enumerator :: sparse_full !! Full Sparse matrix (no symmetry considerations)
38+
enumerator :: sparse_lower !! Symmetric Sparse matrix with triangular inferior storage
39+
enumerator :: sparse_upper !! Symmetric Sparse matrix with triangular supperior storage
4040
end enum
4141
```
4242
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:
@@ -135,14 +135,14 @@ Experimental
135135
The Sliced ELLPACK format `SELLC` is a variation of the `ELLPACK` format. This modification reduces the storage size compared to the `ELLPACK` format but maintaining its efficient data access scheme. It can be seen as an intermediate format between `CSR` and `ELLPACK`. For more details read [the reference](https://arxiv.org/pdf/1307.6209v1)
136136

137137
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
138-
## `add`/`at` - Sparse Matrix data accessors
138+
## `add`- sparse matrix data accessors
139139

140140
### Status
141141

142142
Experimental
143143

144144
### Description
145-
Type-bound procedures to enable adding or requesting data in/from a sparse matrix.
145+
Type-bound procedures to enable adding data in a sparse matrix.
146146

147147
### Syntax
148148

@@ -151,19 +151,32 @@ Type-bound procedures to enable adding or requesting data in/from a sparse matri
151151

152152
### Arguments
153153

154-
`i`, `intent(in)`: Shall be an integer value or rank-1 array.
155-
`j`, `intent(in)`: Shall be an integer value or rank-1 array.
156-
`v`, `intent(in)`: Shall be a `real` or `complex` value or rank-2 array. The type shall be in accordance to the declared sparse matrix object.
154+
`i`: Shall be an integer value or rank-1 array. It is an `intent(in)` argument.
155+
156+
`j`: Shall be an integer value or rank-1 array. It is an `intent(in)` argument.
157+
158+
`v`: Shall be a `real` or `complex` value or rank-2 array. The type shall be in accordance to the declared sparse matrix object. It is an `intent(in)` argument.
159+
160+
## `at`- sparse matrix data accessors
161+
162+
### Status
163+
164+
Experimental
165+
166+
### Description
167+
Type-bound procedures to enable requesting data from a sparse matrix.
157168

158169
### Syntax
159170

160171
`v = matrix%at(i,j)`
161172

162173
### Arguments
163174

164-
`i`, `intent(in)` : Shall be an integer value.
165-
`j`, `intent(in)` : Shall be an integer value.
166-
`v`, `result` : Shall be a `real` or `complex` value in accordance to the declared sparse matrix object. If the `ij` tuple is within the sparse pattern, `v` contains the value in the data buffer. If the `ij` tuple is outside the sparse pattern, `v` is equal `0`. If the `ij` tuple is outside the matrix pattern `(nrows,ncols)`, `v` is `NaN`.
175+
`i` : Shall be an integer value. It is an `intent(in)` argument.
176+
177+
`j` : Shall be an integer value. It is an `intent(in)` argument.
178+
179+
`v` : Shall be a `real` or `complex` value in accordance to the declared sparse matrix object. If the `ij` tuple is within the sparse pattern, `v` contains the value in the data buffer. If the `ij` tuple is outside the sparse pattern, `v` is equal `0`. If the `ij` tuple is outside the matrix pattern `(nrows,ncols)`, `v` is `NaN`.
167180

168181
## Example
169182
```fortran
@@ -189,18 +202,18 @@ $$y=\alpha*M*x+\beta*y$$
189202

190203
### Arguments
191204

192-
`matrix`, `intent(in)`: Shall be a `real` or `complex` sparse type matrix.
205+
`matrix`: Shall be a `real` or `complex` sparse type matrix. It is an `intent(in)` argument.
193206

194-
`vec_x`, `intent(in)`: Shall be a rank-1 or rank-2 array of `real` or `complex` type array.
207+
`vec_x`: Shall be a rank-1 or rank-2 array of `real` or `complex` type array. It is an `intent(in)` argument.
195208

196-
`vec_y`, `intent(inout)`: Shall be a rank-1 or rank-2 array of `real` or `complex` type array.
209+
`vec_y`: Shall be a rank-1 or rank-2 array of `real` or `complex` type array. . It is an `intent(inout)` argument.
197210

198-
`alpha`, `intent(in)`, `optional` : Shall be a scalar value of the same type as `vec_x`. Default value `alpha=1`.
211+
`alpha`, `optional` : Shall be a scalar value of the same type as `vec_x`. Default value `alpha=1`. It is an `intent(in)` argument.
199212

200-
`beta`, `intent(in)`, `optional` : Shall be a scalar value of the same type as `vec_x`. Default value `beta=0`.
213+
`beta`, `optional` : Shall be a scalar value of the same type as `vec_x`. Default value `beta=0`. It is an `intent(in)` argument.
201214

202215
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
203-
## `sparse_conversion` - Sparse matrix to matrix conversions
216+
## Sparse matrix to matrix conversions
204217

205218
### Status
206219

@@ -212,35 +225,35 @@ This module provides facility functions for converting between storage formats.
212225

213226
### Syntax
214227

215-
`call ` [[stdlib_sparse_conversion(module):coo2ordered(interface)]] `(coo)`
228+
`call ` [[stdlib_sparse_conversion(module):coo2ordered(interface)]] `(coo[,sort_data])`
216229

217230
### Arguments
218231

219-
`COO`, `intent(inout)`: Shall be any `COO` type. The same object will be returned with the arrays reallocated to the correct size after removing duplicates.
232+
`COO` : Shall be any `COO` type. The same object will be returned with the arrays reallocated to the correct size after removing duplicates. It is an `intent(inout)` argument.
220233

221-
`sort_data`, `logical(in)`, `optional`:: Shall be an optional `logical` argument to determine whether data in the COO graph should be sorted while sorting the index array, default `.false.`.
234+
`sort_data`, `optional` : Shall be a `logical` argument to determine whether data in the COO graph should be sorted while sorting the index array, default `.false.`. It is an `intent(in)` argument.
222235

223236
### Syntax
224237

225238
`call ` [[stdlib_sparse_conversion(module):from_ijv(interface)]] `(sparse,row,col[,data,nrows,ncols,num_nz_rows,chunk])`
226239

227240
### Arguments
228241

229-
`sparse`, `intent(inout)`: Shall be a `COO`, `CSR`, `ELL` or `SELLC` type. The graph object will be returned with a canonical shape after sorting and removing duplicates from the `(row,col,data)` triplet. If the graph is `COO_type` no data buffer is allowed.
242+
`sparse` : Shall be a `COO`, `CSR`, `ELL` or `SELLC` type. The graph object will be returned with a canonical shape after sorting and removing duplicates from the `(row,col,data)` triplet. If the graph is `COO_type` no data buffer is allowed. It is an `intent(inout)` argument.
230243

231-
`row`, `integer(in)`:: rows index array.
244+
`row` : rows index array. It is an `intent(in)` argument.
232245

233-
`col`, `integer(in)`:: columns index array.
246+
`col` : columns index array. It is an `intent(in)` argument.
234247

235-
`data`, `real/complex(in)`, `optional`:: `real` or `complex` data array.
248+
`data`, `optional`: `real` or `complex` data array. It is an `intent(in)` argument.
236249

237-
`nrows`, `integer(in)`, `optional`:: number of rows, if not given it will be computed from the `row` array.
250+
`nrows`, `optional`: number of rows, if not given it will be computed from the `row` array. It is an `intent(in)` argument.
238251

239-
`ncols`, `integer(in)`, `optional`:: number of columns, if not given it will be computed from the `col` array.
252+
`ncols`, `optional`: number of columns, if not given it will be computed from the `col` array. It is an `intent(in)` argument.
240253

241-
`num_nz_rows`, `integer(in)`, `optional`:: number of non zeros per row, only valid in the case of an `ELL` matrix, by default it will computed from the largest row.
254+
`num_nz_rows`, `optional`: number of non zeros per row, only valid in the case of an `ELL` matrix, by default it will computed from the largest row. It is an `intent(in)` argument.
242255

243-
`chunk`, `integer(in)`, `optional`:: chunk size, only valid in the case of a `SELLC` matrix, by default it will be taken from the `SELLC` default attribute chunk size.
256+
`chunk`, `optional`: chunk size, only valid in the case of a `SELLC` matrix, by default it will be taken from the `SELLC` default attribute chunk size. It is an `intent(in)` argument.
244257

245258
## Example
246259
```fortran
@@ -253,51 +266,51 @@ This module provides facility functions for converting between storage formats.
253266

254267
### Arguments
255268

256-
`dense`, `intent(in)`: Shall be a rank-2 array of `real` or `complex` type.
269+
`dense` : Shall be a rank-2 array of `real` or `complex` type. It is an `intent(in)` argument.
257270

258-
`coo`, `intent(inout)`: Shall be a `COO` type of `real` or `complex` type.
271+
`coo` : Shall be a `COO` type of `real` or `complex` type. It is an `intent(out)` argument.
259272

260273
### Syntax
261274

262275
`call ` [[stdlib_sparse_conversion(module):coo2dense(interface)]] `(coo,dense)`
263276

264277
### Arguments
265278

266-
`coo`, `intent(in)`: Shall be a `COO` type of `real` or `complex` type.
279+
`coo` : Shall be a `COO` type of `real` or `complex` type. It is an `intent(in)` argument.
267280

268-
`dense`, `intent(inout)`: Shall be a rank-2 array of `real` or `complex` type.
281+
`dense` : Shall be a rank-2 array of `real` or `complex` type. It is an `intent(out)` argument.
269282

270283
### Syntax
271284

272285
`call ` [[stdlib_sparse_conversion(module):coo2csr(interface)]] `(coo,csr)`
273286

274287
### Arguments
275288

276-
`coo`, `intent(in)`: Shall be a `COO` type of `real` or `complex` type.
289+
`coo` : Shall be a `COO` type of `real` or `complex` type. It is an `intent(in)` argument.
277290

278-
`csr`, `intent(inout)`: Shall be a `CSR` type of `real` or `complex` type.
291+
`csr` : Shall be a `CSR` type of `real` or `complex` type. It is an `intent(out)` argument.
279292

280293
### Syntax
281294

282295
`call ` [[stdlib_sparse_conversion(module):csr2coo(interface)]] `(csr,coo)`
283296

284297
### Arguments
285298

286-
`csr`, `intent(in)`: Shall be a `CSR` type of `real` or `complex` type.
299+
`csr` : Shall be a `CSR` type of `real` or `complex` type. It is an `intent(in)` argument.
287300

288-
`coo`, `intent(inout)`: Shall be a `COO` type of `real` or `complex` type.
301+
`coo` : Shall be a `COO` type of `real` or `complex` type. It is an `intent(out)` argument.
289302

290303
### Syntax
291304

292305
`call ` [[stdlib_sparse_conversion(module):csr2sellc(interface)]] `(csr,sellc[,chunk])`
293306

294307
### Arguments
295308

296-
`csr`, `intent(in)`: Shall be a `CSR` type of `real` or `complex` type.
309+
`csr` : Shall be a `CSR` type of `real` or `complex` type. It is an `intent(in)` argument.
297310

298-
`sellc`, `intent(inout)`: Shall be a `SELLC` type of `real` or `complex` type.
311+
`sellc` : Shall be a `SELLC` type of `real` or `complex` type. It is an `intent(out)` argument.
299312

300-
`chunk`, `intent(in)`, `optional`: chunk size for the Sliced ELLPACK format.
313+
`chunk`, `optional`: chunk size for the Sliced ELLPACK format. It is an `intent(in)` argument.
301314

302315
## Example
303316
```fortran

src/stdlib_sparse.f90

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
!! public API
22
module stdlib_sparse
33
use stdlib_sparse_kinds
4-
use stdlib_sparse_spmv
54
end module stdlib_sparse

src/stdlib_sparse_conversion.fypp

Lines changed: 18 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -2,15 +2,15 @@
22
#:set R_KINDS_TYPES = list(zip(REAL_KINDS, REAL_TYPES, REAL_SUFFIX))
33
#:set C_KINDS_TYPES = list(zip(CMPLX_KINDS, CMPLX_TYPES, CMPLX_SUFFIX))
44
#:set KINDS_TYPES = R_KINDS_TYPES+C_KINDS_TYPES
5-
!> The `stdlib_sparse_conversion` module provides sparse to sparse matrix conversion utilities.
6-
!>
5+
!! The `stdlib_sparse_conversion` submodule provides sparse to sparse matrix conversion utilities.
6+
!!
77
! This code was modified from https://github.com/jalvesz/FSPARSE by its author: Alves Jose
88
submodule(stdlib_sparse_kinds) stdlib_sparse_conversion
99
use stdlib_sorting, only: sort
1010
implicit none
1111

12-
!> Sort arrays of a COO matrix
13-
!>
12+
!! Sort arrays of a COO matrix
13+
!!
1414
interface sort_coo
1515
module procedure sort_coo_unique
1616
#:for k1, t1, s1 in (KINDS_TYPES)
@@ -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(inout) :: COO
26+
type(COO_${s1}$), intent(out) :: COO
2727
integer :: num_rows, num_cols, nnz
2828
integer :: i, j, idx
2929

@@ -51,7 +51,7 @@ contains
5151
#:for k1, t1, s1 in (KINDS_TYPES)
5252
module subroutine coo2dense_${s1}$(COO,dense)
5353
type(COO_${s1}$), intent(in) :: COO
54-
${t1}$, allocatable, intent(inout) :: dense(:,:)
54+
${t1}$, allocatable, intent(out) :: dense(:,:)
5555
integer :: idx
5656

5757
if(.not.allocated(dense)) allocate(dense(COO%nrows,COO%nrows),source=zero_${s1}$)
@@ -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(inout) :: CSR
67+
type(COO_${s1}$), intent(in) :: COO
68+
type(CSR_${s1}$), intent(out) :: CSR
6969
integer :: i
7070

7171
CSR%nnz = COO%nnz; CSR%nrows = COO%nrows; CSR%ncols = COO%ncols
@@ -95,7 +95,7 @@ contains
9595
#:for k1, t1, s1 in (KINDS_TYPES)
9696
module subroutine csr2dense_${s1}$(CSR,dense)
9797
type(CSR_${s1}$), intent(in) :: CSR
98-
${t1}$, allocatable, intent(inout) :: dense(:,:)
98+
${t1}$, allocatable, intent(out) :: dense(:,:)
9999
integer :: i, j
100100

101101
if(.not.allocated(dense)) allocate(dense(CSR%nrows,CSR%nrows),source=zero_${s1}$)
@@ -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(inout) :: COO
123+
type(CSR_${s1}$), intent(in) :: CSR
124+
type(COO_${s1}$), intent(out) :: COO
125125
integer :: i, j
126126

127127
COO%nnz = CSR%nnz; COO%nrows = CSR%nrows; COO%ncols = CSR%ncols
@@ -146,9 +146,9 @@ 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(inout) :: ELL
151-
integer, intent(in), optional :: num_nz_rows !> number of non zeros per row
149+
type(CSR_${s1}$), intent(in) :: CSR
150+
type(ELL_${s1}$), intent(out) :: ELL
151+
integer, intent(in), optional :: num_nz_rows !! number of non zeros per row
152152

153153
integer :: i, j, num_nz_rows_, adr1, adr2
154154
!-------------------------------------------
@@ -176,10 +176,10 @@ contains
176176

177177
#:for k1, t1, s1 in (KINDS_TYPES)
178178
module subroutine csr2sellc_${s1}$(CSR,SELLC,chunk)
179-
!> csr2sellc: This function enables transfering data from a CSR matrix to a SELL-C matrix
180-
!> 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(inout) :: SELLC
179+
!! csr2sellc: This function enables transfering data from a CSR matrix to a SELL-C matrix
180+
!! 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
183183
integer, intent(in), optional :: chunk
184184
${t1}$, parameter :: zero = zero_${s1}$
185185
integer :: i, j, num_chunks

0 commit comments

Comments
 (0)