Skip to content

Commit 8afdf4b

Browse files
committed
rename with stdlib_ prefix
1 parent b3b5f43 commit 8afdf4b

8 files changed

+85
-85
lines changed

doc/specs/stdlib_linalg_iterative_solvers.md

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ The `stdlib_linalg_iterative_solvers` module provides base implementations for k
1717
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
1818
### The `linop` derived type
1919

20-
The `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.
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.
2121

2222
#### Type-bound procedures
2323

@@ -72,7 +72,7 @@ The output is a scalar of `type` and `kind` same as to that of `x` and `y`.
7272
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
7373
### The `solver_workspace` derived type
7474

75-
The `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.
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.
7676

7777
#### Type-bound procedures
7878

@@ -91,15 +91,15 @@ Subroutine
9191
`iter`: scalar of `integer` type giving the current iteration counter. This argument is `intent(in)`.
9292

9393
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
94-
### `solve_cg_kernel` subroutine
94+
### `stdlib_solve_cg_kernel` subroutine
9595

9696
#### Description
9797

9898
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 `linop` type. This is the core implementation, allowing flexibility for custom matrix types or parallel environments.
9999

100100
#### Syntax
101101

102-
`call ` [[stdlib_iterative_solvers(module):solve_cg_kernel(interface)]] ` (A, b, x, tol, maxiter, workspace)`
102+
`call ` [[stdlib_iterative_solvers(module):stdlib_solve_cg_kernel(interface)]] ` (A, b, x, tol, maxiter, workspace)`
103103

104104
#### Status
105105

@@ -111,7 +111,7 @@ Subroutine
111111

112112
#### Argument(s)
113113

114-
`A`: `class(linop_<kind>_type)` defining the linear operator. This argument is `intent(in)`.
114+
`A`: `class(stdlib_linop_<kind>_type)` defining the linear operator. This argument is `intent(in)`.
115115

116116
`b`: 1-D array of `real(<kind>)` defining the loading conditions of the linear system. This argument is `intent(in)`.
117117

@@ -121,7 +121,7 @@ Subroutine
121121

122122
`maxiter`: scalar of type `integer` defining the maximum allowed number of iterations. This argument is `intent(in)`.
123123

124-
`workspace`: `type(solver_workspace_<kind>_type)` holding the work temporal array for the solver. This argument is `intent(inout)`.
124+
`workspace`: `type(stdlib_solver_workspace_<kind>_type)` holding the work temporal array for the solver. This argument is `intent(inout)`.
125125

126126
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
127127
### `solve_cg` subroutine
@@ -156,7 +156,7 @@ Subroutine
156156

157157
`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)`.
158158

159-
`workspace` (optional): scalar derived type of `type(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)`.
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)`.
160160

161161
#### Example
162162

@@ -165,15 +165,15 @@ Subroutine
165165
```
166166

167167
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
168-
### `solve_pcg_kernel` subroutine
168+
### `stdlib_solve_pcg_kernel` subroutine
169169

170170
#### Description
171171

172172
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 `linop` type. This is the core implementation, allowing flexibility for custom matrix types or parallel environments.
173173

174174
#### Syntax
175175

176-
`call ` [[stdlib_iterative_solvers(module):solve_cg_kernel(interface)]] ` (A, M, b, x, tol, maxiter, workspace)`
176+
`call ` [[stdlib_iterative_solvers(module):stdlib_solve_cg_kernel(interface)]] ` (A, M, b, x, tol, maxiter, workspace)`
177177

178178
#### Status
179179

@@ -185,9 +185,9 @@ Subroutine
185185

186186
#### Argument(s)
187187

188-
`A`: `class(linop_<kind>_type)` defining the linear operator. This argument is `intent(in)`.
188+
`A`: `class(stdlib_linop_<kind>_type)` defining the linear operator. This argument is `intent(in)`.
189189

190-
`M`: `class(linop_<kind>_type)` defining the preconditioner linear operator. This argument is `intent(in)`.
190+
`M`: `class(stdlib_linop_<kind>_type)` defining the preconditioner linear operator. This argument is `intent(in)`.
191191

192192
`b`: 1-D array of `real(<kind>)` defining the loading conditions of the linear system. This argument is `intent(in)`.
193193

@@ -197,7 +197,7 @@ Subroutine
197197

198198
`maxiter`: scalar of type `integer` defining the maximum allowed number of iterations. This argument is `intent(in)`.
199199

200-
`workspace`: scalar derived type of `type(solver_workspace_<kind>_type)` holding the work array for the solver. This argument is `intent(inout)`.
200+
`workspace`: scalar derived type of `type(stdlib_solver_workspace_<kind>_type)` holding the work array for the solver. This argument is `intent(inout)`.
201201

