Skip to content

Commit 0f9732e

Browse files
committed
add _type suffix
1 parent 9e5d000 commit 0f9732e

File tree

5 files changed

+39
-39
lines changed

5 files changed

+39
-39
lines changed

doc/specs/stdlib_linalg_iterative_solvers.md

Lines changed: 10 additions & 10 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>` derive type is an auxiliary class enabling to abstract the definition of the linear system and the actual implementation of the solvers.
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.
2121

2222
#### Type-bound procedures
2323

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

73-
The `solver_workspace_<kind>` derive type is an auxiliary class enabling to hold the data associated to the working arrays needed by the solvers to operate.
73+
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.
7474

7575
#### Type-bound procedures
7676

@@ -109,7 +109,7 @@ Subroutine
109109

110110
#### Argument(s)
111111

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

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

@@ -119,7 +119,7 @@ Subroutine
119119

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

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

124124
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
125125
### `solve_cg` subroutine
@@ -154,7 +154,7 @@ Subroutine
154154

155155
`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)`.
156156

157-
`workspace` (optional): `type(solver_workspace_<kind>)` 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)`.
157+
`workspace` (optional): `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)`.
158158

159159
#### Example
160160

@@ -183,9 +183,9 @@ Subroutine
183183

184184
#### Argument(s)
185185

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

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

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

@@ -195,7 +195,7 @@ Subroutine
195195

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

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

200200
#### Example
201201

@@ -238,9 +238,9 @@ Subroutine
238238

239239
`precond` (optional): scalar of type `integer` enabling to switch among the default preconditionners available. If no value is given, no preconditionning will be applied. This argument is `intent(in)`.
240240

241-
`M` (optional): `class(linop_<kind>)` defining a custom preconditionner linear operator. If given, `precond` will have no effect, a pointer is set to this custom preconditionner.
241+
`M` (optional): `class(linop_<kind>_type)` defining a custom preconditionner linear operator. If given, `precond` will have no effect, a pointer is set to this custom preconditionner.
242242

