Skip to content

Commit 6777aa0

Browse files
committed
Consistent lower-casing and imports.
1 parent 78b5085 commit 6777aa0

File tree

4 files changed

+54
-49
lines changed

4 files changed

+54
-49
lines changed

doc/specs/stdlib_specialmatrices.md

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ Experimental
3333
#### Description
3434

3535
Tridiagonal matrices are ubiquituous in scientific computing and often appear when discretizing 1D differential operators.
36-
A generic tridiagonal matrix has the following structure
36+
A generic tridiagonal matrix has the following structure:
3737
$$
3838
A
3939
=
@@ -50,25 +50,25 @@ This particular structure also lends itself to specialized implementations for m
5050
Interfaces to the most common ones will soon be provided by `stdlib_specialmatrices`.
5151
To date, `stdlib_specialmatrices` supports the following data types:
5252

53-
- `Tridiagonal_sp_type` : Tridiagonal matrix of size `n` with `real`/`single precision` data.
54-
- `Tridiagonal_dp_type` : Tridiagonal matrix of size `n` with `real`/`double precision` data.
55-
- `Tridiagonal_xdp_type` : Tridiagonal matrix of size `n` with `real`/`extended precision` data.
56-
- `Tridiagonal_qp_type` : Tridiagonal matrix of size `n` with `real`/`quadruple precision` data.
57-
- `Tridiagonal_csp_type` : Tridiagonal matrix of size `n` with `complex`/`single precision` data.
58-
- `Tridiagonal_cdp_type` : Tridiagonal matrix of size `n` with `complex`/`double precision` data.
59-
- `Tridiagonal_cxdp_type` : Tridiagonal matrix of size `n` with `complex`/`extended precision` data.
60-
- `Tridiagonal_cqp_type` : Tridiagonal matrix of size `n` with `complex`/`quadruple precision` data.
53+
- `tridiagonal_sp_type` : Tridiagonal matrix of size `n` with `real`/`single precision` data.
54+
- `tridiagonal_dp_type` : Tridiagonal matrix of size `n` with `real`/`double precision` data.
55+
- `tridiagonal_xdp_type` : Tridiagonal matrix of size `n` with `real`/`extended precision` data.
56+
- `tridiagonal_qp_type` : Tridiagonal matrix of size `n` with `real`/`quadruple precision` data.
57+
- `tridiagonal_csp_type` : Tridiagonal matrix of size `n` with `complex`/`single precision` data.
58+
- `tridiagonal_cdp_type` : Tridiagonal matrix of size `n` with `complex`/`double precision` data.
59+
- `tridiagonal_cxdp_type` : Tridiagonal matrix of size `n` with `complex`/`extended precision` data.
60+
- `tridiagonal_cqp_type` : Tridiagonal matrix of size `n` with `complex`/`quadruple precision` data.
6161

6262

6363
#### Syntax
6464

6565
- To construct a tridiagonal matrix from already allocated arrays `dl` (lower diagonal, size `n-1`), `dv` (main diagonal, size `n`) and `du` (upper diagonal, size `n-1`):
6666

67-
`A = ` [[stdlib_specialmatrices(module):Tridiagonal(interface)]] `(dl, dv, du)`
67+
`A = ` [[stdlib_specialmatrices(module):tridiagonal(interface)]] `(dl, dv, du)`
6868

6969
- To construct a tridiagonal matrix of size `n x n` with constant diagonal elements `dl`, `dv`, and `du`:
7070

71-
`A = ` [[stdlib_specialmatrices(module):Tridiagonal(interface)]] `(dl, dv, du, n)`
71+
`A = ` [[stdlib_specialmatrices(module):tridiagonal(interface)]] `(dl, dv, du, n)`
7272

7373
#### Example
7474

@@ -90,7 +90,7 @@ Experimental
9090

9191
With the exception of `extended precision` and `quadruple precision`, all the types provided by `stdlib_specialmatrices` benefit from specialized kernels for matrix-vector products accessible via the common `spmv` interface.
9292

93-
- For `Tridiagonal` matrices, the LAPACK `lagtm` backend is being used.
93+
- For `tridiagonal` matrices, the LAPACK `lagtm` backend is being used.
9494

9595
#### Syntax
9696

@@ -111,7 +111,7 @@ With the exception of `extended precision` and `quadruple precision`, all the ty
111111
- `op` (optional) : In-place operator identifier. Shall be a character(1) argument. It can have any of the following values: `N`: no transpose, `T`: transpose, `H`: hermitian or complex transpose.
112112

