Skip to content

Commit 23be647

Browse files
committed
breaking change: rename matvec to spmv for consistency with stdlib blas gemv
1 parent 14bfef9 commit 23be647

File tree

6 files changed

+36
-34
lines changed

6 files changed

+36
-34
lines changed

doc/specs/stdlib_sparse.md

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,8 @@ Experimental
135135
#### Description
136136
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 [here](https://arxiv.org/pdf/1307.6209v1)
137137

138-
## `matvec` - Sparse Matrix-Vector product
138+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
139+
## `spmv` - Sparse Matrix-Vector product
139140

140141
### Status
141142

@@ -149,7 +150,7 @@ $$y=\alpha*M*x+\beta*y$$
149150

150151
### Syntax
151152

152-
`call ` [[stdlib_sparse_matvec(module):matvec(interface)]] `(matrix,vec_x,vec_y [,alpha,beta])`
153+
`call ` [[stdlib_sparse_spmv(module):spmv(interface)]] `(matrix,vec_x,vec_y [,alpha,beta])`
153154

154155
### Arguments
155156

@@ -163,6 +164,7 @@ $$y=\alpha*M*x+\beta*y$$
163164

164165
`beta`, `intent(in)`, `optional` : Shall be a scalar value of the same type as `vec_x`. Default value `beta=0`.
165166

167+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
166168
## `sparse_conversion` - Sparse matrix to matrix conversions
167169

168170
### Status

src/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@ set(fppFiles
3636
stdlib_sorting_sort_index.fypp
3737
stdlib_sparse_conversion.fypp
3838
stdlib_sparse_kinds.fypp
39-
stdlib_sparse_matvec.fypp
39+
stdlib_sparse_spmv.fypp
4040
stdlib_specialfunctions_gamma.fypp
4141
stdlib_stats.fypp
4242
stdlib_stats_corr.fypp

src/stdlib_sparse.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
!! public API
22
module stdlib_sparse
33
use stdlib_sparse_kinds
4-
use stdlib_sparse_matvec
4+
use stdlib_sparse_spmv
55
use stdlib_sparse_conversion
66
end module stdlib_sparse

src/stdlib_sparse_matvec.fypp renamed to src/stdlib_sparse_spmv.fypp

Lines changed: 20 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -7,38 +7,38 @@
77
#:def rksfx2(rank)
88
#{if rank > 0}#${":," + ":," * (rank - 1)}$#{endif}#
99
#:enddef
10-
!> The `stdlib_sparse_matvec` module provides matrix-vector product kernels.
10+
!> The `stdlib_sparse_spmv` module provides matrix-vector product kernels.
1111
!>
1212
! This code was modified from https://github.com/jalvesz/FSPARSE by its author: Alves Jose
13-
module stdlib_sparse_matvec
13+
module stdlib_sparse_spmv
1414
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
1515
use stdlib_sparse_kinds
1616
implicit none
1717
private
1818

19-
public :: matvec
20-
interface matvec
19+
public :: spmv
20+
interface spmv
2121
!! Version experimental
2222
!!
2323
!! Applay the sparse matrix-vector product $$y = \beta * y + \alpha * M * x $$
2424
!!
2525
#:for k1, t1, s1 in (KINDS_TYPES)
2626
#:for rank in RANKS
27-
module procedure matvec_coo_${rank}$d_${s1}$
28-
module procedure matvec_csr_${rank}$d_${s1}$
29-
module procedure matvec_csc_${rank}$d_${s1}$
30-
module procedure matvec_ell_${rank}$d_${s1}$
27+
module procedure spmv_coo_${rank}$d_${s1}$
28+
module procedure spmv_csr_${rank}$d_${s1}$
29+
module procedure spmv_csc_${rank}$d_${s1}$
30+
module procedure spmv_ell_${rank}$d_${s1}$
3131
#:endfor
32-
module procedure matvec_sellc_${s1}$
32+
module procedure spmv_sellc_${s1}$
3333
#:endfor
3434
end interface
3535

3636
contains
3737

38-
!> matvec_coo
38+
!> spmv_coo
3939
#:for k1, t1, s1 in (KINDS_TYPES)
4040
#:for rank in RANKS
41-
subroutine matvec_coo_${rank}$d_${s1}$(matrix,vec_x,vec_y,alpha,beta)
41+
subroutine spmv_coo_${rank}$d_${s1}$(matrix,vec_x,vec_y,alpha,beta)
4242
type(COO_${s1}$), intent(in) :: matrix
4343
${t1}$, intent(in) :: vec_x${ranksuffix(rank)}$
4444
${t1}$, intent(inout) :: vec_y${ranksuffix(rank)}$
@@ -78,10 +78,10 @@ contains
7878
#:endfor
7979
#:endfor
8080

81-
!! matvec_csr
81+
!! spmv_csr
8282
#:for k1, t1, s1 in (KINDS_TYPES)
8383
#:for rank in RANKS
84-
subroutine matvec_csr_${rank}$d_${s1}$(matrix,vec_x,vec_y,alpha,beta)
84+
subroutine spmv_csr_${rank}$d_${s1}$(matrix,vec_x,vec_y,alpha,beta)
8585
type(CSR_${s1}$), intent(in) :: matrix
8686
${t1}$, intent(in) :: vec_x${ranksuffix(rank)}$
8787
${t1}$, intent(inout) :: vec_y${ranksuffix(rank)}$
@@ -158,10 +158,10 @@ contains
158158
#:endfor
159159
#:endfor
160160

161-
!> matvec_csc
161+
!> spmv_csc
162162
#:for k1, t1, s1 in (KINDS_TYPES)
163163
#:for rank in RANKS
164-
subroutine matvec_csc_${rank}$d_${s1}$(matrix,vec_x,vec_y,alpha,beta)
164+
subroutine spmv_csc_${rank}$d_${s1}$(matrix,vec_x,vec_y,alpha,beta)
165165
type(CSC_${s1}$), intent(in) :: matrix
166166
${t1}$, intent(in) :: vec_x${ranksuffix(rank)}$
167167
${t1}$, intent(inout) :: vec_y${ranksuffix(rank)}$
@@ -222,10 +222,10 @@ contains
222222
#:endfor
223223
#:endfor
224224

225-
!> matvec_ell
225+
!> spmv_ell
226226
#:for k1, t1, s1 in (KINDS_TYPES)
227227
#:for rank in RANKS
228-
subroutine matvec_ell_${rank}$d_${s1}$(matrix,vec_x,vec_y,alpha,beta)
228+
subroutine spmv_ell_${rank}$d_${s1}$(matrix,vec_x,vec_y,alpha,beta)
229229
type(ELL_${s1}$), intent(in) :: matrix
230230
${t1}$, intent(in) :: vec_x${ranksuffix(rank)}$
231231
${t1}$, intent(inout) :: vec_y${ranksuffix(rank)}$
@@ -256,10 +256,10 @@ contains
256256
#:endfor
257257
#:endfor
258258

259-
!> matvec_sellc
259+
!> spmv_sellc
260260
#:set CHUNKS = [4,8,16]
261261
#:for k1, t1, s1 in (KINDS_TYPES)
262-
subroutine matvec_sellc_${s1}$(matrix,vec_x,vec_y,alpha,beta)
262+
subroutine spmv_sellc_${s1}$(matrix,vec_x,vec_y,alpha,beta)
263263
!> This algorithm was gracefully provided by Ivan Privec and adapted by Jose Alves
264264
type(SELLC_${s1}$), intent(in) :: matrix
265265
${t1}$, intent(in) :: vec_x(:)
@@ -336,4 +336,4 @@ contains
336336

337337
#:endfor
338338

339-
end module stdlib_sparse_matvec
339+
end module stdlib_sparse_spmv

test/linalg/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ set(
66
"test_linalg_lstsq.fypp"
77
"test_linalg_determinant.fypp"
88
"test_linalg_matrix_property_checks.fypp"
9-
"test_sparse_matvec.fypp"
9+
"test_sparse_spmv.fypp"
1010
)
1111
fypp_f90("${fyppFlags}" "${fppFiles}" outFiles)
1212

test/linalg/test_sparse_matvec.fypp renamed to test/linalg/test_sparse_spmv.fypp

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
#:include "common.fypp"
22
#:set R_KINDS_TYPES = list(zip(REAL_KINDS, REAL_TYPES, REAL_SUFFIX))
33
#:set KINDS_TYPES = R_KINDS_TYPES
4-
module test_sparse_matvec
4+
module test_sparse_spmv
55
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
66
use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64
77
use stdlib_sparse
@@ -55,7 +55,7 @@ contains
5555
call check(error, all(vec_y1 == real([6,11,15,15],kind=wp)) )
5656
if (allocated(error)) return
5757

58-
call matvec( COO, vec_x, vec_y2 )
58+
call spmv( COO, vec_x, vec_y2 )
5959
call check(error, all(vec_y1 == vec_y2) )
6060
if (allocated(error)) return
6161
end block
@@ -79,7 +79,7 @@ contains
7979

8080
allocate( vec_x(5) , source = 1._wp )
8181
allocate( vec_y(4) , source = 0._wp )
82-
call matvec( CSR, vec_x, vec_y )
82+
call spmv( CSR, vec_x, vec_y )
8383

8484
call check(error, all(vec_y == real([6,11,15,15],kind=wp)) )
8585
if (allocated(error)) return
@@ -104,7 +104,7 @@ contains
104104

105105
allocate( vec_x(5) , source = 1._wp )
106106
allocate( vec_y(4) , source = 0._wp )
107-
call matvec( CSC, vec_x, vec_y )
107+
call spmv( CSC, vec_x, vec_y )
108108

109109
call check(error, all(vec_y == real([6,11,15,15],kind=wp)) )
110110
if (allocated(error)) return
@@ -135,7 +135,7 @@ contains
135135

136136
allocate( vec_x(5) , source = 1._wp )
137137
allocate( vec_y(4) , source = 0._wp )
138-
call matvec( ELL, vec_x, vec_y )
138+
call spmv( ELL, vec_x, vec_y )
139139

140140
call check(error, all(vec_y == real([6,11,15,15],kind=wp)) )
141141
if (allocated(error)) return
@@ -172,7 +172,7 @@ contains
172172
allocate( vec_x(6) , source = 1._wp )
173173
allocate( vec_y(6) , source = 0._wp )
174174

175-
call matvec( SELLC, vec_x, vec_y )
175+
call spmv( SELLC, vec_x, vec_y )
176176

177177
call check(error, all(vec_y == real([6,22,27,23,27,48],kind=wp)) )
178178
if (allocated(error)) return
@@ -212,11 +212,11 @@ contains
212212
call check(error, all(vec_y1 == [3,5,5,3]) )
213213
if (allocated(error)) return
214214

215-
call matvec( COO , vec_x, vec_y2 )
215+
call spmv( COO , vec_x, vec_y2 )
216216
call check(error, all(vec_y1 == vec_y2) )
217217
if (allocated(error)) return
218218

219-
call matvec( CSR , vec_x, vec_y3 )
219+
call spmv( CSR , vec_x, vec_y3 )
220220
call check(error, all(vec_y1 == vec_y3) )
221221
if (allocated(error)) return
222222
end block
@@ -229,7 +229,7 @@ end module
229229
program tester
230230
use, intrinsic :: iso_fortran_env, only : error_unit
231231
use testdrive, only : run_testsuite, new_testsuite, testsuite_type
232-
use test_sparse_matvec, only : collect_suite
232+
use test_sparse_spmv, only : collect_suite
233233
implicit none
234234
integer :: stat, is
235235
type(testsuite_type), allocatable :: testsuites(:)

0 commit comments

Comments
 (0)