Skip to content

Commit b68b4c8

Browse files
committed
add support for op with csc format
1 parent cd30636 commit b68b4c8

File tree

1 file changed

+46
-5
lines changed

1 file changed

+46
-5
lines changed

src/stdlib_sparse_spmv.fypp

Lines changed: 46 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -299,14 +299,24 @@ contains
299299

300300
associate( data => matrix%data, colptr => matrix%colptr, row => matrix%row, &
301301
& nnz => matrix%nnz, nrows => matrix%nrows, ncols => matrix%ncols, storage => matrix%storage )
302-
if( storage == sparse_full) then
302+
if( storage == sparse_full .and. op_==sparse_op_none ) then
303303
do concurrent(j=1:ncols)
304+
aux = alpha_ * vec_x(${rksfx2(rank-1)}$j)
304305
do i = colptr(j), colptr(j+1)-1
305-
vec_y(${rksfx2(rank-1)}$row(i)) = vec_y(${rksfx2(rank-1)}$row(i)) + alpha_ * data(i) * vec_x(${rksfx2(rank-1)}$j)
306+
vec_y(${rksfx2(rank-1)}$row(i)) = vec_y(${rksfx2(rank-1)}$row(i)) + data(i) * aux
307+
end do
308+
end do
309+
310+
else if( storage == sparse_full .and. op_==sparse_op_transpose ) then
311+
do concurrent(j=1:ncols)
312+
aux = zero_${k1}$
313+
do i = colptr(j), colptr(j+1)-1
314+
aux = aux + data(i) * vec_x(${rksfx2(rank-1)}$row(i))
306315
end do
316+
vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_ * aux
307317
end do
308318

309-
else if( storage == sparse_lower )then
319+
else if( storage == sparse_lower .and. op_/=sparse_op_hermitian )then
310320
do j = 1 , ncols
311321
aux = vec_x(${rksfx2(rank-1)}$j) * data(colptr(j))
312322
do i = colptr(j)+1, colptr(j+1)-1
@@ -316,7 +326,7 @@ contains
316326
vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_ * aux
317327
end do
318328

319-
else if( storage == sparse_upper )then
329+
else if( storage == sparse_upper .and. op_/=sparse_op_hermitian )then
320330
do j = 1 , ncols
321331
aux = zero_${s1}$
322332
do i = colptr(j), colptr(i+1)-2
@@ -326,7 +336,38 @@ contains
326336
aux = aux + data(colptr(j)) * vec_x(${rksfx2(rank-1)}$j)
327337
vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_ * aux
328338
end do
329-
339+
340+
#:if t1.startswith('complex')
341+
else if( storage == sparse_full .and. op_==sparse_op_hermitian ) then
342+
do concurrent(j=1:ncols)
343+
aux = zero_${k1}$
344+
do i = colptr(j), colptr(j+1)-1
345+
aux = aux + conjg(data(i)) * vec_x(${rksfx2(rank-1)}$row(i))
346+
end do
347+
vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_ * aux
348+
end do
349+
350+
else if( storage == sparse_lower .and. op_==sparse_op_hermitian )then
351+
do j = 1 , ncols
352+
aux = vec_x(${rksfx2(rank-1)}$j) * conjg(data(colptr(j)))
353+
do i = colptr(j)+1, colptr(j+1)-1
354+
aux = aux + conjg(data(i)) * vec_x(${rksfx2(rank-1)}$row(i))
355+
vec_y(${rksfx2(rank-1)}$row(i)) = vec_y(${rksfx2(rank-1)}$row(i)) + alpha_ * conjg(data(i)) * vec_x(${rksfx2(rank-1)}$j)
356+
end do
357+
vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_ * aux
358+
end do
359+
360+
else if( storage == sparse_upper .and. op_==sparse_op_hermitian )then
361+
do j = 1 , ncols
362+
aux = zero_${s1}$
363+
do i = colptr(j), colptr(i+1)-2
364+
aux = aux + conjg(data(i)) * vec_x(${rksfx2(rank-1)}$j)
365+
vec_y(${rksfx2(rank-1)}$i) = vec_y(${rksfx2(rank-1)}$i) + alpha_ * conjg(data(i)) * vec_x(${rksfx2(rank-1)}$row(i))
366+
end do
367+
aux = aux + conjg(data(colptr(j))) * vec_x(${rksfx2(rank-1)}$j)
368+
vec_y(${rksfx2(rank-1)}$j) = vec_y(${rksfx2(rank-1)}$j) + alpha_ * aux
369+
end do
370+
#:endif
330371
end if
331372
end associate
332373
end subroutine

0 commit comments

Comments
 (0)