Skip to content

Commit 3dc4088

Browse files
committed
implement bicgstab with copilot
1 parent fb404bb commit 3dc4088

8 files changed

+563
-7
lines changed

doc/specs/stdlib_linalg_iterative_solvers.md

Lines changed: 95 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -248,4 +248,99 @@ Subroutine
248248

249249
```fortran
250250
{!example/linalg/example_solve_pcg.f90!}
251+
```
252+
253+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
254+
### `stdlib_solve_bicgstab_kernel` subroutine
255+
256+
#### Description
257+
258+
Implements the Biconjugate Gradient Stabilized (BiCGSTAB) method for solving the linear system \( Ax = b \), where \( A \) is a general (non-symmetric) linear operator defined via the `stdlib_linop` type. BiCGSTAB is particularly suitable for solving non-symmetric linear systems and provides better stability than the basic BiCG method. This is the core implementation, allowing flexibility for custom matrix types or parallel environments.
259+
260+
#### Syntax
261+
262+
`call ` [[stdlib_iterative_solvers(module):stdlib_solve_bicgstab_kernel(interface)]] ` (A, M, b, x, rtol, atol, maxiter, workspace)`
263+
264+
#### Status
265+
266+
Experimental
267+
268+
#### Class
269+
270+
Subroutine
271+
272+
#### Argument(s)
273+
274+
`A`: `class(stdlib_linop_<kind>_type)` defining the linear operator. This argument is `intent(in)`.
275+
276+
`M`: `class(stdlib_linop_<kind>_type)` defining the preconditioner linear operator. This argument is `intent(in)`.
277+
278+
`b`: 1-D array of `real(<kind>)` defining the loading conditions of the linear system. This argument is `intent(in)`.
279+
280+
`x`: 1-D array of `real(<kind>)` which serves as the input initial guess and the output solution. This argument is `intent(inout)`.
281+
282+
`rtol` and `atol`: scalars of type `real(<kind>)` specifying the convergence test. For convergence, the following criterion is used \( || b - Ax ||^2 <= max(rtol^2 * || b ||^2 , atol^2 ) \). These arguments are `intent(in)`.
283+
284+
`maxiter`: scalar of type `integer` defining the maximum allowed number of iterations. This argument is `intent(in)`.
285+
286+
`workspace`: scalar derived type of `type(stdlib_solver_workspace_<kind>_type)` holding the work array for the solver. This argument is `intent(inout)`.
287+
288+
#### Note
289+
290+
The BiCGSTAB method requires 8 auxiliary vectors in its workspace, making it more memory-intensive than CG or PCG methods. However, it can handle general non-symmetric matrices and often converges faster than BiCG for many problems.
291+
292+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
293+
### `stdlib_solve_bicgstab` subroutine
294+
295+
#### Description
296+
297+
Provides a user-friendly interface to the BiCGSTAB method for solving \( Ax = b \), supporting `dense` and `CSR_<kind>_type` matrices. BiCGSTAB is suitable for general (non-symmetric) linear systems and supports optional preconditioners for improved convergence. It handles workspace allocation and optional parameters for customization.
298+
299+
#### Syntax
300+
301+
`call ` [[stdlib_iterative_solvers(module):stdlib_solve_bicgstab(interface)]] ` (A, b, x [, di, rtol, atol, maxiter, restart, precond, M, workspace])`
302+
303+
#### Status
304+
305+
Experimental
306+
307+
#### Class
308+
309+
Subroutine
310+
311+
#### Argument(s)
312+
313+
`A`: `dense` or `CSR_<kind>_type` matrix defining the linear system. This argument is `intent(in)`.
314+
315+
`b`: 1-D array of `real(<kind>)` defining the loading conditions of the linear system. This argument is `intent(in)`.
316+
317+
`x`: 1-D array of `real(<kind>)` which serves as the input initial guess and the output solution. This argument is `intent(inout)`.
318+
319+
`di` (optional): 1-D mask array of type `logical(int8)` defining the degrees of freedom subject to dirichlet boundary conditions. The actual boundary conditions values should be stored in the `b` load array. This argument is `intent(in)`.
320+
321+
`rtol` and `atol` (optional): scalars of type `real(<kind>)` specifying the convergence test. For convergence, the following criterion is used \( || b - Ax ||^2 <= max(rtol^2 * || b ||^2 , atol^2 ) \). Default values are `rtol=1.e-5` and `atol=epsilon(1._<kind>)`. These arguments are `intent(in)`.
322+
323+
`maxiter` (optional): scalar of type `integer` defining the maximum allowed number of iterations. If no value is given, a default of `N` is set, where `N = size(b)`. This argument is `intent(in)`.
324+
325+
`restart` (optional): scalar of type `logical` indicating whether to restart the iteration with zero initial guess. Default is `.true.`. This argument is `intent(in)`.
326+
327+
`precond` (optional): scalar of type `integer` enabling to switch among the default preconditioners available with the following enum (`pc_none`, `pc_jacobi`). If no value is given, no preconditioning will be applied. This argument is `intent(in)`.
328+
329+
`M` (optional): scalar derived type of `class(stdlib_linop_<kind>_type)` defining a custom preconditioner linear operator. If given, `precond` will have no effect, and a pointer is set to this custom preconditioner. This argument is `intent(in)`.
330+
331+
`workspace` (optional): scalar derived type of `type(stdlib_solver_workspace_<kind>_type)` holding the work temporal array for the solver. If the user passes its own `workspace`, then internally a pointer is set to it, otherwise, memory will be internally allocated and deallocated before exiting the procedure. This argument is `intent(inout)`.
332+
333+
#### Note
334+
335+
BiCGSTAB is particularly effective for:
336+
- Non-symmetric linear systems
337+
- Systems where CG cannot be applied
338+
- Cases where BiCG suffers from irregular convergence
339+
340+
The method uses 8 auxiliary vectors internally, requiring more memory than simpler methods but often providing better stability and convergence properties.
341+
342+
#### Example
343+
344+
```fortran
345+
{!example/linalg/example_solve_bicgstab.f90!}
251346
```

