Skip to content

Commit fb404bb

Browse files
jalveszjvdp1
andauthored
feat: [linalg] add iterative solvers (#994)
* start iterative solvers * simplify workspace * add pccg solver and example * complete cg with dirichlet flag, add example, fix di filter * add other sparse matrices * add example for custom solver extending the generic interface * small simplifications for working data * make default inner_product point to a default dot_product add enum for workspace sizes * make preconditionner a linop * use facility size * Add a customizable logger facility, change linop matvec to apply * change internal procedure names for custom example * refactor to remove hard dependency on dirichlet BCs * add forward/backward solvers for preconditionning * fix solve forward/backward * fix colum index * add preconditionners * fix cmake * add factorizations * backward solve to use Lt marix * start unit testing * review csr factorization * change name generic for kernel * shorten factorization procedures names * change precond ldl name * rename to pcg * start working on the documentation * clean docstrings * add cg and pcg tests * Update example/linalg/example_solve_cg.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * add _type suffix * reduce PR scope * rename wksp size constants * rename constant * change signature of linop apply to matvec and add operator input argument * Update doc/specs/stdlib_linalg_iterative_solvers.md Co-authored-by: Jeremie Vandenplas <[email protected]> * Update test/linalg/test_linalg_solve_iterative.fypp Co-authored-by: Jeremie Vandenplas <[email protected]> * Update test/linalg/test_linalg_solve_iterative.fypp Co-authored-by: Jeremie Vandenplas <[email protected]> * Update src/stdlib_linalg_iterative_solvers_cg.fypp Co-authored-by: Jeremie Vandenplas <[email protected]> * Update src/stdlib_linalg_iterative_solvers_cg.fypp Co-authored-by: Jeremie Vandenplas <[email protected]> * Update doc/specs/stdlib_linalg_iterative_solvers.md Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_cg.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update doc/specs/stdlib_linalg_iterative_solvers.md Co-authored-by: Jeremie Vandenplas <[email protected]> * Update doc/specs/stdlib_linalg_iterative_solvers.md Co-authored-by: Jeremie Vandenplas <[email protected]> * Update doc/specs/stdlib_linalg_iterative_solvers.md Co-authored-by: Jeremie Vandenplas <[email protected]> * Update doc/specs/stdlib_linalg_iterative_solvers.md Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_cg.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_cg.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_custom.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_custom.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_custom.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_custom.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_custom.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_custom.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_custom.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_pcg.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_pcg.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_pcg.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_pcg.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_pcg.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update example/linalg/example_solve_pcg.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update src/stdlib_linalg_iterative_solvers_cg.fypp Co-authored-by: Jeremie Vandenplas <[email protected]> * small fixes * add documentation information * forgotten attribute in doc * use optval * explicit use of private/public * Update doc/specs/stdlib_linalg_iterative_solvers.md Co-authored-by: Jeremie Vandenplas <[email protected]> * rename with stdlib_ prefix * Update example/linalg/example_solve_custom.f90 Co-authored-by: Jeremie Vandenplas <[email protected]> * Update src/stdlib_linalg_iterative_solvers_pcg.fypp Co-authored-by: Jeremie Vandenplas <[email protected]> * replace tol by rtol and atol for convergence test * change rtol and atol defaults --------- Co-authored-by: Jeremie Vandenplas <[email protected]>
1 parent 21c65ab commit fb404bb

12 files changed

+1101
-10
lines changed
Lines changed: 251 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,251 @@
1+
---
2+
title: linalg_iterative_solvers
3+
---
4+
5+
# The `stdlib_linalg_iterative_solvers` module
6+
7+
[TOC]
8+
9+
## Introduction
10+
11+
The `stdlib_linalg_iterative_solvers` module provides base implementations for known iterative solver methods. Each method is exposed with two procedure flavors:
12+
13+
* A `solve_<method>_kernel` which holds the method's base implementation. The linear system argument is defined through a `linop` derived type which enables extending the method for implicit or unknown (by `stdlib`) matrices or to complex scenarios involving distributed parallelism for which the user shall extend the `inner_product` and/or matrix-vector product to account for parallel syncrhonization.
14+
15+
* A `solve_<method>` which proposes an off-the-shelf ready to use interface for `dense` and `CSR_<kind>_type` matrices for all `real` kinds.
16+
17+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
18+
### The `linop` derived type
19+
20+
The `stdlib_linop_<kind>_type` derive type is an auxiliary class enabling to abstract the definition of the linear system and the actual implementation of the solvers.
21+
22+
#### Type-bound procedures
23+
24+
The following type-bound procedure pointers enable customization of the solver:
25+
26+
##### `matvec`
27+
28+
Proxy procedure for the matrix-vector product $y = alpha * op(M) * x + beta * y$.
29+
30+
#### Syntax
31+
32+
`call ` [[stdlib_iterative_solvers(module):matvec(interface)]] ` (x,y,alpha,beta,op)`
33+
34+
###### Class
35+
36+
Subroutine
37+
38+
###### Argument(s)
39+
40+
`x`: 1-D array of `real(<kind>)`. This argument is `intent(in)`.
41+
42+
`y`: 1-D array of `real(<kind>)`. This argument is `intent(inout)`.
43+
44+
`alpha`: scalar of `real(<kind>)`. This argument is `intent(in)`.
45+
46+
`beta`: scalar of `real(<kind>)`. This argument is `intent(in)`.
47+
48+
`op`: `character(1)` scalar which can be have any of the following values: `N` (no transpose), `T` (transpose) or `H` (conjugate transpose). This argument is `intent(in)`.
49+
50+
##### `inner_product`
51+
52+
Proxy procedure for the `dot_product`.
53+
54+
#### Syntax
55+
56+
`res = ` [[stdlib_iterative_solvers(module):inner_product(interface)]] ` (x,y)`
57+
58+
###### Class
59+
60+
Pure function
61+
62+
###### Argument(s)
63+
64+
`x`: 1-D array of `real(<kind>)`. This argument is `intent(in)`.
65+
66+
`y`: 1-D array of `real(<kind>)`. This argument is `intent(in)`.
67+
68+
###### Output value or Result value
69+
70+
The output is a scalar of `type` and `kind` same as to that of `x` and `y`.
71+
72+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
73+
### The `solver_workspace` derived type
74+
75+
The `stdlib_solver_workspace_<kind>_type` derive type is an auxiliary class enabling to hold the data associated to the working arrays needed by the solvers to operate.
76+
77+
#### Type-bound procedures
78+
79+
- `callback`: null pointer procedure enabling to pass a callback at each iteration to check on the solvers status.
80+
81+
##### Class
82+
83+
Subroutine
84+
85+
##### Argument(s)
86+
87+
`x`: 1-D array of `real(<kind>)` type with the current state of the solution vector. This argument is `intent(in)` as it should not be modified by the callback.
88+
89+
`norm_sq`: scalar of `real(<kind>)` type representing the squared norm of the residual at the current iteration. This argument is `intent(in)`.
90+
91+
`iter`: scalar of `integer` type giving the current iteration counter. This argument is `intent(in)`.
92+
93+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
94+
### `stdlib_solve_cg_kernel` subroutine
95+
96+
#### Description
97+
98+
Implements the Conjugate Gradient (CG) method for solving the linear system \( Ax = b \), where \( A \) is a symmetric positive-definite linear operator defined via the `stdlib_linop` type. This is the core implementation, allowing flexibility for custom matrix types or parallel environments.
99+
100+
#### Syntax
101+
102+
`call ` [[stdlib_iterative_solvers(module):stdlib_solve_cg_kernel(interface)]] ` (A, b, x, tol, maxiter, workspace)`
103+
104+
#### Status
105+
106+
Experimental
107+
108+
#### Class
109+
110+
Subroutine
111+
112+
#### Argument(s)
113+
114+
`A`: `class(stdlib_linop_<kind>_type)` defining the linear operator. This argument is `intent(in)`.
115+
116+
`b`: 1-D array of `real(<kind>)` defining the loading conditions of the linear system. This argument is `intent(in)`.
117+
118+
`x`: 1-D array of `real(<kind>)` which serves as the input initial guess and the output solution. This argument is `intent(inout)`.
119+
120+
`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)`.
121+
122+
`maxiter`: scalar of type `integer` defining the maximum allowed number of iterations. This argument is `intent(in)`.
123+
124+
`workspace`: scalar derived type of `type(stdlib_solver_workspace_<kind>_type)` holding the work array for the solver. This argument is `intent(inout)`.
125+
126+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
127+
### `solve_cg` subroutine
128+
129+
#### Description
130+
131+
Provides a user-friendly interface to the CG method for solving \( Ax = b \), supporting `dense` and `CSR_<kind>_type` matrices. It handles workspace allocation and optional parameters for customization.
132+
133+
#### Syntax
134+
135+
`call ` [[stdlib_iterative_solvers(module):solve_cg(interface)]] ` (A, b, x [, di, rtol, atol, maxiter, restart, workspace])`
136+
137+
#### Status
138+
139+
Experimental
140+
141+
#### Class
142+
143+
Subroutine
144+
145+
#### Argument(s)
146+
147+
`A`: `dense` or `CSR_<kind>_type` matrix defining the linear system. This argument is `intent(in)`.
148+
149+
`b`: 1-D array of `real(<kind>)` defining the right-hand-side (or loading) of the linear system. This argument is `intent(in)`.
150+
151+
`x`: 1-D array of `real(<kind>)` which serves as the input initial guess and as the output solution. This argument is `intent(inout)`.
152+
153+
`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)`.
154+
155+
`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 ) \). Defaults values are `rtol=1.e-5` and `atol=epsilon(1._<kind>)`. These arguments are `intent(in)`.
156+
157+
`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)`.
158+
159+
`workspace` (optional): scalar derived type of `type(stdlib_solver_workspace_<kind>_type)` holding the work array for the solver. If the user passes its own `workspace`, then a pointer is set internally to it. Otherwise, memory will be internally allocated and deallocated before exiting the procedure. This argument is `intent(inout)`.
160+
161+
#### Example
162+
163+
```fortran
164+
{!example/linalg/example_solve_cg.f90!}
165+
```
166+
167+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
168+
### `stdlib_solve_pcg_kernel` subroutine
169+
170+
#### Description
171+
172+
Implements the Preconditioned Conjugate Gradient (PCG) method for solving the linear system \( Ax = b \), where \( A \) is a symmetric positive-definite linear operator defined via the `stdlib_linop` type. This is the core implementation, allowing flexibility for custom matrix types or parallel environments.
173+
174+
#### Syntax
175+
176+
`call ` [[stdlib_iterative_solvers(module):stdlib_solve_cg_kernel(interface)]] ` (A, M, b, x, tol, maxiter, workspace)`
177+
178+
#### Status
179+
180+
Experimental
181+
182+
#### Class
183+
184+
Subroutine
185+
186+
#### Argument(s)
187+
188+
`A`: `class(stdlib_linop_<kind>_type)` defining the linear operator. This argument is `intent(in)`.
189+
190+
`M`: `class(stdlib_linop_<kind>_type)` defining the preconditioner linear operator. This argument is `intent(in)`.
191+
192+
`b`: 1-D array of `real(<kind>)` defining the loading conditions of the linear system. This argument is `intent(in)`.
193+
194+
`x`: 1-D array of `real(<kind>)` which serves as the input initial guess and the output solution. This argument is `intent(inout)`.
195+
196+
`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 ) \). These arguments are `intent(in)`.
197+
198+
`maxiter`: scalar of type `integer` defining the maximum allowed number of iterations. This argument is `intent(in)`.
199+
200+
`workspace`: scalar derived type of `type(stdlib_solver_workspace_<kind>_type)` holding the work array for the solver. This argument is `intent(inout)`.
201+
202+
#### Example
203+
204+
```fortran
205+
{!example/linalg/example_solve_custom.f90!}
206+
```
207+
208+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
209+
### `stdlib_solve_pcg` subroutine
210+
211+
#### Description
212+
213+
Provides a user-friendly interface to the PCG method for solving \( Ax = b \), supporting `dense` and `CSR_<kind>_type` matrices. It supports optional preconditioners and handles workspace allocation.
214+
215+
#### Syntax
216+
217+
`call ` [[stdlib_iterative_solvers(module):stdlib_solve_pcg(interface)]] ` (A, b, x [, di, tol, maxiter, restart, precond, M, workspace])`
218+
219+
#### Status
220+
221+
Experimental
222+
223+
#### Class
224+
225+
Subroutine
226+
227+
#### Argument(s)
228+
229+
`A`: `dense` or `CSR_<kind>_type` matrix defining the linear system. This argument is `intent(in)`.
230+
231+
`b`: 1-D array of `real(<kind>)` defining the loading conditions of the linear system. This argument is `intent(in)`.
232+
233+
`x`: 1-D array of `real(<kind>)` which serves as the input initial guess and the output solution. This argument is `intent(inout)`.
234+
235+
`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)`.
236+
237+
`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 ) \). Defaults values are `rtol=1.e-5` and `atol=epsilon(1._<kind>)`. These arguments are `intent(in)`.
238+
239+
`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)`.
240+
241+
`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 preconditionning will be applied. This argument is `intent(in)`.
242+
243+
`M` (optional): scalar derived type of `class(stdlib_linop_<kind>_type)` defining a custom preconditioner linear operator. If given, `precond` will have no effect, a pointer is set to this custom preconditioner.
244+
245+
`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)`.
246+
247+
#### Example
248+
249+
```fortran
250+
{!example/linalg/example_solve_pcg.f90!}
251+
```