202202
#### Example
203203

@@ -206,15 +206,15 @@ Subroutine
206206
```
207207

208208
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
209-
### `solve_pcg` subroutine
209+
### `stdlib_solve_pcg` subroutine
210210

211211
#### Description
212212

213213
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.
214214

215215
#### Syntax
216216

217-
`call ` [[stdlib_iterative_solvers(module):solve_pcg(interface)]] ` (A, b, x [, di, tol, maxiter, restart, precond, M, workspace])`
217+
`call ` [[stdlib_iterative_solvers(module):stdlib_solve_pcg(interface)]] ` (A, b, x [, di, tol, maxiter, restart, precond, M, workspace])`
218218

219219
#### Status
220220

@@ -240,9 +240,9 @@ Subroutine
240240

241241
`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)`.
242242

243-
`M` (optional): scalar derived type of `class(linop_<kind>_type)` defining a custom preconditioner linear operator. If given, `precond` will have no effect, a pointer is set to this custom preconditioner.
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.
244244

245-
`workspace` (optional): scalar derived type of `type(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)`.
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)`.
246246

247247
#### Example
248248

example/linalg/example_solve_cg.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
program example_solve_cg
22
use stdlib_kinds, only: int8, dp
3-
use stdlib_linalg_iterative_solvers, only: solve_cg
3+
use stdlib_linalg_iterative_solvers, only: stdlib_solve_cg
44

55
real(dp) :: matrix(2,2)
66
real(dp) :: x(2), rhs(2)
@@ -11,7 +11,7 @@ program example_solve_cg
1111
x = dble( [2,1] ) !> initial guess
1212
rhs = dble( [1,2] ) !> rhs vector
1313

14-
call solve_cg(matrix, rhs, x, restart=.false.)
14+
call stdlib_solve_cg(matrix, rhs, x, restart=.false.)
1515
print *, x !> solution: [0.0909, 0.6364]
1616

1717
end program

example/linalg/example_solve_custom.f90

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,30 +1,30 @@
11
module custom_solver
22
use stdlib_kinds, only: int8, dp
33
use stdlib_sparse, only: CSR_dp_type, spmv, diag
4-
use stdlib_linalg_iterative_solvers, only: linop_dp_type, &
5-
solver_workspace_dp_type, &
6-
solve_pcg_kernel, &
4+
use stdlib_linalg_iterative_solvers, only: stdlib_linop_dp_type, &
5+
stdlib_solver_workspace_dp_type, &
6+
stdlib_solve_pcg_kernel, &
77
stdlib_size_wksp_pcg
88
use stdlib_optval, only: optval
99
implicit none
1010
private
11-
public :: solve_pcg_custom
11+
public :: stdlib_solve_pcg_custom
1212

1313
contains
1414

15-
subroutine solve_pcg_custom(A,b,x,di,tol,maxiter,restart,workspace)
15+
subroutine stdlib_solve_pcg_custom(A,b,x,di,tol,maxiter,restart,workspace)
1616
type(CSR_dp_type), intent(in) :: A
1717
real(dp), intent(in) :: b(:)
1818
real(dp), intent(inout) :: x(:)
1919
real(dp), intent(in), optional :: tol
2020
logical(int8), intent(in), optional, target :: di(:)
2121
integer, intent(in), optional :: maxiter
2222
logical, intent(in), optional :: restart
23-
type(solver_workspace_dp_type), optional, intent(inout), target :: workspace
23+
type(stdlib_solver_workspace_dp_type), optional, intent(inout), target :: workspace
2424
!-------------------------
25-
type(linop_dp_type) :: op
26-
type(linop_dp_type) :: M
27-
type(solver_workspace_dp_type), pointer :: workspace_
25+
type(stdlib_linop_dp_type) :: op
26+
type(stdlib_linop_dp_type) :: M
27+
type(stdlib_solver_workspace_dp_type), pointer :: workspace_
2828
integer :: n, maxiter_
2929
real(dp) :: tol_
3030
logical :: restart_
@@ -61,7 +61,7 @@ subroutine solve_pcg_custom(A,b,x,di,tol,maxiter,restart,workspace)
6161
where(abs(diagonal)>epsilon(0._dp)) diagonal = 1._dp/diagonal
6262
!-------------------------
6363
! main call to the solver
64-
call solve_pcg_kernel(op,M,b,x,tol_,maxiter_,workspace_)
64+
call stdlib_solve_pcg_kernel(op,M,b,x,tol_,maxiter_,workspace_)
6565

6666
!-------------------------
6767
! internal memory cleanup
@@ -135,7 +135,7 @@ program example_solve_custom
135135
dirichlet = .false._1
136136
dirichlet([1,5]) = .true._1
137137

