Skip to content

Commit 7ea8d29

Browse files
committed
In-code documentation.
1 parent d8bcc82 commit 7ea8d29

File tree

2 files changed

+38
-29
lines changed

2 files changed

+38
-29
lines changed

src/stdlib_specialmatrices.fypp

Lines changed: 18 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -188,7 +188,7 @@ module stdlib_specialmatrices
188188
!! ```
189189
#:for k1, t1, s1 in (KINDS_TYPES)
190190
pure module function initialize_symtridiagonal_pure_${s1}$(dv, ev) result(A)
191-
!! Construct a `tridiagonal` matrix from the rank-1 arrays
191+
!! Construct a `symtridiagonal` matrix from the rank-1 arrays
192192
!! `dl`, `dv` and `du`.
193193
${t1}$, intent(in) :: dv(:), ev(:)
194194
!! SymTridiagonal matrix elements.
@@ -241,10 +241,10 @@ module stdlib_specialmatrices
241241
!! =
242242
!! \begin{bmatrix}
243243
!! a_1 & b_1 \\
244-
!! b_1 & a_2 & b_2 \\
244+
!! \bar{b}_1 & a_2 & b_2 \\
245245
!! & \ddots & \ddots & \ddots \\
246-
!! & & b_{n-2} & a_{n-1} & b_{n-1} \\
247-
!! & & & b_{n-1} & a_n
246+
!! & & \bar{b}_{n-2} & a_{n-1} & b_{n-1} \\
247+
!! & & & \bar{b}_{n-1} & a_n
248248
!! \end{bmatrix}.
249249
!! \]
250250
!!
@@ -273,10 +273,10 @@ module stdlib_specialmatrices
273273
!! ```
274274
#:for k1, t1, s1 in (C_KINDS_TYPES)
275275
pure module function initialize_hermtridiagonal_pure_${s1}$(dv, ev) result(A)
276-
!! Construct a `tridiagonal` matrix from the rank-1 arrays
276+
!! Construct a `hermtridiagonal` matrix from the rank-1 arrays
277277
!! `dl`, `dv` and `du`.
278278
${t1}$, intent(in) :: dv(:), ev(:)
279-
!! SymTridiagonal matrix elements.
279+
!! HermTridiagonal matrix elements.
280280
type(hermtridiagonal_${s1}$_type) :: A
281281
!! Corresponding HermTridiagonal matrix.
282282
end function
@@ -332,12 +332,22 @@ module stdlib_specialmatrices
332332
#:for k1, t1, s1 in (KINDS_TYPES)
333333
#:for rank in RANKS
334334
module subroutine spmv_tridiag_${rank}$d_${s1}$(A, x, y, alpha, beta, op)
335+
!! Matrix-vector kernel for matrices extended from the `tridiagonal` class.
335336
class(tridiagonal_${s1}$_type), intent(in) :: A
337+
!! Input matrix.
336338
${t1}$, intent(in), contiguous, target :: x${ranksuffix(rank)}$
339+
!! Vector(s) to be multiplied by the matrix `A`.
337340
${t1}$, intent(inout), contiguous, target :: y${ranksuffix(rank)}$
341+
!! Resulting vector.
338342
real(${k1}$), intent(in), optional :: alpha
343+
!! Real scaling parameter for `Ax`
339344
real(${k1}$), intent(in), optional :: beta
345+
!! Real scaling parameter for `y` (right-hand side)
340346
character(1), intent(in), optional :: op
347+
!! Which operation to perform:
348+
!! - `op = "N"` : `y = alpha * A @ x + beta * y`
349+
!! - `op = "T"` : `y = alpha * A.T @ x + beta * y`
350+
!! - `op = "H"` : `y = alpha * A.H @ x + beta * y` (for complex-valued matrices only).
341351
end subroutine
342352
#:endfor
343353
#:endfor
@@ -475,7 +485,7 @@ module stdlib_specialmatrices
475485

