easytensor-2.1.1.1: Pure, type-indexed haskell vector, matrix, and tensor library.
Safe HaskellNone
LanguageHaskell2010

Numeric.Matrix.Bidiagonal

Synopsis

Documentation

data BiDiag (t :: Type) (n :: Nat) (m :: Nat) Source #

Decomposition of a matrix \( A = U B V^\intercal \) such that \( U \) and \( V \) are orthogonal and \( B \) is bidiagonal.

Constructors

BiDiag 

Fields

  • bdU :: Matrix t n n

    \( U \) left orthogonal matrix

  • bdUDet :: Scalar t

    A shortcut for evaluating a determinant of \( |U| = \pm 1 \)

  • bdAlpha :: Vector t (Min n m)

    Main diagonal of \( B \)

  • bdBeta :: Vector t (Min n m)

    First upper diagonal of \( B \); its last element equals zero if \( n \geq m \)

  • bdV :: Matrix t m m

    \( B \) left orthogonal matrix

  • bdVDet :: Scalar t

    A shortcut for evaluating a determinant of \( |V| = \pm 1 \)

Instances

Instances details
(Eq t, PrimBytes t, KnownDim n, KnownDim m, KnownDim (Min n m), KnownBackend t '[Min n m]) => Eq (BiDiag t n m) Source # 
Instance details

Defined in Numeric.Matrix.Bidiagonal

Methods

(==) :: BiDiag t n m -> BiDiag t n m -> Bool #

(/=) :: BiDiag t n m -> BiDiag t n m -> Bool #

(Show t, PrimBytes t, KnownDim n, KnownDim m, KnownDim (Min n m)) => Show (BiDiag t n m) Source # 
Instance details

Defined in Numeric.Matrix.Bidiagonal

Methods

showsPrec :: Int -> BiDiag t n m -> ShowS #

show :: BiDiag t n m -> String #

showList :: [BiDiag t n m] -> ShowS #

biDiag :: forall (t :: Type) (n :: Nat) (m :: Nat). (PrimBytes t, Num t) => Dims '[n, m] -> Vector t (Min n m) -> Vector t (Min n m) -> Matrix t n m Source #

Put two vectors on the main and first upper diagonal.

bidiagonalHouseholder :: forall (t :: Type) (n :: Nat) (m :: Nat). (PrimBytes t, Ord t, Epsilon t, KnownDim n, KnownDim m) => Matrix t n m -> BiDiag t n m Source #

Decompose a matrix \( A = U B V^\intercal \) such that ( U ) and \( V \) are orthogonal and \( B \) is bidiagonal.

The first returned number