138-
call solve_pcg_custom(laplacian_csr, rhs, x, tol=1.d-6, di=dirichlet)
138+
call stdlib_solve_pcg_custom(laplacian_csr, rhs, x, tol=1.d-6, di=dirichlet)
139139
print *, x !> solution: [0.0, 2.5, 5.0, 2.5, 0.0]
140140

141141
end program example_solve_custom

example/linalg/example_solve_pcg.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
program example_solve_pcg
22
use stdlib_kinds, only: int8, dp
33
use stdlib_sparse
4-
use stdlib_linalg_iterative_solvers, only: solve_pcg
4+
use stdlib_linalg_iterative_solvers, only: stdlib_solve_pcg
55

66
type(CSR_dp_type) :: laplacian_csr
77
type(COO_dp_type) :: COO
@@ -23,10 +23,10 @@ program example_solve_pcg
2323
dirichlet = .false._int8
2424
dirichlet([1,5]) = .true._int8
2525

26-
call solve_pcg(laplacian, rhs, x, tol=1.d-6, di=dirichlet)
26+
call stdlib_solve_pcg(laplacian, rhs, x, tol=1.d-6, di=dirichlet)
2727
print *, x !> solution: [0.0, 2.5, 5.0, 2.5, 0.0]
2828
x = 0._dp
2929

30-
call solve_pcg(laplacian_csr, rhs, x, tol=1.d-6, di=dirichlet)
30+
call stdlib_solve_pcg(laplacian_csr, rhs, x, tol=1.d-6, di=dirichlet)
3131
print *, x !> solution: [0.0, 2.5, 5.0, 2.5, 0.0]
3232
end program

src/stdlib_linalg_iterative_solvers.fypp

Lines changed: 26 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ module stdlib_linalg_iterative_solvers
2323
!! linop type holding the linear operator and its associated methods.
2424
!! The `linop` type is used to define the linear operator for the iterative solvers.
2525
#:for k, t, s in R_KINDS_TYPES
26-
type, public :: linop_${s}$_type
26+
type, public :: stdlib_linop_${s}$_type
2727
procedure(vector_sub_${s}$), nopass, pointer :: matvec => null()
2828
procedure(reduction_sub_${s}$), nopass, pointer :: inner_product => default_dot_${s}$
2929
end type
@@ -33,7 +33,7 @@ module stdlib_linalg_iterative_solvers
3333
!!
3434
!! solver_workspace type holding temporal array data for the iterative solvers.
3535
#:for k, t, s in R_KINDS_TYPES
36-
type, public :: solver_workspace_${s}$_type
36+
type, public :: stdlib_solver_workspace_${s}$_type
3737
${t}$, allocatable :: tmp(:,:)
3838
procedure(logger_sub_${s}$), pointer, nopass :: callback => null()
3939
end type
@@ -66,26 +66,26 @@ module stdlib_linalg_iterative_solvers
6666