example/linalg/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ ADD_EXAMPLE(get_norm)
4141
ADD_EXAMPLE(solve1)
4242
ADD_EXAMPLE(solve2)
4343
ADD_EXAMPLE(solve3)
44+
ADD_EXAMPLE(solve_bicgstab)
4445
ADD_EXAMPLE(solve_cg)
4546
ADD_EXAMPLE(solve_pcg)
4647
ADD_EXAMPLE(solve_custom)
Lines changed: 41 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,41 @@
1+
program example_solve_bicgstab
2+
use stdlib_kinds, only: dp
3+
use stdlib_linalg_iterative_solvers
4+
implicit none
5+
6+
integer, parameter :: n = 4
7+
real(dp) :: A(n,n), b(n), x(n)
8+
integer :: i
9+
10+
! Example matrix (same as SciPy documentation)
11+
A = reshape([4.0_dp, 2.0_dp, 0.0_dp, 1.0_dp, &
12+
3.0_dp, 0.0_dp, 0.0_dp, 2.0_dp, &
13+
0.0_dp, 1.0_dp, 1.0_dp, 1.0_dp, &
14+
0.0_dp, 2.0_dp, 1.0_dp, 0.0_dp], [n,n])
15+
16+
b = [-1.0_dp, -0.5_dp, -1.0_dp, 2.0_dp]
17+
18+
x = 0.0_dp ! Initial guess
19+
20+
print *, 'Solving Ax = b using BiCGSTAB method:'
21+
print *, 'Matrix A:'
22+
do i = 1, n
23+
print '(4F8.2)', A(i,:)
24+
end do
25+
print *, 'Right-hand side b:'
26+
print '(4F8.2)', b
27+
28+
! Solve using BiCGSTAB
29+
call stdlib_solve_bicgstab(A, b, x, rtol=1e-10_dp, atol=1e-12_dp)
30+
31+
print *, 'Solution x:'
32+
print '(4F10.6)', x
33+
34+
! Verify solution
35+
print *, 'Verification A*x:'
36+
print '(4F10.6)', matmul(A, x)
37+
38+
print *, 'Residual ||b - A*x||:'
39+
print *, norm2(b - matmul(A, x))
40+
41+
end program

src/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -98,6 +98,7 @@ set(cppFiles
9898
stdlib_linalg_iterative_solvers.fypp
9999
stdlib_linalg_iterative_solvers_cg.fypp
100100
stdlib_linalg_iterative_solvers_pcg.fypp
101+
stdlib_linalg_iterative_solvers_bicgstab.fypp
101102
)
102103

103104
add_subdirectory(blas)

src/stdlib_linalg_iterative_solvers.fypp

