Skip to content

Commit a3a3bdd

Browse files
committed
add example with wilkilson matrix
1 parent 05a694b commit a3a3bdd

File tree

2 files changed

+53
-0
lines changed

2 files changed

+53
-0
lines changed

example/linalg/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ ADD_EXAMPLE(solve1)
4242
ADD_EXAMPLE(solve2)
4343
ADD_EXAMPLE(solve3)
4444
ADD_EXAMPLE(solve_bicgstab)
45+
ADD_EXAMPLE(solve_bicgstab_wilkinson)
4546
ADD_EXAMPLE(solve_cg)
4647
ADD_EXAMPLE(solve_pcg)
4748
ADD_EXAMPLE(solve_custom)
Lines changed: 52 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,52 @@
1+
program example_solve_bicgstab_wilkinson
2+
use stdlib_kinds, only: dp
3+
use stdlib_linalg_iterative_solvers
4+
use stdlib_sparse
5+
use stdlib_sparse_spmv
6+
implicit none
7+
8+
integer, parameter :: n = 21
9+
type(COO_dp_type) :: COO
10+
type(CSR_dp_type) :: A
11+
type(stdlib_solver_workspace_dp_type) :: workspace
12+
real(dp) :: b(n), x(n), norm_sq0
13+
integer :: i
14+
15+
! Construct the Wilkinson's matrix in COO format
16+
! https://en.wikipedia.org/wiki/Wilkinson_matrix
17+
call COO%malloc(n, n, n + 2*(n-1))
18+
COO%data(1:n) = [( dble(abs(i)), i=-(n-1)/2, (n-1)/2)]
19+
COO%data(n+1:) = 1.0_dp
20+
do i = 1, n
21+
COO%index(1:2, i) = [i,i]
22+
end do
23+
do i = 1, n-1
24+
COO%index(1:2, n+i) = [i,i+1]
25+
COO%index(1:2, n+n-1+i) = [i+1,i]
26+
end do
27+
call coo2ordered(COO,sort_data=.true.)
28+
29+
! Convert COO to CSR format
30+
call coo2csr(COO, A)
31+
32+
! Set up the right-hand side for the solution to be ones
33+
b = 0.0_dp
34+
x = 1.0_dp
35+
call spmv(A, x, b) ! b = A * 1
36+
x = 0.0_dp ! initial guess
37+
38+
! Solve the system using BiCGSTAB
39+
workspace%callback => my_logger
40+
call stdlib_solve_bicgstab(A, b, x, rtol=1e-12_dp, maxiter=100, workspace=workspace)
41+
42+
contains
43+
44+
subroutine my_logger(x,norm_sq,iter)
45+
real(dp), intent(in) :: x(:)
46+
real(dp), intent(in) :: norm_sq
47+
integer, intent(in) :: iter
48+
if(iter == 0) norm_sq0 = norm_sq
49+
print *, "Iteration: ", iter, " Residual: ", norm_sq, " Relative: ", norm_sq/norm_sq0
50+
end subroutine
51+
52+
end program example_solve_bicgstab_wilkinson

0 commit comments

Comments
 (0)