@@ -43,25 +43,25 @@ contains
4343 if ( norm_sq0 > zero_${s}$ ) then
4444
4545 R = B
46- call A%apply (X, R, alpha= -one_${s}$, beta=one_${s}$) ! R = B - A*X
46+ call A%matvec (X, R, alpha= -one_${s}$, beta=one_${s}$, op='N' ) ! R = B - A*X
4747
48- call M%apply (R,P, alpha= one_${s}$, beta=zero_${s}$) ! P = M^{-1}*R
48+ call M%matvec (R,P, alpha= one_${s}$, beta=zero_${s}$, op='N' ) ! P = M^{-1}*R
4949
5050 tolsq = tol*tol
5151
5252 zr1 = zero_${s}$
5353 zr2 = one_${s}$
5454 do while ( (iter < maxiter) .AND. (norm_sq > tolsq * norm_sq0) )
55-
56- call M%apply (R,S, alpha= one_${s}$, beta=zero_${s}$) ! S = M^{-1}*R
55+
56+ call M%matvec (R,S, alpha= one_${s}$, beta=zero_${s}$, op='N' ) ! S = M^{-1}*R
5757 zr2 = A%inner_product( R, S )
5858
5959 if (iter>0) then
6060 beta = zr2 / zr1
6161 P = S + beta * P
6262 end if
63-
64- call A%apply (P, Q, alpha= one_${s}$, beta=zero_${s}$) ! Q = A*P
63+
64+ call A%matvec (P, Q, alpha= one_${s}$, beta=zero_${s}$, op='N' ) ! Q = A*P
6565 zv2 = A%inner_product( P, Q )
6666
6767 alpha = zr2 / zv2
@@ -134,14 +134,14 @@ contains
134134 #:else
135135 call diag(A,diagonal)
136136 #:endif
137- M_%apply => precond_jacobi
137+ M_%matvec => precond_jacobi
138138 case default
139- M_%apply => precond_none
139+ M_%matvec => precond_none
140140 end select
141141 where(abs(diagonal)>epsilon(zero_${s}$)) diagonal = one_${s}$/diagonal
142142 end if
143143 ! matvec for the operator
144- op%apply => matvec
144+ op%matvec => matvec
145145
146146 ! direchlet boundary conditions mask
147147 if(present(di))then
@@ -176,31 +176,37 @@ contains
176176 workspace_ => null()
177177 contains
178178
179- subroutine matvec(x,y,alpha,beta)
179+ subroutine matvec(x,y,alpha,beta,op)
180+ #:if matrix == "dense"
181+ use stdlib_linalg_blas, only: gemv
182+ #:endif
180183 ${t}$, intent(in) :: x(:)
181184 ${t}$, intent(inout) :: y(:)
182185 ${t}$, intent(in) :: alpha
183186 ${t}$, intent(in) :: beta
187+ character(1), intent(in) :: op
184188 #:if matrix == "dense"
185- y = alpha * matmul (A,x) + beta * y
189+ call gemv(op,m=size(A,1),n=size(A,2), alpha=alpha,a=A,lda=size (A,1),x=x,incx=1, beta=beta,y=y,incy=1)
186190 #:else
187- call spmv( A , x, y , alpha, beta )
191+ call spmv( A , x, y , alpha, beta , op )
188192 #:endif
189193 y = merge( zero_${s}$, y, di_ )
190194 end subroutine
191195
192- subroutine precond_none(x,y,alpha,beta)
196+ subroutine precond_none(x,y,alpha,beta,op )
193197 ${t}$, intent(in) :: x(:)
194198 ${t}$, intent(inout) :: y(:)
195199 ${t}$, intent(in) :: alpha
196200 ${t}$, intent(in) :: beta
201+ character(1), intent(in) :: op
197202 y = merge( zero_${s}$, x, di_ )
198203 end subroutine
199- subroutine precond_jacobi(x,y,alpha,beta)
204+ subroutine precond_jacobi(x,y,alpha,beta,op )
200205 ${t}$, intent(in) :: x(:)
201206 ${t}$, intent(inout) :: y(:)
202207 ${t}$, intent(in) :: alpha
203208 ${t}$, intent(in) :: beta
209+ character(1), intent(in) :: op
204210 y = merge( zero_${s}$, diagonal * x, di_ ) ! inverted diagonal
205211 end subroutine
206212 end subroutine
0 commit comments