Skip to content

Commit d8b2b7c

Browse files
committed
test(tridiagonal): added test cases for all alpha and beta combinations under spmv
1 parent 1f0f686 commit d8b2b7c

File tree

1 file changed

+20
-2
lines changed

1 file changed

+20
-2
lines changed

test/linalg/test_linalg_specialmatrices.fypp

Lines changed: 20 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,10 @@ contains
3535
${t1}$, allocatable :: Amat(:,:), dl(:), dv(:), du(:)
3636
${t1}$, allocatable :: x(:)
3737
${t1}$, allocatable :: y1(:), y2(:)
38+
${t1}$ :: alpha, beta
39+
40+
integer :: i, j
41+
${t1}$, parameter :: coeffs(3) = [-1.0_wp, 0.0_wp, 1.0_wp]
3842

3943
! Initialize matrix.
4044
allocate(dl(n-1), dv(n), du(n-1))
@@ -56,13 +60,27 @@ contains
5660
call check(error, all_close(y1, y2), .true.)
5761
if (allocated(error)) return
5862

59-
#:if t1.startswith('complex')
63+
#:if t1.startswith('complex')
6064
! Test y = A.H @ x
6165
y1 = 0.0_wp ; y2 = 0.0_wp
6266
y1 = matmul(hermitian(Amat), x) ; call spmv(A, x, y2, op="H")
6367
call check(error, all_close(y1, y2), .true.)
6468
if (allocated(error)) return
6569
#:endif
70+
71+
! Test y = alpha * A @ x + beta * y for alpha,beta in {-1,0,1}
72+
do i = 1, 3
73+
do j = 1,3
74+
alpha = coeffs(i)
75+
beta = coeffs(j)
76+
77+
y1 = 0.0_wp
78+
call random_number(y2)
79+
y1 = alpha * matmul(Amat, x) + beta * y2 ; call spmv(A, x, y2, alpha=alpha, beta=beta)
80+
call check(error, all_close(y1, y2), .true.)
81+
if (allocated(error)) return
82+
end do
83+
end do
6684
end block
6785
#:endfor
6886
end subroutine
@@ -91,7 +109,7 @@ contains
91109
call check(error, state%ok(), .false.)
92110
if (allocated(error)) return
93111
end block
94-
#:endfor
112+
#:endfor
95113
end subroutine
96114

97115
end module

0 commit comments

Comments
 (0)