Skip to content

Commit 59d33f0

Browse files
committed
complete spmv for the ellpack format including symmetric representations
1 parent 581d215 commit 59d33f0

File tree

4 files changed

+39
-1
lines changed

4 files changed

+39
-1
lines changed

doc/specs/stdlib_sparse.md

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -338,6 +338,18 @@ If the `diagonal` array has not been previously allocated, the `diag` subroutine
338338

339339
### Syntax
340340

341+
`call ` [[stdlib_sparse_conversion(module):csr2sellc(interface)]] `(csr,ell[,num_nz_rows])`
342+
343+
### Arguments
344+
345+
`csr` : Shall be a `CSR` type of `real` or `complex` type. It is an `intent(in)` argument.
346+
347+
`ell` : Shall be a `ELL` type of `real` or `complex` type. It is an `intent(out)` argument.
348+
349+
`num_nz_rows`, `optional`: number of non zeros per row. If not give, it will correspond to the size of the longest row in the `CSR` matrix. It is an `intent(in)` argument.
350+
351+
### Syntax
352+
341353
`call ` [[stdlib_sparse_conversion(module):csc2coo(interface)]] `(csc,coo)`
342354

343355
### Arguments

src/stdlib_sparse_conversion.fypp

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -378,6 +378,7 @@ contains
378378
end do
379379
end if
380380
call ELL%malloc(CSR%nrows,CSR%ncols,num_nz_rows_)
381+
ELL%storage = CSR%storage
381382
!-------------------------------------------
382383
do i = 1, CSR%nrows
383384
adr1 = CSR%rowptr(i)

src/stdlib_sparse_spmv.fypp

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -409,12 +409,30 @@ contains
409409
j = index(i,k)
410410
if(j>0) vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_*data(i,k) * vec_x(${rksfx2(rank-1)}$i)
411411
end do
412+
else if( storage /= sparse_full .and. op_/=sparse_op_hermitian ) then
413+
do concurrent (i = 1:nrows, k = 1:MNZ_P_ROW)
414+
j = index(i,k)
415+
if(j>0) then
416+
vec_y(${rksfx2(rank-1)}$i) = vec_y(${rksfx2(rank-1)}$i) + alpha_*data(i,k) * vec_x(${rksfx2(rank-1)}$j)
417+
if(i==j) cycle
418+
vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_*data(i,k) * vec_x(${rksfx2(rank-1)}$i)
419+
end if
420+
end do
412421
#:if t1.startswith('complex')
413422
else if( storage == sparse_full .and. op_==sparse_op_hermitian ) then
414423
do concurrent (i = 1:nrows, k = 1:MNZ_P_ROW)
415424
j = index(i,k)
416425
if(j>0) vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_*conjg(data(i,k)) * vec_x(${rksfx2(rank-1)}$i)
417426
end do
427+
else if( storage /= sparse_full .and. op_==sparse_op_hermitian ) then
428+
do concurrent (i = 1:nrows, k = 1:MNZ_P_ROW)
429+
j = index(i,k)
430+
if(j>0) then
431+
vec_y(${rksfx2(rank-1)}$i) = vec_y(${rksfx2(rank-1)}$i) + alpha_*conjg(data(i,k)) * vec_x(${rksfx2(rank-1)}$j)
432+
if(i==j) cycle
433+
vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_*conjg(data(i,k)) * vec_x(${rksfx2(rank-1)}$i)
434+
end if
435+
end do
418436
#:endif
419437
end if
420438
end associate

test/linalg/test_sparse_spmv.fypp

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -243,14 +243,16 @@ contains
243243
integer, parameter :: wp = ${k1}$
244244
type(COO_${s1}$_type) :: COO
245245
type(CSR_${s1}$_type) :: CSR
246+
type(ELL_${s1}$_type) :: ELL
246247
${t1}$, allocatable :: dense(:,:)
247248
${t1}$, allocatable :: vec_x(:)
248-
${t1}$, allocatable :: vec_y1(:), vec_y2(:), vec_y3(:)
249+
${t1}$, allocatable :: vec_y1(:), vec_y2(:), vec_y3(:), vec_y4(:)
249250

250251
allocate( vec_x(4) , source = 1._wp )
251252
allocate( vec_y1(4) , source = 0._wp )
252253
allocate( vec_y2(4) , source = 0._wp )
253254
allocate( vec_y3(4) , source = 0._wp )
255+
allocate( vec_y4(4) , source = 0._wp )
254256

255257
allocate( dense(4,4) , source = &
256258
reshape(real([1,0,0,0, &
@@ -261,6 +263,7 @@ contains
261263
call dense2coo( dense , COO )
262264
COO%storage = sparse_upper
263265
call coo2csr(COO, CSR)
266+
call csr2ell(CSR, ELL)
264267

265268
dense(2,1) = 2._wp; dense(3,2) = 2._wp; dense(4,3) = 2._wp
266269
vec_y1 = matmul( dense, vec_x )
@@ -274,6 +277,10 @@ contains
274277
call spmv( CSR , vec_x, vec_y3 )
275278
call check(error, all(vec_y1 == vec_y3) )
276279
if (allocated(error)) return
280+
281+
call spmv( ELL , vec_x, vec_y4 )
282+
call check(error, all(vec_y1 == vec_y4) )
283+
if (allocated(error)) return
277284
end block
278285
#:endfor
279286
end subroutine

0 commit comments

Comments
 (0)