@@ -11,7 +11,7 @@ module stdlib_specialmatrices
11
11
use stdlib_linalg_constants
12
12
implicit none
13
13
private
14
- public :: Tridiagonal
14
+ public :: tridiagonal
15
15
public :: spmv
16
16
public :: dense, transpose, hermitian
17
17
public :: operator(*), operator(+), operator(-)
@@ -24,8 +24,8 @@ module stdlib_specialmatrices
24
24
25
25
!--> Tridiagonal matrices
26
26
#:for k1, t1, s1 in (KINDS_TYPES)
27
- type, public :: Tridiagonal_ ${s1}$_type
28
- !! Base type to define a `Tridiagonal ` matrix.
27
+ type, public :: tridiagonal_ ${s1}$_type
28
+ !! Base type to define a `tridiagonal ` matrix.
29
29
private
30
30
${t1}$, allocatable :: dl(:), dv(:), du(:)
31
31
integer(ilp) :: n
@@ -38,9 +38,9 @@ module stdlib_specialmatrices
38
38
!----- -----
39
39
!--------------------------------
40
40
41
- interface Tridiagonal
41
+ interface tridiagonal
42
42
!! ([Specifications](../page/specs/stdlib_specialmatrices.html#Tridiagonal)) This
43
- !! interface provides different methods to construct a `Tridiagonal ` matrix. Only
43
+ !! interface provides different methods to construct a `tridiagonal ` matrix. Only
44
44
!! the non-zero elements of \( A \) are stored, i.e.
45
45
!!
46
46
!! \[
@@ -57,44 +57,44 @@ module stdlib_specialmatrices
57
57
!!
58
58
!! #### Syntax
59
59
!!
60
- !! - Construct a real `Tridiagonal ` matrix from rank-1 arrays:
60
+ !! - Construct a real `tridiagonal ` matrix from rank-1 arrays:
61
61
!!
62
62
!! ```fortran
63
63
!! integer, parameter :: n
64
64
!! real(dp), allocatable :: dl(:), dv(:), du(:)
65
- !! type(Tridiagonal_rdp_type ) :: A
65
+ !! type(tridiagonal_rdp_type ) :: A
66
66
!! integer :: i
67
67
!!
68
68
!! dl = [(i, i=1, n-1)]; dv = [(2*i, i=1, n)]; du = [(3*i, i=1, n)]
69
69
!! A = Tridiagonal(dl, dv, du)
70
70
!! ```
71
71
!!
72
- !! - Construct a real `Tridiagonal ` matrix with constant diagonals:
72
+ !! - Construct a real `tridiagonal ` matrix with constant diagonals:
73
73
!!
74
74
!! ```fortran
75
75
!! integer, parameter :: n
76
76
!! real(dp), parameter :: a = 1.0_dp, b = 1.0_dp, c = 2.0_dp
77
- !! type(Tridiagonal_rdp_type ) :: A
77
+ !! type(tridiagonal_rdp_type ) :: A
78
78
!!
79
79
!! A = Tridiagonal(a, b, c, n)
80
80
!! ```
81
81
#:for k1, t1, s1 in (KINDS_TYPES)
82
82
pure module function initialize_tridiagonal_${s1}$(dl, dv, du) result(A)
83
- !! Construct a `Tridiagonal ` matrix from the rank-1 arrays
83
+ !! Construct a `tridiagonal ` matrix from the rank-1 arrays
84
84
!! `dl`, `dv` and `du`.
85
85
${t1}$, intent(in) :: dl(:), dv(:), du(:)
86
86
!! Tridiagonal matrix elements.
87
- type(Tridiagonal_ ${s1}$_type) :: A
87
+ type(tridiagonal_ ${s1}$_type) :: A
88
88
!! Corresponding Tridiagonal matrix.
89
89
end function
90
90
91
91
pure module function initialize_constant_tridiagonal_${s1}$(dl, dv, du, n) result(A)
92
- !! Construct a `Tridiagonal ` matrix with constant elements.
92
+ !! Construct a `tridiagonal ` matrix with constant elements.
93
93
${t1}$, intent(in) :: dl, dv, du
94
94
!! Tridiagonal matrix elements.
95
95
integer(ilp), intent(in) :: n
96
96
!! Matrix dimension.
97
- type(Tridiagonal_ ${s1}$_type) :: A
97
+ type(tridiagonal_ ${s1}$_type) :: A
98
98
!! Corresponding Tridiagonal matrix.
99
99
end function
100
100
#:endfor
@@ -116,7 +116,7 @@ module stdlib_specialmatrices
116
116
#:for k1, t1, s1 in (KINDS_TYPES)
117
117
#:for rank in RANKS
118
118
module subroutine spmv_tridiag_${rank}$d_${s1}$(A, x, y, alpha, beta, op)
119
- type(Tridiagonal_ ${s1}$_type), intent(in) :: A
119
+ type(tridiagonal_ ${s1}$_type), intent(in) :: A
120
120
${t1}$, intent(in), contiguous, target :: x${ranksuffix(rank)}$
121
121
${t1}$, intent(inout), contiguous, target :: y${ranksuffix(rank)}$
122
122
real(${k1}$), intent(in), optional :: alpha
@@ -139,8 +139,8 @@ module stdlib_specialmatrices
139
139
!! ([Specifications](../page/specs/stdlib_specialmatrices.html#dense))
140
140
#:for k1, t1, s1 in (KINDS_TYPES)
141
141
pure module function tridiagonal_to_dense_${s1}$(A) result(B)
142
- !! Convert a `Tridiagonal ` matrix to its dense representation.
143
- type(Tridiagonal_ ${s1}$_type), intent(in) :: A
142
+ !! Convert a `tridiagonal ` matrix to its dense representation.
143
+ type(tridiagonal_ ${s1}$_type), intent(in) :: A
144
144
!! Input Tridiagonal matrix.
145
145
${t1}$, allocatable :: B(:, :)
146
146
!! Corresponding dense matrix.
@@ -154,9 +154,9 @@ module stdlib_specialmatrices
154
154
!! [Specifications](../page/specs/stdlib_specialmatrices.html#transpose)
155
155
#:for k1, t1, s1 in (KINDS_TYPES)
156
156
pure module function transpose_tridiagonal_${s1}$(A) result(B)
157
- type(Tridiagonal_ ${s1}$_type), intent(in) :: A
157
+ type(tridiagonal_ ${s1}$_type), intent(in) :: A
158
158
!! Input matrix.
159
- type(Tridiagonal_ ${s1}$_type) :: B
159
+ type(tridiagonal_ ${s1}$_type) :: B
160
160
end function
161
161
#:endfor
162
162
end interface
@@ -168,9 +168,9 @@ module stdlib_specialmatrices
168
168
!! [Specifications](../page/specs/stdlib_specialmatrices.html#hermitian)
169
169
#:for k1, t1, s1 in (KINDS_TYPES)
170
170
pure module function hermitian_tridiagonal_${s1}$(A) result(B)
171
- type(Tridiagonal_ ${s1}$_type), intent(in) :: A
171
+ type(tridiagonal_ ${s1}$_type), intent(in) :: A
172
172
!! Input matrix.
173
- type(Tridiagonal_ ${s1}$_type) :: B
173
+ type(tridiagonal_ ${s1}$_type) :: B
174
174
end function
175
175
#:endfor
176
176
end interface
@@ -188,13 +188,13 @@ module stdlib_specialmatrices
188
188
#:for k1, t1, s1 in (KINDS_TYPES)
189
189
pure module function scalar_multiplication_tridiagonal_${s1}$(alpha, A) result(B)
190
190
${t1}$, intent(in) :: alpha
191
- type(Tridiagonal_ ${s1}$_type), intent(in) :: A
192
- type(Tridiagonal_ ${s1}$_type) :: B
191
+ type(tridiagonal_ ${s1}$_type), intent(in) :: A
192
+ type(tridiagonal_ ${s1}$_type) :: B
193
193
end function
194
194
pure module function scalar_multiplication_bis_tridiagonal_${s1}$(A, alpha) result(B)
195
- type(Tridiagonal_ ${s1}$_type), intent(in) :: A
195
+ type(tridiagonal_ ${s1}$_type), intent(in) :: A
196
196
${t1}$, intent(in) :: alpha
197
- type(Tridiagonal_ ${s1}$_type) :: B
197
+ type(tridiagonal_ ${s1}$_type) :: B
198
198
end function
199
199
#:endfor
200
200
end interface
@@ -205,9 +205,9 @@ module stdlib_specialmatrices
205
205
!! [Specifications](../page/specs/stdlib_specialmatrices.html#operators)
206
206
#:for k1, t1, s1 in (KINDS_TYPES)
207
207
pure module function matrix_add_tridiagonal_${s1}$(A, B) result(C)
208
- type(Tridiagonal_ ${s1}$_type), intent(in) :: A
209
- type(Tridiagonal_ ${s1}$_type), intent(in) :: B
210
- type(Tridiagonal_ ${s1}$_type) :: C
208
+ type(tridiagonal_ ${s1}$_type), intent(in) :: A
209
+ type(tridiagonal_ ${s1}$_type), intent(in) :: B
210
+ type(tridiagonal_ ${s1}$_type) :: C
211
211
end function
212
212
#:endfor
213
213
end interface
@@ -218,9 +218,9 @@ module stdlib_specialmatrices
218
218
!! [Specifications](../page/specs/stdlib_specialmatrices.html#operators)
219
219
#:for k1, t1, s1 in (KINDS_TYPES)
220
220
pure module function matrix_sub_tridiagonal_${s1}$(A, B) result(C)
221
- type(Tridiagonal_ ${s1}$_type), intent(in) :: A
222
- type(Tridiagonal_ ${s1}$_type), intent(in) :: B
223
- type(Tridiagonal_ ${s1}$_type) :: C
221
+ type(tridiagonal_ ${s1}$_type), intent(in) :: A
222
+ type(tridiagonal_ ${s1}$_type), intent(in) :: B
223
+ type(tridiagonal_ ${s1}$_type) :: C
224
224
end function
225
225
#:endfor
226
226
end interface
0 commit comments