113113
@warning
114-
Due to some underlying `lapack`-related designs, `alpha` and `beta` can only take values in `[-1, 0, 1]` for `Tridiagonal` and `SymTridiagonal` matrices. See `lagtm` for more details.
114+
Due to some underlying `lapack`-related designs, `alpha` and `beta` can only take values in `[-1, 0, 1]` for `tridiagonal` and `symtridiagonal` matrices. See `lagtm` for more details.
115115
@endwarning
116116

117117
#### Examples

example/specialmatrices/example_specialmatrices_dp_spmv.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,17 @@
11
program example_tridiagonal_matrix
22
use stdlib_linalg_constants, only: dp
3-
use stdlib_specialmatrices, only: tridiaonal_dp_type, tridiagonal, dense
3+
use stdlib_specialmatrices, only: tridiagonal_dp_type, tridiagonal, dense, spmv
44
implicit none
55

66
integer, parameter :: n = 5
7-
type(Tridiagonal_dp_type) :: A
7+
type(tridiagonal_dp_type) :: A
88
real(dp) :: dl(n - 1), dv(n), du(n - 1)
99
real(dp) :: x(n), y(n), y_dense(n)
1010
integer :: i
1111

1212
! Create an arbitrary tridiagonal matrix.
1313
dl = [(i, i=1, n - 1)]; dv = [(2*i, i=1, n)]; du = [(3*i, i=1, n - 1)]
14-
A = Tridiagonal(dl, dv, du)
14+
A = tridiagonal(dl, dv, du)
1515

1616
! Initialize vectors.
1717
x = 1.0_dp; y = 0.0_dp; y_dense = 0.0_dp

src/stdlib_specialmatrices.fypp

Lines changed: 30 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@ module stdlib_specialmatrices
1111
use stdlib_linalg_constants
1212
implicit none
1313
private
14-
public :: Tridiagonal
14+
public :: tridiagonal
1515
public :: spmv
1616
public :: dense, transpose, hermitian
1717
public :: operator(*), operator(+), operator(-)
@@ -24,8 +24,8 @@ module stdlib_specialmatrices
2424

2525
!--> Tridiagonal matrices
2626
#: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.
2929
private
3030
${t1}$, allocatable :: dl(:), dv(:), du(:)
3131
integer(ilp) :: n
@@ -38,9 +38,9 @@ module stdlib_specialmatrices
3838
!----- -----
3939
!--------------------------------
4040