243-
`workspace` (optional): `type(solver_workspace_<kind>)` 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)`.
243+
`workspace` (optional): `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)`.
244244

245245
#### Example
246246

example/linalg/example_solve_custom.f90

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,8 @@
11
module custom_solver
22
use stdlib_kinds, only: dp
33
use stdlib_sparse
4-
use stdlib_linalg_iterative_solvers, only: linop_dp, &
5-
solver_workspace_dp, &
4+
use stdlib_linalg_iterative_solvers, only: linop_dp_type, &
5+
solver_workspace_dp_type, &
66
solve_pcg_kernel, &
77
size_wksp_pcg
88
implicit none
@@ -15,11 +15,11 @@ subroutine solve_pcg_custom(A,b,x,di,tol,maxiter,restart,workspace)
1515
logical(1), intent(in), optional, target :: di(:)
1616
integer, intent(in), optional :: maxiter
1717
logical, intent(in), optional :: restart
18-
type(solver_workspace_dp), optional, intent(inout), target :: workspace
18+
type(solver_workspace_dp_type), optional, intent(inout), target :: workspace
1919
!-------------------------
20-
type(linop_dp) :: op
21-
type(linop_dp) :: M
22-
type(solver_workspace_dp), pointer :: workspace_
20+
type(linop_dp_type) :: op
21+
type(linop_dp_type) :: M
22+
type(solver_workspace_dp_type), pointer :: workspace_
2323
integer :: n, maxiter_
2424
real(dp) :: tol_
2525
logical :: restart_

src/stdlib_linalg_iterative_solvers.fypp

Lines changed: 10 additions & 10 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}$
26+
type, public :: linop_${s}$_type
2727
procedure(vector_sub_${s}$), nopass, pointer :: apply => 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}$
36+
type, public :: solver_workspace_${s}$_type
3737
${t}$, allocatable :: tmp(:,:)
3838
procedure(logger_sub_${s}$), pointer, nopass :: callback => null()
3939
end type
@@ -70,12 +70,12 @@ module stdlib_linalg_iterative_solvers
7070
interface solve_cg_kernel
7171
#:for k, t, s in R_KINDS_TYPES
7272
module subroutine solve_cg_kernel_${s}$(A,b,x,tol,maxiter,workspace)
73-
class(linop_${s}$), intent(in) :: A !! linear operator
73+
class(linop_${s}$_type), intent(in) :: A !! linear operator
7474
${t}$, intent(in) :: b(:) !! right-hand side vector
7575
${t}$, intent(inout) :: x(:) !! solution vector and initial guess
7676
${t}$, intent(in) :: tol !! tolerance for convergence
7777
integer, intent(in) :: maxiter !! maximum number of iterations
78-
type(solver_workspace_${s}$), intent(inout) :: workspace !! workspace for the solver
78+
type(solver_workspace_${s}$_type), intent(inout) :: workspace !! workspace for the solver
7979
end subroutine
8080
#:endfor
8181
end interface
@@ -97,7 +97,7 @@ module stdlib_linalg_iterative_solvers
9797
logical(1), intent(in), optional, target :: di(:) !! dirichlet conditions mask
9898
integer, intent(in), optional :: maxiter !! maximum number of iterations
9999
logical, intent(in), optional :: restart !! restart flag
100-
type(solver_workspace_${s}$), optional, intent(inout), target :: workspace !! workspace for the solver
100+
type(solver_workspace_${s}$_type), optional, intent(inout), target :: workspace !! workspace for the solver
101101
end subroutine
102102
#:endfor
103103
#:endfor
@@ -111,13 +111,13 @@ module stdlib_linalg_iterative_solvers
111111
interface solve_pcg_kernel
112112
#:for k, t, s in R_KINDS_TYPES
113113
module subroutine solve_pcg_kernel_${s}$(A,M,b,x,tol,maxiter,workspace)
114-
class(linop_${s}$), intent(in) :: A !! linear operator
115-
class(linop_${s}$), intent(in) :: M !! preconditionner linear operator
114+
class(linop_${s}$_type), intent(in) :: A !! linear operator
115+
class(linop_${s}$_type), intent(in) :: M !! preconditionner linear operator
116116
${t}$, intent(in) :: b(:) !! right-hand side vector
117117
${t}$, intent(inout) :: x(:) !! solution vector and initial guess
118118
${t}$, intent(in) :: tol !! tolerance for convergence
119119
integer, intent(in) :: maxiter !! maximum number of iterations
120-
type(solver_workspace_${s}$), intent(inout) :: workspace !! workspace for the solver
120+
type(solver_workspace_${s}$_type), intent(inout) :: workspace !! workspace for the solver
121121
end subroutine
122122
#:endfor
123123
end interface
@@ -140,8 +140,8 @@ module stdlib_linalg_iterative_solvers
140140
integer, intent(in), optional :: maxiter !! maximum number of iterations
141141
logical, intent(in), optional :: restart !! restart flag
142142
integer, intent(in), optional :: precond !! preconditionner method enumerator
143-
class(linop_${s}$), optional , intent(in), target :: M !! preconditionner linear operator
144-
type(solver_workspace_${s}$), optional, intent(inout), target :: workspace !! workspace for the solver
143+
class(linop_${s}$_type), optional , intent(in), target :: M !! preconditionner linear operator
144+
type(solver_workspace_${s}$_type), optional, intent(inout), target :: workspace !! workspace for the solver
145145
end subroutine
146146
#:endfor
147147
#:endfor

src/stdlib_linalg_iterative_solvers_cg.fypp

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -15,11 +15,11 @@ contains
1515

1616
#:for k, t, s in R_KINDS_TYPES
1717
module subroutine solve_cg_kernel_${s}$(A,b,x,tol,maxiter,workspace)
18-
class(linop_${s}$), intent(in) :: A
18+
class(linop_${s}$_type), intent(in) :: A
1919
${t}$, intent(in) :: b(:), tol
2020
${t}$, intent(inout) :: x(:)
2121
integer, intent(in) :: maxiter
22-
type(solver_workspace_${s}$), intent(inout) :: workspace
22+
type(solver_workspace_${s}$_type), intent(inout) :: workspace
2323
!-------------------------
2424
integer :: iter
2525
${t}$ :: norm_sq, norm_sq_old, norm_sq0
@@ -78,10 +78,10 @@ contains
7878
logical(1), intent(in), optional, target :: di(:)
7979
integer, intent(in), optional :: maxiter
8080
logical, intent(in), optional :: restart
81-
type(solver_workspace_${s}$), optional, intent(inout), target :: workspace
81+
type(solver_workspace_${s}$_type), optional, intent(inout), target :: workspace
8282
!-------------------------
83-
type(linop_${s}$) :: op
84-
type(solver_workspace_${s}$), pointer :: workspace_
83+
type(linop_${s}$_type) :: op
84+
type(solver_workspace_${s}$_type), pointer :: workspace_
8585
integer :: n, maxiter_
8686
${t}$ :: tol_
8787
logical :: restart_

src/stdlib_linalg_iterative_solvers_pcg.fypp

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -22,12 +22,12 @@ contains
2222

2323
#:for k, t, s in R_KINDS_TYPES
2424
module subroutine solve_pcg_kernel_${s}$(A,M,b,x,tol,maxiter,workspace)
25-
class(linop_${s}$), intent(in) :: A
26-
class(linop_${s}$), intent(in) :: M
25+
class(linop_${s}$_type), intent(in) :: A
26+
class(linop_${s}$_type), intent(in) :: M
2727
${t}$, intent(in) :: b(:), tol
2828
${t}$, intent(inout) :: x(:)
2929
integer, intent(in) :: maxiter
30-
type(solver_workspace_${s}$), intent(inout) :: workspace
30+
type(solver_workspace_${s}$_type), intent(inout) :: workspace
3131
!-------------------------
3232
integer :: iter
3333
${t}$ :: norm_sq, norm_sq0, norm_sq_old
@@ -99,12 +99,12 @@ contains
9999
integer, intent(in), optional :: maxiter
100100
logical, intent(in), optional :: restart
101101
integer, intent(in), optional :: precond
102-
class(linop_${s}$), optional , intent(in), target :: M
103-
type(solver_workspace_${s}$), optional, intent(inout), target :: workspace
102+
class(linop_${s}$_type), optional , intent(in), target :: M
103+
type(solver_workspace_${s}$_type), optional, intent(inout), target :: workspace
104104
!-------------------------
105-
type(linop_${s}$) :: op
106-
type(linop_${s}$), pointer :: M_ => null()
107-
type(solver_workspace_${s}$), pointer :: workspace_
105+
type(linop_${s}$_type) :: op
106+
type(linop_${s}$_type), pointer :: M_ => null()
107+
type(solver_workspace_${s}$_type), pointer :: workspace_
108108
integer :: n, maxiter_
109109
${t}$ :: tol_
110110
logical :: restart_

0 commit comments

Comments
 (0)