Lines changed: 54 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,9 +15,16 @@ module stdlib_linalg_iterative_solvers
1515
enum, bind(c)
1616
enumerator :: stdlib_size_wksp_cg = 3
1717
enumerator :: stdlib_size_wksp_pcg = 4
18+
enumerator :: stdlib_size_wksp_bicgstab = 8
1819
end enum
19-
public :: stdlib_size_wksp_cg, stdlib_size_wksp_pcg
20+
public :: stdlib_size_wksp_cg, stdlib_size_wksp_pcg, stdlib_size_wksp_bicgstab
2021

22+
enum, bind(c)
23+
enumerator :: pc_none = 0
24+
enumerator :: pc_jacobi
25+
end enum
26+
public :: pc_none, pc_jacobi
27+
2128
!! version: experimental
2229
!!
2330
!! linop type holding the linear operator and its associated methods.
@@ -127,6 +134,26 @@ module stdlib_linalg_iterative_solvers
127134
end interface
128135
public :: stdlib_solve_pcg_kernel
129136

137+
!! version: experimental
138+
!!
139+
!! stdlib_solve_bicgstab_kernel interface for the biconjugate gradient stabilized method.
140+
!! [Specifications](../page/specs/stdlib_linalg_iterative_solvers.html#stdlib_solve_bicgstab_kernel)
141+
interface stdlib_solve_bicgstab_kernel
142+
#:for k, t, s in R_KINDS_TYPES
143+
module subroutine stdlib_solve_bicgstab_kernel_${s}$(A,M,b,x,rtol,atol,maxiter,workspace)
144+
class(stdlib_linop_${s}$_type), intent(in) :: A !! linear operator
145+
class(stdlib_linop_${s}$_type), intent(in) :: M !! preconditioner linear operator
146+
${t}$, intent(in) :: b(:) !! right-hand side vector
147+
${t}$, intent(inout) :: x(:) !! solution vector and initial guess
148+
${t}$, intent(in) :: rtol !! relative tolerance for convergence
149+
${t}$, intent(in) :: atol !! absolute tolerance for convergence
150+
integer, intent(in) :: maxiter !! maximum number of iterations
151+
type(stdlib_solver_workspace_${s}$_type), intent(inout) :: workspace !! workspace for the solver
152+
end subroutine
153+
#:endfor
154+
end interface
155+
public :: stdlib_solve_bicgstab_kernel
156+
130157
interface stdlib_solve_pcg
131158
#:for matrix in MATRIX_TYPES
132159
#:for k, t, s in R_KINDS_TYPES
@@ -153,6 +180,32 @@ module stdlib_linalg_iterative_solvers
153180
end interface
154181
public :: stdlib_solve_pcg
155182

183+
interface stdlib_solve_bicgstab
184+
#:for matrix in MATRIX_TYPES
185+
#:for k, t, s in R_KINDS_TYPES
186+
module subroutine stdlib_solve_bicgstab_${matrix}$_${s}$(A,b,x,di,rtol,atol,maxiter,restart,precond,M,workspace)
187+
!! linear operator matrix
188+
#:if matrix == "dense"
189+
${t}$, intent(in) :: A(:,:)
190+
#:else
191+
type(${matrix}$_${s}$_type), intent(in) :: A
192+
#:endif
193+
${t}$, intent(in) :: b(:) !! right-hand side vector
194+
${t}$, intent(inout) :: x(:) !! solution vector and initial guess
195+
${t}$, intent(in), optional :: rtol !! relative tolerance for convergence
196+
${t}$, intent(in), optional :: atol !! absolute tolerance for convergence
197+
logical(1), intent(in), optional, target :: di(:) !! dirichlet conditions mask
198+
integer, intent(in), optional :: maxiter !! maximum number of iterations
199+
logical, intent(in), optional :: restart !! restart flag
200+
integer, intent(in), optional :: precond !! preconditioner method enumerator
201+
class(stdlib_linop_${s}$_type), optional , intent(in), target :: M !! preconditioner linear operator
202+
type(stdlib_solver_workspace_${s}$_type), optional, intent(inout), target :: workspace !! workspace for the solver
203+
end subroutine
204+
#:endfor
205+
#:endfor
206+
end interface
207+
public :: stdlib_solve_bicgstab
208+
156209
contains
157210

158211
!------------------------------------------------------------------

0 commit comments

Comments
 (0)