41-
interface Tridiagonal
41+
interface tridiagonal
4242
!! ([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
4444
!! the non-zero elements of \( A \) are stored, i.e.
4545
!!
4646
!! \[
@@ -57,44 +57,44 @@ module stdlib_specialmatrices
5757
!!
5858
!! #### Syntax
5959
!!
60-
!! - Construct a real `Tridiagonal` matrix from rank-1 arrays:
60+
!! - Construct a real `tridiagonal` matrix from rank-1 arrays:
6161
!!
6262
!! ```fortran
6363
!! integer, parameter :: n
6464
!! real(dp), allocatable :: dl(:), dv(:), du(:)
65-
!! type(Tridiagonal_rdp_type) :: A
65+
!! type(tridiagonal_rdp_type) :: A
6666
!! integer :: i
6767
!!
6868
!! dl = [(i, i=1, n-1)]; dv = [(2*i, i=1, n)]; du = [(3*i, i=1, n)]
6969
!! A = Tridiagonal(dl, dv, du)
7070
!! ```
7171
!!
72-
!! - Construct a real `Tridiagonal` matrix with constant diagonals:
72+
!! - Construct a real `tridiagonal` matrix with constant diagonals:
7373
!!
7474
!! ```fortran
7575
!! integer, parameter :: n
7676
!! 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
7878
!!
7979
!! A = Tridiagonal(a, b, c, n)
8080
!! ```
8181
#:for k1, t1, s1 in (KINDS_TYPES)
8282
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
8484
!! `dl`, `dv` and `du`.
8585
${t1}$, intent(in) :: dl(:), dv(:), du(:)
8686
!! Tridiagonal matrix elements.
87-
type(Tridiagonal_${s1}$_type) :: A
87+
type(tridiagonal_${s1}$_type) :: A
8888
!! Corresponding Tridiagonal matrix.
8989
end function
9090

9191
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.
9393
${t1}$, intent(in) :: dl, dv, du
9494
!! Tridiagonal matrix elements.
9595
integer(ilp), intent(in) :: n
9696
!! Matrix dimension.
97-
type(Tridiagonal_${s1}$_type) :: A
97+
type(tridiagonal_${s1}$_type) :: A
9898
!! Corresponding Tridiagonal matrix.
9999
end function
100100
#:endfor
@@ -116,7 +116,7 @@ module stdlib_specialmatrices
116116
#:for k1, t1, s1 in (KINDS_TYPES)
117117
#:for rank in RANKS
118118
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
120120
${t1}$, intent(in), contiguous, target :: x${ranksuffix(rank)}$
121121
${t1}$, intent(inout), contiguous, target :: y${ranksuffix(rank)}$
122122
real(${k1}$), intent(in), optional :: alpha
@@ -139,8 +139,8 @@ module stdlib_specialmatrices
139139
!! ([Specifications](../page/specs/stdlib_specialmatrices.html#dense))
140140
#:for k1, t1, s1 in (KINDS_TYPES)
141141
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
144144
!! Input Tridiagonal matrix.
145145
${t1}$, allocatable :: B(:, :)
146146
!! Corresponding dense matrix.
@@ -154,9 +154,9 @@ module stdlib_specialmatrices
154154
!! [Specifications](../page/specs/stdlib_specialmatrices.html#transpose)
155155
#:for k1, t1, s1 in (KINDS_TYPES)
156156
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
158158
!! Input matrix.
159-
type(Tridiagonal_${s1}$_type) :: B
159+
type(tridiagonal_${s1}$_type) :: B
160160
end function
161161
#:endfor
162162
end interface
@@ -168,9 +168,9 @@ module stdlib_specialmatrices
168168
!! [Specifications](../page/specs/stdlib_specialmatrices.html#hermitian)
169169
#:for k1, t1, s1 in (KINDS_TYPES)
170170
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
172172
!! Input matrix.
173-
type(Tridiagonal_${s1}$_type) :: B
173+
type(tridiagonal_${s1}$_type) :: B
174174
end function
175175
#:endfor
176176
end interface
@@ -188,13 +188,13 @@ module stdlib_specialmatrices
188188
#:for k1, t1, s1 in (KINDS_TYPES)
189189
pure module function scalar_multiplication_tridiagonal_${s1}$(alpha, A) result(B)
190190
${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
193193
end function
194194
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
196196
${t1}$, intent(in) :: alpha
197-
type(Tridiagonal_${s1}$_type) :: B
197+
type(tridiagonal_${s1}$_type) :: B
198198
end function
199199
#:endfor
200200
end interface
@@ -205,9 +205,9 @@ module stdlib_specialmatrices
205205
!! [Specifications](../page/specs/stdlib_specialmatrices.html#operators)
206206
#:for k1, t1, s1 in (KINDS_TYPES)
207207
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
211211
end function
212212
#:endfor
213213
end interface
@@ -218,9 +218,9 @@ module stdlib_specialmatrices
218218
!! [Specifications](../page/specs/stdlib_specialmatrices.html#operators)
219219
#:for k1, t1, s1 in (KINDS_TYPES)
220220
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
224224
end function
225225
#:endfor
226226
end interface

test/linalg/test_linalg_specialmatrices.fypp

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,12 @@ module test_specialmatrices
66
use stdlib_kinds, only: sp, dp, xdp, qp, int8, int16, int32, int64
77
use stdlib_linalg, only: hermitian
88
use stdlib_math, only: all_close
9-
use stdlib_specialmatrices
9+
use stdlib_specialmatrices, only: tridiagonal, &
10+
tridiagonal_sp_type, &
11+
tridiagonal_dp_type, &
12+
tridiagonal_xdp_type, &
13+
tridiagonal_qp_type, &
14+
dense, spmv
1015

1116
implicit none
1217

@@ -30,15 +35,15 @@ contains
3035
block
3136
integer, parameter :: wp = ${k1}$
3237
integer, parameter :: n = 5
33-
type(Tridiagonal_${s1}$_type) :: A
38+
type(tridiagonal_${s1}$_type) :: A
3439
${t1}$, allocatable :: Amat(:,:), dl(:), dv(:), du(:)
3540
${t1}$, allocatable :: x(:)
3641
${t1}$, allocatable :: y1(:), y2(:)
3742

3843
! Initialize matrix.
3944
allocate(dl(n-1), dv(n), du(n-1))
4045
call random_number(dl) ; call random_number(dv) ; call random_number(du)
41-
A = Tridiagonal(dl, dv, du) ; Amat = dense(A)
46+
A = tridiagonal(dl, dv, du) ; Amat = dense(A)
4247

4348
! Random vectors.
4449
allocate(x(n), source = 0.0_wp) ; call random_number(x)

0 commit comments

Comments
 (0)