Skip to content

Commit 05e44f0

Browse files
authored
sparse linalg: simplify SELLC spmv kernel (#912)
2 parents 94f201d + 6590506 commit 05e44f0

File tree

2 files changed

+13
-13
lines changed

2 files changed

+13
-13
lines changed

src/stdlib_sparse_conversion.fypp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -430,7 +430,7 @@ contains
430430
end block
431431
!-------------------------------------------
432432
! copy values and colum index
433-
allocate(SELLC%col(chunk_size,nnz), source = -1)
433+
allocate(SELLC%col(chunk_size,nnz), source = 1)
434434
allocate(SELLC%data(chunk_size,nnz), source = zero )
435435
block
436436
integer :: lb, ri, iaa, iab, rownnz

src/stdlib_sparse_spmv.fypp

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -513,23 +513,23 @@ contains
513513
#:for chunk in CHUNKS
514514
pure subroutine chunk_kernel_${chunk}$(n,a,col,x,y)
515515
integer, value :: n
516-
${t1}$, intent(in) :: a(${chunk}$,n), x(*)
516+
${t1}$, intent(in) :: a(${chunk}$,n), x(:)
517517
integer(ilp), intent(in) :: col(${chunk}$,n)
518518
${t1}$, intent(inout) :: y(${chunk}$)
519519
integer :: j
520520
do j = 1, n
521-
where(col(:,j) > 0) y = y + alpha_ * a(:,j) * x(col(:,j))
521+
y(:) = y(:) + alpha_ * a(:,j) * x(col(:,j))
522522
end do
523523
end subroutine
524524
pure subroutine chunk_kernel_trans_${chunk}$(n,a,col,x,y)
525525
integer, value :: n
526526
${t1}$, intent(in) :: a(${chunk}$,n), x(${chunk}$)
527527
integer(ilp), intent(in) :: col(${chunk}$,n)
528-
${t1}$, intent(inout) :: y(*)
528+
${t1}$, intent(inout) :: y(:)
529529
integer :: j, k
530530
do j = 1, n
531531
do k = 1, ${chunk}$
532-
if(col(k,j) > 0) y(col(k,j)) = y(col(k,j)) + alpha_ * a(k,j) * x(k)
532+
y(col(k,j)) = y(col(k,j)) + alpha_ * a(k,j) * x(k)
533533
end do
534534
end do
535535
end subroutine
@@ -538,11 +538,11 @@ contains
538538
integer, value :: n
539539
${t1}$, intent(in) :: a(${chunk}$,n), x(${chunk}$)
540540
integer(ilp), intent(in) :: col(${chunk}$,n)
541-
${t1}$, intent(inout) :: y(*)
541+
${t1}$, intent(inout) :: y(:)
542542
integer :: j, k
543543
do j = 1, n
544544
do k = 1, ${chunk}$
545-
if(col(k,j) > 0) y(col(k,j)) = y(col(k,j)) + alpha_ * conjg(a(k,j)) * x(k)
545+
y(col(k,j)) = y(col(k,j)) + alpha_ * conjg(a(k,j)) * x(k)
546546
end do
547547
end do
548548
end subroutine
@@ -551,23 +551,23 @@ contains
551551

552552
pure subroutine chunk_kernel_rm(n,cs,r,a,col,x,y)
553553
integer, value :: n, cs, r
554-
${t1}$, intent(in) :: a(cs,n), x(*)
554+
${t1}$, intent(in) :: a(cs,n), x(:)
555555
integer(ilp), intent(in) :: col(cs,n)
556556
${t1}$, intent(inout) :: y(r)
557557
integer :: j
558558
do j = 1, n
559-
where(col(1:r,j) > 0) y = y + alpha_ * a(1:r,j) * x(col(1:r,j))
559+
y(1:r) = y(1:r) + alpha_ * a(1:r,j) * x(col(1:r,j))
560560
end do
561561
end subroutine
562562
pure subroutine chunk_kernel_rm_trans(n,cs,r,a,col,x,y)
563563
integer, value :: n, cs, r
564564
${t1}$, intent(in) :: a(cs,n), x(r)
565565
integer(ilp), intent(in) :: col(cs,n)
566-
${t1}$, intent(inout) :: y(*)
566+
${t1}$, intent(inout) :: y(:)
567567
integer :: j, k
568568
do j = 1, n
569569
do k = 1, r
570-
if(col(k,j) > 0) y(col(k,j)) = y(col(k,j)) + alpha_ * a(k,j) * x(k)
570+
y(col(k,j)) = y(col(k,j)) + alpha_ * a(k,j) * x(k)
571571
end do
572572
end do
573573
end subroutine
@@ -576,11 +576,11 @@ contains
576576
integer, value :: n, cs, r
577577
${t1}$, intent(in) :: a(cs,n), x(r)
578578
integer(ilp), intent(in) :: col(cs,n)
579-
${t1}$, intent(inout) :: y(*)
579+
${t1}$, intent(inout) :: y(:)
580580
integer :: j, k
581581
do j = 1, n
582582
do k = 1, r
583-
if(col(k,j) > 0) y(col(k,j)) = y(col(k,j)) + alpha_ * conjg(a(k,j)) * x(k)
583+
y(col(k,j)) = y(col(k,j)) + alpha_ * conjg(a(k,j)) * x(k)
584584
end do
585585
end do
586586
end subroutine

0 commit comments

Comments
 (0)