476486
interface operator(+)
477487
!! Overload the `+` operator for matrix-matrix addition. The two matrices need to
478-
!! be of the same type and kind.
488+
!! be of the class type and kind.
479489
!! [Specifications](../page/specs/stdlib_specialmatrices.html#operators)
480490
#:for k1, t1, s1 in (KINDS_TYPES)
481491
pure module function matrix_add_tridiag_tridiag_${s1}$(A, B) result(C)
@@ -528,7 +538,7 @@ module stdlib_specialmatrices
528538

529539
interface operator(-)
530540
!! Overload the `-` operator for matrix-matrix subtraction. The two matrices need to
531-
!! be of the same type and kind.
541+
!! be of the same class and kind.
532542
!! [Specifications](../page/specs/stdlib_specialmatrices.html#operators)
533543
#:for k1, t1, s1 in (KINDS_TYPES)
534544
pure module function matrix_sub_tridiag_tridiag_${s1}$(A, B) result(C)

src/stdlib_specialmatrices_tridiagonal.fypp

Lines changed: 20 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
77
use stdlib_linalg_lapack, only: lagtm
88

99
character(len=*), parameter :: this = "tridiagonal matrices"
10+
1011
contains
1112

1213
!--------------------------------
@@ -144,7 +145,7 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
144145
#:for k1, t1, s1 in (KINDS_TYPES)
145146
pure module function initialize_symtridiagonal_pure_${s1}$(dv, ev) result(A)
146147
!! Construct a `symtridiagonal` matrix from the rank-1 arrays
147-
!! `dl`, `dv` and `du`.
148+
!! `dv` and `ev`.
148149
${t1}$, intent(in) :: dv(:), ev(:)
149150
!! symtridiagonal matrix elements.
150151
type(symtridiagonal_${s1}$_type) :: A
@@ -198,7 +199,7 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
198199

199200
module function initialize_symtridiagonal_impure_${s1}$(dv, ev, err) result(A)
200201
!! Construct a `symtridiagonal` matrix from the rank-1 arrays
201-
!! `dl`, `dv` and `du`.
202+
!! `dl` and `ev`.
202203
${t1}$, intent(in) :: dv(:), ev(:)
203204
!! symtridiagonal matrix elements.
204205
type(linalg_state_type), intent(out) :: err
@@ -259,12 +260,12 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
259260

260261
#:for k1, t1, s1 in (C_KINDS_TYPES)
261262
pure module function initialize_hermtridiagonal_pure_${s1}$(dv, ev) result(A)
262-
!! Construct a `symtridiagonal` matrix from the rank-1 arrays
263-
!! `dl`, `dv` and `du`.
263+
!! Construct a `hermtridiagonal` matrix from the rank-1 arrays
264+
!! `dl` and `ev`.
264265
${t1}$, intent(in) :: dv(:), ev(:)
265-
!! symtridiagonal matrix elements.
266+
!! hermtridiagonal matrix elements.
266267
type(hermtridiagonal_${s1}$_type) :: A
267-
!! Corresponding symtridiagonal matrix.
268+
!! Corresponding hermtridiagonal matrix.
268269

269270
! Internal variables.
270271
integer(ilp) :: n
@@ -284,17 +285,17 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
284285
! Description of the matrix.
285286
A%n = n
286287
! Matrix elements.
287-
A%dl = conjg(ev) ; A%dv = dv ; A%du = ev
288+
A%dl = conjg(ev) ; A%dv = dv%re ; A%du = ev
288289
end function
289290

290291
pure module function initialize_constant_hermtridiagonal_pure_${s1}$(dv, ev, n) result(A)
291-
!! Construct a `symtridiagonal` matrix with constant elements.
292+
!! Construct a `hermtridiagonal` matrix with constant elements.
292293
${t1}$, intent(in) :: dv, ev
293-
!! symtridiagonal matrix elements.
294+
!! hermtridiagonal matrix elements.
294295
integer(ilp), intent(in) :: n
295296
!! Matrix dimension.
296297
type(hermtridiagonal_${s1}$_type) :: A
297-
!! Corresponding symtridiagonal matrix.
298+
!! Corresponding hermtridiagonal matrix.
298299

299300
! Internal variables.
300301
integer(ilp) :: i
@@ -308,19 +309,19 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
308309
endif
309310
! Matrix elements.
310311
A%dl = [(conjg(ev), i = 1, n-1)]
311-
A%dv = [(dv, i = 1, n-1)]
312+
A%dv = [(dv%re, i = 1, n-1)]
312313
A%du = [(ev, i = 1, n-1)]
313314
end function
314315

315316
module function initialize_hermtridiagonal_impure_${s1}$(dv, ev, err) result(A)
316-
!! Construct a `symtridiagonal` matrix from the rank-1 arrays
317+
!! Construct a `hermtridiagonal` matrix from the rank-1 arrays
317318
!! `dl`, `dv` and `du`.
318319
${t1}$, intent(in) :: dv(:), ev(:)
319320
!! symtridiagonal matrix elements.
320321
type(linalg_state_type), intent(out) :: err
321322
!! Error handling.
322323
type(hermtridiagonal_${s1}$_type) :: A
323-
!! Corresponding symtridiagonal matrix.
324+
!! Corresponding hermtridiagonal matrix.
324325

325326
! Internal variables.
326327
integer(ilp) :: n
@@ -340,19 +341,19 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
340341
! Description of the matrix.
341342
A%n = n
342343
! Matrix elements.
343-
A%dl = conjg(ev) ; A%dv = dv ; A%du = ev
344+
A%dl = conjg(ev) ; A%dv = dv%re ; A%du = ev
344345
end function
345346

346347
module function initialize_constant_hermtridiagonal_impure_${s1}$(dv, ev, n, err) result(A)
347-
!! Construct a `symtridiagonal` matrix with constant elements.
348+
!! Construct a `hermtridiagonal` matrix with constant elements.
348349
${t1}$, intent(in) :: dv, ev
349350
!! symtridiagonal matrix elements.
350351
integer(ilp), intent(in) :: n
351352
!! Matrix dimension.
352353
type(linalg_state_type), intent(out) :: err
353354
!! Error handling
354355
type(hermtridiagonal_${s1}$_type) :: A
355-
!! Corresponding symtridiagonal matrix.
356+
!! Corresponding hermtridiagonal matrix.
356357

357358
! Internal variables.
358359
integer(ilp) :: i
@@ -366,7 +367,7 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
366367
endif
367368
! Matrix elements.
368369
A%dl = [(conjg(ev), i = 1, n)]
369-
A%dv = [(dv, i = 1, n-1)]
370+
A%dv = [(dv%re, i = 1, n-1)]
370371
A%du = [(ev, i = 1, n)]
371372
end function
372373
#:endfor
@@ -459,7 +460,6 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
459460
#:for k1, t1, s1 in (KINDS_TYPES)
460461
pure module function transpose_tridiagonal_${s1}$(A) result(B)
461462
type(tridiagonal_${s1}$_type), intent(in) :: A
462-
!! Input matrix.
463463
type(tridiagonal_${s1}$_type) :: B
464464
B = tridiagonal(A%du, A%dv, A%dl)
465465
end function
@@ -484,7 +484,6 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
484484
#:for k1, t1, s1 in (KINDS_TYPES)
485485
pure module function hermitian_tridiagonal_${s1}$(A) result(B)
486486
type(tridiagonal_${s1}$_type), intent(in) :: A
487-
!! Input matrix.
488487
type(tridiagonal_${s1}$_type) :: B
489488
#:if t1.startswith("complex")
490489
B = tridiagonal(conjg(A%du), conjg(A%dv), conjg(A%dl))
@@ -568,15 +567,15 @@ submodule (stdlib_specialmatrices) tridiagonal_matrices
568567
type(hermtridiagonal_${s1}$_type), intent(in) :: A
569568
type(hermtridiagonal_${s1}$_type) :: B
570569
B = hermtridiagonal(A%dv, A%du)
571-
B%dl = alpha*B%dl; B%dv = alpha*B%dv; B%du = alpha*B%du
570+
B%dl = alpha*B%dl; B%dv = alpha*B%dv; B%du = conjg(B%dl)
572571
end function
573572

574573
pure module function real_scalar_multiplication_bis_hermtridiagonal_${s1}$(A, alpha) result(B)
575574
type(hermtridiagonal_${s1}$_type), intent(in) :: A
576575
real(${k1}$), intent(in) :: alpha
577576
type(hermtridiagonal_${s1}$_type) :: B
578577
B = hermtridiagonal(A%dv, A%du)
579-
B%dl = alpha*B%dl; B%dv = alpha*B%dv; B%du = alpha*B%du
578+
B%dl = alpha*B%dl; B%dv = alpha*B%dv; B%du = conjg(B%dl)
580579
end function
581580
#:endif
582581
#:endfor

0 commit comments

Comments
 (0)