6767
!! version: experimental
6868
!!
69-
!! solve_cg_kernel interface for the conjugate gradient method.
70-
!! [Specifications](../page/specs/stdlib_linalg_iterative_solvers.html#solve_cg_kernel)
71-
interface solve_cg_kernel
69+
!! stdlib_solve_cg_kernel interface for the conjugate gradient method.
70+
!! [Specifications](../page/specs/stdlib_linalg_iterative_solvers.html#stdlib_solve_cg_kernel)
71+
interface stdlib_solve_cg_kernel
7272
#:for k, t, s in R_KINDS_TYPES
73-
module subroutine solve_cg_kernel_${s}$(A,b,x,tol,maxiter,workspace)
74-
class(linop_${s}$_type), intent(in) :: A !! linear operator
73+
module subroutine stdlib_solve_cg_kernel_${s}$(A,b,x,tol,maxiter,workspace)
74+
class(stdlib_linop_${s}$_type), intent(in) :: A !! linear operator
7575
${t}$, intent(in) :: b(:) !! right-hand side vector
7676
${t}$, intent(inout) :: x(:) !! solution vector and initial guess
7777
${t}$, intent(in) :: tol !! tolerance for convergence
7878
integer, intent(in) :: maxiter !! maximum number of iterations
79-
type(solver_workspace_${s}$_type), intent(inout) :: workspace !! workspace for the solver
79+
type(stdlib_solver_workspace_${s}$_type), intent(inout) :: workspace !! workspace for the solver
8080
end subroutine
8181
#:endfor
8282
end interface
83-
public :: solve_cg_kernel
83+
public :: stdlib_solve_cg_kernel
8484

85-
interface solve_cg
85+
interface stdlib_solve_cg
8686
#:for matrix in MATRIX_TYPES
8787
#:for k, t, s in R_KINDS_TYPES
88-
module subroutine solve_cg_${matrix}$_${s}$(A,b,x,di,tol,maxiter,restart,workspace)
88+
module subroutine stdlib_solve_cg_${matrix}$_${s}$(A,b,x,di,tol,maxiter,restart,workspace)
8989
!! linear operator matrix
9090
#:if matrix == "dense"
9191
${t}$, intent(in) :: A(:,:)
@@ -98,36 +98,36 @@ module stdlib_linalg_iterative_solvers
9898
logical(1), intent(in), optional, target :: di(:) !! dirichlet conditions mask
9999
integer, intent(in), optional :: maxiter !! maximum number of iterations
100100
logical, intent(in), optional :: restart !! restart flag
101-
type(solver_workspace_${s}$_type), optional, intent(inout), target :: workspace !! workspace for the solver
101+
type(stdlib_solver_workspace_${s}$_type), optional, intent(inout), target :: workspace !! workspace for the solver
102102
end subroutine
103103
#:endfor
104104
#:endfor
105105
end interface
106-
public :: solve_cg
106+
public :: stdlib_solve_cg
107107

108108
!! version: experimental
109109
!!
110-
!! solve_pcg_kernel interface for the preconditionned conjugate gradient method.
111-
!! [Specifications](../page/specs/stdlib_linalg_iterative_solvers.html#solve_pcg_kernel)
112-
interface solve_pcg_kernel
110+
!! stdlib_solve_pcg_kernel interface for the preconditionned conjugate gradient method.
111+
!! [Specifications](../page/specs/stdlib_linalg_iterative_solvers.html#stdlib_solve_pcg_kernel)
112+
interface stdlib_solve_pcg_kernel
113113
#:for k, t, s in R_KINDS_TYPES
114-
module subroutine solve_pcg_kernel_${s}$(A,M,b,x,tol,maxiter,workspace)
115-
class(linop_${s}$_type), intent(in) :: A !! linear operator
116-
class(linop_${s}$_type), intent(in) :: M !! preconditioner linear operator
114+
module subroutine stdlib_solve_pcg_kernel_${s}$(A,M,b,x,tol,maxiter,workspace)
115+
class(stdlib_linop_${s}$_type), intent(in) :: A !! linear operator
116+
class(stdlib_linop_${s}$_type), intent(in) :: M !! preconditioner linear operator
117117
${t}$, intent(in) :: b(:) !! right-hand side vector
118118
${t}$, intent(inout) :: x(:) !! solution vector and initial guess
119119
${t}$, intent(in) :: tol !! tolerance for convergence
120120
integer, intent(in) :: maxiter !! maximum number of iterations
121-
type(solver_workspace_${s}$_type), intent(inout) :: workspace !! workspace for the solver
121+
type(stdlib_solver_workspace_${s}$_type), intent(inout) :: workspace !! workspace for the solver
122122
end subroutine
123123
#:endfor
124124
end interface
125-
public :: solve_pcg_kernel
125+
public :: stdlib_solve_pcg_kernel
126126

127-
interface solve_pcg
127+
interface stdlib_solve_pcg
128128
#:for matrix in MATRIX_TYPES
129129
#:for k, t, s in R_KINDS_TYPES
130-
module subroutine solve_pcg_${matrix}$_${s}$(A,b,x,di,tol,maxiter,restart,precond,M,workspace)
130+
module subroutine stdlib_solve_pcg_${matrix}$_${s}$(A,b,x,di,tol,maxiter,restart,precond,M,workspace)
131131
!! linear operator matrix
132132
#:if matrix == "dense"
133133
${t}$, intent(in) :: A(:,:)
@@ -141,13 +141,13 @@ module stdlib_linalg_iterative_solvers
141141
integer, intent(in), optional :: maxiter !! maximum number of iterations
142142
logical, intent(in), optional :: restart !! restart flag
143143
integer, intent(in), optional :: precond !! preconditioner method enumerator
144-
class(linop_${s}$_type), optional , intent(in), target :: M !! preconditioner linear operator
145-
type(solver_workspace_${s}$_type), optional, intent(inout), target :: workspace !! workspace for the solver
144+
class(stdlib_linop_${s}$_type), optional , intent(in), target :: M !! preconditioner linear operator
145+
type(stdlib_solver_workspace_${s}$_type), optional, intent(inout), target :: workspace !! workspace for the solver
146146
end subroutine
147147
#:endfor
148148
#:endfor
149149
end interface
150-
public :: solve_pcg
150+
public :: stdlib_solve_pcg
151151

152152
contains
153153

0 commit comments

Comments
 (0)