@@ -46,6 +46,15 @@ module stdlib_specialmatrices
4646 end type
4747 #:endfor
4848
49+ !--> Hermitian Tridiagonal matrices
50+ #:for k1, t1, s1 in (C_KINDS_TYPES)
51+ type, extends(tridiagonal_${s1}$_type), public :: hermtridiagonal_${s1}$_type
52+ !! Base type to de fine a `hermtridiagonal` matrix.
53+ private
54+ logical(lk) :: is_posdef
55+ end type
56+ #:endfor
57+
4958 !--------------------------------
5059 !----- -----
5160 !----- CONSTRUCTORS -----
@@ -222,6 +231,91 @@ module stdlib_specialmatrices
222231 #:endfor
223232 end interface
224233
234+ interface hermtridiagonal
235+ !! ([Specifications](../page/specs/stdlib_specialmatrices.html#HermTridiagonal)) This
236+ !! interface provides different methods to construct a `hermtridiagonal`
237+ !! matrix. Only the non-zero elements of \( A \) are stored, i.e.
238+ !!
239+ !! \[
240+ !! A
241+ !! =
242+ !! \begin{bmatrix}
243+ !! a_1 & b_1 \\
244+ !! b_1 & a_2 & b_2 \\
245+ !! & \ddots & \ddots & \ddots \\
246+ !! & & b_{n-2} & a_{n-1} & b_{n-1} \\
247+ !! & & & b_{n-1} & a_n
248+ !! \end{bmatrix}.
249+ !! \]
250+ !!
251+ !! #### Syntax
252+ !!
253+ !! - Construct a complex `hermtridiagonal` matrix from rank-1 arrays:
254+ !!
255+ !! ```fortran
256+ !! integer, parameter :: n
257+ !! complex(dp), allocatable :: dv(:), ev(:)
258+ !! type(hermtridiagonal_cdp_type) :: A
259+ !! integer :: i
260+ !!
261+ !! ev = [(i, i=1, n-1)]; dv = [(2*i, i=1, n)]
262+ !! A = HermTridiagonal(dv, ev)
263+ !! ```
264+ !!
265+ !! - Construct a complex `hermtridiagonal` matrix with constant diagonals:
266+ !!
267+ !! ```fortran
268+ !! integer, parameter :: n
269+ !! complex(dp), parameter :: a = 1.0_dp, b = 1.0_dp
270+ !! type(hermtridiagonal_rdp_type) :: A
271+ !!
272+ !! A = HermTridiagonal(a, b, n)
273+ !! ```
274+ #:for k1, t1, s1 in (C_KINDS_TYPES)
275+ pure module function initialize_hermtridiagonal_pure_${s1}$(dv, ev) result(A)
276+ !! Construct a `tridiagonal` matrix from the rank-1 arrays
277+ !! `dl`, `dv` and `du`.
278+ ${t1}$, intent(in) :: dv(:), ev(:)
279+ !! SymTridiagonal matrix elements.
280+ type(hermtridiagonal_${s1}$_type) :: A
281+ !! Corresponding HermTridiagonal matrix.
282+ end function
283+
284+ pure module function initialize_constant_hermtridiagonal_pure_${s1}$(dv, ev, n) result(A)
285+ !! Construct a `hermtridiagonal` matrix with constant elements.
286+ ${t1}$, intent(in) :: dv, ev
287+ !! HermTridiagonal matrix elements.
288+ integer(ilp), intent(in) :: n
289+ !! Matrix dimension.
290+ type(hermtridiagonal_${s1}$_type) :: A
291+ !! Corresponding HermTridiagonal matrix.
292+ end function
293+
294+ module function initialize_hermtridiagonal_impure_${s1}$(dv, ev, err) result(A)
295+ !! Construct a `hermtridiagonal` matrix from the rank-1 arrays
296+ !! `dl`, `dv` and `du`.
297+ ${t1}$, intent(in) :: dv(:), ev(:)
298+ !! Tridiagonal matrix elements.
299+ type(linalg_state_type), intent(out) :: err
300+ !! Error handling.
301+ type(hermtridiagonal_${s1}$_type) :: A
302+ !! Corresponding HermTridiagonal matrix.
303+ end function
304+
305+ module function initialize_constant_hermtridiagonal_impure_${s1}$(dv, ev, n, err) result(A)
306+ !! Construct a `hermtridiagonal` matrix with constant elements.
307+ ${t1}$, intent(in) :: dv, ev
308+ !! Tridiagonal matrix elements.
309+ integer(ilp), intent(in) :: n
310+ !! Matrix dimension.
311+ type(linalg_state_type), intent(out) :: err
312+ !! Error handling.
313+ type(Hermtridiagonal_${s1}$_type) :: A
314+ !! Corresponding HermTridiagonal matrix.
315+ end function
316+ #:endfor
317+ end interface
318+
225319 !----------------------------------
226320 !----- -----
227321 !----- LINEAR ALGEBRA -----
0 commit comments