example/linalg/CMakeLists.txt

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,9 @@ ADD_EXAMPLE(get_norm)
4141
ADD_EXAMPLE(solve1)
4242
ADD_EXAMPLE(solve2)
4343
ADD_EXAMPLE(solve3)
44+
ADD_EXAMPLE(solve_cg)
45+
ADD_EXAMPLE(solve_pcg)
46+
ADD_EXAMPLE(solve_custom)
4447
ADD_EXAMPLE(sparse_from_ijv)
4548
ADD_EXAMPLE(sparse_data_accessors)
4649
ADD_EXAMPLE(sparse_spmv)
Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
program example_solve_cg
2+
use stdlib_kinds, only: int8, dp
3+
use stdlib_linalg_iterative_solvers, only: stdlib_solve_cg
4+
5+
real(dp) :: matrix(2,2)
6+
real(dp) :: x(2), rhs(2)
7+
8+
matrix = reshape( [4, 1,&
9+
1, 3] , [2,2])
10+
11+
x = dble( [2,1] ) !> initial guess
12+
rhs = dble( [1,2] ) !> rhs vector
13+
14+
call stdlib_solve_cg(matrix, rhs, x, restart=.false.)
15+
print *, x !> solution: [0.0909, 0.6364]
16+
17+
end program

0 commit comments

Comments
 (0)