lapack-0.3: Numerical Linear Algebra using LAPACK

Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Matrix.Shape

Synopsis

Documentation

type General height width = Full Big Big height width Source #

type Tall height width = Full Big Small height width Source #

type Wide height width = Full Small Big height width Source #

type Square size = Full Small Small size size Source #

data Full vert horiz height width Source #

Constructors

Full 

Fields

Instances
(C vert, C horiz, C size, size ~ height, Eq height, C width) => Multiply (Hermitian size) (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Hermitian size) (Full vert horiz height width) :: Type

Methods

matrixMatrix :: Floating a => Array (Hermitian size) a -> Array (Full vert horiz height width) a -> Array (Multiplied (Hermitian size) (Full vert horiz height width)) a

(Natural offDiag, C vert, C horiz, C size, size ~ height, Eq height, C width, Eq width) => Multiply (BandedHermitian offDiag size) (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (BandedHermitian offDiag size) (Full vert horiz height width) :: Type

Methods

matrixMatrix :: Floating a => Array (BandedHermitian offDiag size) a -> Array (Full vert horiz height width) a -> Array (Multiplied (BandedHermitian offDiag size) (Full vert horiz height width)) a

(C vert, C horiz, Eq height, Eq width) => Eq (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

(==) :: Full vert horiz height width -> Full vert horiz height width -> Bool #

(/=) :: Full vert horiz height width -> Full vert horiz height width -> Bool #

(C vert, C horiz, Show height, Show width) => Show (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

showsPrec :: Int -> Full vert horiz height width -> ShowS #

show :: Full vert horiz height width -> String #

showList :: [Full vert horiz height width] -> ShowS #

(C vert, C horiz, C height, C width) => C (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

size :: Full vert horiz height width -> Int #

uncheckedSize :: Full vert horiz height width -> Int #

(C vert, C horiz, Indexed height, Indexed width) => Indexed (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type Index (Full vert horiz height width) :: Type #

Methods

indices :: Full vert horiz height width -> [Index (Full vert horiz height width)] #

offset :: Full vert horiz height width -> Index (Full vert horiz height width) -> Int #

uncheckedOffset :: Full vert horiz height width -> Index (Full vert horiz height width) -> Int #

inBounds :: Full vert horiz height width -> Index (Full vert horiz height width) -> Bool #

sizeOffset :: Full vert horiz height width -> (Int, Index (Full vert horiz height width) -> Int) #

uncheckedSizeOffset :: Full vert horiz height width -> (Int, Index (Full vert horiz height width) -> Int) #

(C vert, C horiz, InvIndexed height, InvIndexed width) => InvIndexed (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

indexFromOffset :: Full vert horiz height width -> Int -> Index (Full vert horiz height width) #

uncheckedIndexFromOffset :: Full vert horiz height width -> Int -> Index (Full vert horiz height width) #

(C vert, C horiz, NFData height, NFData width) => NFData (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

rnf :: Full vert horiz height width -> () #

(C vert, C horiz, C height, C width) => Box (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (Full vert horiz height width) :: Type Source #

type WidthOf (Full vert horiz height width) :: Type Source #

Methods

height :: Full vert horiz height width -> HeightOf (Full vert horiz height width) Source #

width :: Full vert horiz height width -> WidthOf (Full vert horiz height width) Source #

(C vert, C horiz, C height, C width) => FormatArray (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Format

Methods

formatArray :: (Floating a, Output out) => String -> Array (Full vert horiz height width) a -> out Source #

(vert ~ Small, horiz ~ Small, C height, Eq height, height ~ width) => MultiplySquare (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

transposableSquare :: (HeightOf (Full vert horiz height width) ~ height0, Eq height0, C width0, C horiz0, C vert0, Floating a) => Transposition -> Array (Full vert horiz height width) a -> Full0 vert0 horiz0 height0 width0 a -> Full0 vert0 horiz0 height0 width0 a

squareFull :: (HeightOf (Full vert horiz height width) ~ height0, Eq height0, C width0, C horiz0, C vert0, Floating a) => Array (Full vert horiz height width) a -> Full0 vert0 horiz0 height0 width0 a -> Full0 vert0 horiz0 height0 width0 a

fullSquare :: (WidthOf (Full vert horiz height width) ~ width0, Eq width0, C height0, C horiz0, C vert0, Floating a) => Full0 vert0 horiz0 height0 width0 a -> Array (Full vert horiz height width) a -> Full0 vert0 horiz0 height0 width0 a

(C vert, C horiz, Eq height, C width, C height) => MultiplyLeft (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

vectorMatrix :: Floating a => Vector (HeightOf (Full vert horiz height width)) a -> Array (Full vert horiz height width) a -> Vector (WidthOf (Full vert horiz height width)) a

(C vert, C horiz, Eq width, C width, C height) => MultiplyRight (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

matrixVector :: Floating a => Array (Full vert horiz height width) a -> Vector (WidthOf (Full vert horiz height width)) a -> Vector (HeightOf (Full vert horiz height width)) a

(C vert, C horiz, C height, Eq height, C width, Eq width) => Additive (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

add :: Floating a => ArrayMatrix (Full vert horiz height width) a -> ArrayMatrix (Full vert horiz height width) a -> ArrayMatrix (Full vert horiz height width) a Source #

sub :: Floating a => ArrayMatrix (Full vert horiz height width) a -> ArrayMatrix (Full vert horiz height width) a -> ArrayMatrix (Full vert horiz height width) a Source #

(C vert, C horiz, C height, C width) => ShapeOrder (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

forceOrder :: Floating a => Order -> ArrayMatrix (Full vert horiz height width) a -> ArrayMatrix (Full vert horiz height width) a Source #

shapeOrder :: Full vert horiz height width -> Order Source #

(C vert, C horiz, C height, C width) => Homogeneous (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

zero :: Floating a => Full vert horiz height width -> ArrayMatrix (Full vert horiz height width) a Source #

negate :: Floating a => ArrayMatrix (Full vert horiz height width) a -> ArrayMatrix (Full vert horiz height width) a Source #

scaleReal :: Floating a => RealOf a -> ArrayMatrix (Full vert horiz height width) a -> ArrayMatrix (Full vert horiz height width) a Source #

(C vert, C horiz, C height, C width) => Complex (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

conjugate :: Floating a => ArrayMatrix (Full vert horiz height width) a -> ArrayMatrix (Full vert horiz height width) a

fromReal :: Floating a => ArrayMatrix (Full vert horiz height width) (RealOf a) -> ArrayMatrix (Full vert horiz height width) a

toComplex :: Floating a => ArrayMatrix (Full vert horiz height width) a -> ArrayMatrix (Full vert horiz height width) (ComplexOf a)

(C vert, C horiz, C size, size ~ width, Eq width, C height) => Multiply (Full vert horiz height width) (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Full vert horiz height width) (Hermitian size) :: Type

Methods

matrixMatrix :: Floating a => Array (Full vert horiz height width) a -> Array (Hermitian size) a -> Array (Multiplied (Full vert horiz height width) (Hermitian size)) a

(Natural offDiag, C vert, C horiz, C size, size ~ width, Eq width, C height, Eq height) => Multiply (Full vert horiz height width) (BandedHermitian offDiag size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Full vert horiz height width) (BandedHermitian offDiag size) :: Type

Methods

matrixMatrix :: Floating a => Array (Full vert horiz height width) a -> Array (BandedHermitian offDiag size) a -> Array (Multiplied (Full vert horiz height width) (BandedHermitian offDiag size)) a

(Content lo, Content up, TriDiag diag, C vert, C horiz, C size, size ~ height, Eq height, C width) => Multiply (Triangular lo diag up size) (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Triangular lo diag up size) (Full vert horiz height width) :: Type

Methods

matrixMatrix :: Floating a => Array (Triangular lo diag up size) a -> Array (Full vert horiz height width) a -> Array (Multiplied (Triangular lo diag up size) (Full vert horiz height width)) a

(Content lo, Content up, TriDiag diag, C vert, C horiz, C size, size ~ width, Eq width, C height) => Multiply (Full vert horiz height width) (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Full vert horiz height width) (Triangular lo diag up size) :: Type

Methods

matrixMatrix :: Floating a => Array (Full vert horiz height width) a -> Array (Triangular lo diag up size) a -> Array (Multiplied (Full vert horiz height width) (Triangular lo diag up size)) a

(C heightA, C widthA, C widthB, widthA ~ heightB, Eq heightB, C vertA, C horizA, C vertB, C horizB) => Multiply (Full vertA horizA heightA widthA) (Full vertB horizB heightB widthB) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Full vertA horizA heightA widthA) (Full vertB horizB heightB widthB) :: Type

Methods

matrixMatrix :: Floating a => Array (Full vertA horizA heightA widthA) a -> Array (Full vertB horizB heightB widthB) a -> Array (Multiplied (Full vertA horizA heightA widthA) (Full vertB horizB heightB widthB)) a

(Natural sub, Natural super, C vertA, C horizA, C vertB, C horizB, C heightA, C widthA, C widthB, widthA ~ heightB, Eq heightB) => Multiply (Full vertA horizA heightA widthA) (Banded sub super vertB horizB heightB widthB) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Full vertA horizA heightA widthA) (Banded sub super vertB horizB heightB widthB) :: Type

Methods

matrixMatrix :: Floating a => Array (Full vertA horizA heightA widthA) a -> Array (Banded sub super vertB horizB heightB widthB) a -> Array (Multiplied (Full vertA horizA heightA widthA) (Banded sub super vertB horizB heightB widthB)) a

(Natural sub, Natural super, C vertA, C horizA, C vertB, C horizB, C heightA, C widthA, C widthB, widthA ~ heightB, Eq heightB) => Multiply (Banded sub super vertA horizA heightA widthA) (Full vertB horizB heightB widthB) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Banded sub super vertA horizA heightA widthA) (Full vertB horizB heightB widthB) :: Type

Methods

matrixMatrix :: Floating a => Array (Banded sub super vertA horizA heightA widthA) a -> Array (Full vertB horizB heightB widthB) a -> Array (Multiplied (Banded sub super vertA horizA heightA widthA) (Full vertB horizB heightB widthB)) a

type Index (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type Index (Full vert horiz height width) = (Index height, Index width)
type HeightOf (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (Full vert horiz height width) = height
type WidthOf (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (Full vert horiz height width) = width

fullHeight :: (C vert, C horiz) => Full vert horiz height width -> height Source #

fullWidth :: (C vert, C horiz) => Full vert horiz height width -> width Source #

data Order Source #

Constructors

RowMajor 
ColumnMajor 
Instances
Eq Order Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

(==) :: Order -> Order -> Bool #

(/=) :: Order -> Order -> Bool #

Show Order Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

NFData Order Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

rnf :: Order -> () #

general :: Order -> height -> width -> General height width Source #

square :: Order -> sh -> Square sh Source #

wide :: (C height, C width) => Order -> height -> width -> Wide height width Source #

tall :: (C height, C width) => Order -> height -> width -> Tall height width Source #

data Split lower vert horiz height width Source #

Instances
(C vert, C horiz, Eq lower, Eq height, Eq width) => Eq (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

(==) :: Split lower vert horiz height width -> Split lower vert horiz height width -> Bool #

(/=) :: Split lower vert horiz height width -> Split lower vert horiz height width -> Bool #

(C vert, C horiz, Show lower, Show height, Show width) => Show (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

showsPrec :: Int -> Split lower vert horiz height width -> ShowS #

show :: Split lower vert horiz height width -> String #

showList :: [Split lower vert horiz height width] -> ShowS #

(Eq lower, C vert, C horiz, C height, C width) => C (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

size :: Split lower vert horiz height width -> Int #

uncheckedSize :: Split lower vert horiz height width -> Int #

(Eq lower, C vert, C horiz, Indexed height, Indexed width) => Indexed (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type Index (Split lower vert horiz height width) :: Type #

Methods

indices :: Split lower vert horiz height width -> [Index (Split lower vert horiz height width)] #

offset :: Split lower vert horiz height width -> Index (Split lower vert horiz height width) -> Int #

uncheckedOffset :: Split lower vert horiz height width -> Index (Split lower vert horiz height width) -> Int #

inBounds :: Split lower vert horiz height width -> Index (Split lower vert horiz height width) -> Bool #

sizeOffset :: Split lower vert horiz height width -> (Int, Index (Split lower vert horiz height width) -> Int) #

uncheckedSizeOffset :: Split lower vert horiz height width -> (Int, Index (Split lower vert horiz height width) -> Int) #

(Eq lower, C vert, C horiz, InvIndexed height, InvIndexed width) => InvIndexed (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

indexFromOffset :: Split lower vert horiz height width -> Int -> Index (Split lower vert horiz height width) #

uncheckedIndexFromOffset :: Split lower vert horiz height width -> Int -> Index (Split lower vert horiz height width) #

(NFData lower, C vert, C horiz, NFData height, NFData width) => NFData (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

rnf :: Split lower vert horiz height width -> () #

(Eq lower, C vert, C horiz, C height, C width) => Box (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (Split lower vert horiz height width) :: Type Source #

type WidthOf (Split lower vert horiz height width) :: Type Source #

Methods

height :: Split lower vert horiz height width -> HeightOf (Split lower vert horiz height width) Source #

width :: Split lower vert horiz height width -> WidthOf (Split lower vert horiz height width) Source #

(Eq lower, C vert, C horiz, C height, C width) => FormatArray (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Format

Methods

formatArray :: (Floating a, Output out) => String -> Array (Split lower vert horiz height width) a -> out Source #

type Index (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type Index (Split lower vert horiz height width) = (Either lower Triangle, (Index height, Index width))
type HeightOf (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (Split lower vert horiz height width) = height
type WidthOf (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (Split lower vert horiz height width) = width

type SplitGeneral lower height width = Split lower Big Big height width Source #

data Triangle Source #

Constructors

Triangle 
Instances
Eq Triangle Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Show Triangle Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

NFData Triangle Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

rnf :: Triangle -> () #

data Reflector Source #

Constructors

Reflector 
Instances
Eq Reflector Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Show Reflector Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

NFData Reflector Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

rnf :: Reflector -> () #

splitGeneral :: lower -> Order -> height -> width -> SplitGeneral lower height width Source #

splitFromFull :: lower -> Full vert horiz height width -> Split lower vert horiz height width Source #

data Hermitian size Source #

Store the upper triangular half of a real symmetric or complex Hermitian matrix.

Constructors

Hermitian 

Fields

Instances
Eq size => Eq (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

(==) :: Hermitian size -> Hermitian size -> Bool #

(/=) :: Hermitian size -> Hermitian size -> Bool #

Show size => Show (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

showsPrec :: Int -> Hermitian size -> ShowS #

show :: Hermitian size -> String #

showList :: [Hermitian size] -> ShowS #

C size => C (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

size :: Hermitian size -> Int #

uncheckedSize :: Hermitian size -> Int #

Indexed size => Indexed (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type Index (Hermitian size) :: Type #

Methods

indices :: Hermitian size -> [Index (Hermitian size)] #

offset :: Hermitian size -> Index (Hermitian size) -> Int #

uncheckedOffset :: Hermitian size -> Index (Hermitian size) -> Int #

inBounds :: Hermitian size -> Index (Hermitian size) -> Bool #

sizeOffset :: Hermitian size -> (Int, Index (Hermitian size) -> Int) #

uncheckedSizeOffset :: Hermitian size -> (Int, Index (Hermitian size) -> Int) #

InvIndexed size => InvIndexed (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

NFData size => NFData (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

rnf :: Hermitian size -> () #

C size => Box (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (Hermitian size) :: Type Source #

type WidthOf (Hermitian size) :: Type Source #

Methods

height :: Hermitian size -> HeightOf (Hermitian size) Source #

width :: Hermitian size -> WidthOf (Hermitian size) Source #

C size => FormatArray (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Format

Methods

formatArray :: (Floating a, Output out) => String -> Array (Hermitian size) a -> out Source #

(Eq shape, C shape) => MultiplySquare (Hermitian shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

transposableSquare :: (HeightOf (Hermitian shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Array (Hermitian shape) a -> Full vert horiz height width a -> Full vert horiz height width a

squareFull :: (HeightOf (Hermitian shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Array (Hermitian shape) a -> Full vert horiz height width a -> Full vert horiz height width a

fullSquare :: (WidthOf (Hermitian shape) ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Array (Hermitian shape) a -> Full vert horiz height width a

(Eq shape, C shape) => MultiplyLeft (Hermitian shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

vectorMatrix :: Floating a => Vector (HeightOf (Hermitian shape)) a -> Array (Hermitian shape) a -> Vector (WidthOf (Hermitian shape)) a

(Eq shape, C shape) => MultiplyRight (Hermitian shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

matrixVector :: Floating a => Array (Hermitian shape) a -> Vector (WidthOf (Hermitian shape)) a -> Vector (HeightOf (Hermitian shape)) a

(C size, Eq size) => Additive (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

add :: Floating a => ArrayMatrix (Hermitian size) a -> ArrayMatrix (Hermitian size) a -> ArrayMatrix (Hermitian size) a Source #

sub :: Floating a => ArrayMatrix (Hermitian size) a -> ArrayMatrix (Hermitian size) a -> ArrayMatrix (Hermitian size) a Source #

C size => ShapeOrder (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

C size => Homogeneous (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

C size => Complex (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

(C shapeA, shapeA ~ shapeB, Eq shapeB) => Multiply (Hermitian shapeA) (Hermitian shapeB) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Hermitian shapeA) (Hermitian shapeB) :: Type

Methods

matrixMatrix :: Floating a => Array (Hermitian shapeA) a -> Array (Hermitian shapeB) a -> Array (Multiplied (Hermitian shapeA) (Hermitian shapeB)) a

(C vert, C horiz, C size, size ~ height, Eq height, C width) => Multiply (Hermitian size) (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Hermitian size) (Full vert horiz height width) :: Type

Methods

matrixMatrix :: Floating a => Array (Hermitian size) a -> Array (Full vert horiz height width) a -> Array (Multiplied (Hermitian size) (Full vert horiz height width)) a

(C vert, C horiz, C size, size ~ width, Eq width, C height) => Multiply (Full vert horiz height width) (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Full vert horiz height width) (Hermitian size) :: Type

Methods

matrixMatrix :: Floating a => Array (Full vert horiz height width) a -> Array (Hermitian size) a -> Array (Multiplied (Full vert horiz height width) (Hermitian size)) a

type Index (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type Index (Hermitian size) = (Index size, Index size)
type HeightOf (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (Hermitian size) = size
type WidthOf (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (Hermitian size) = size

hermitian :: Order -> size -> Hermitian size Source #

data Triangular lo diag up size Source #

Constructors

Triangular 

Fields

Instances
(Eq diag, Eq lo, Eq up, Eq size) => Eq (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

(==) :: Triangular lo diag up size -> Triangular lo diag up size -> Bool #

(/=) :: Triangular lo diag up size -> Triangular lo diag up size -> Bool #

(Show diag, Show lo, Show up, Show size) => Show (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

showsPrec :: Int -> Triangular lo diag up size -> ShowS #

show :: Triangular lo diag up size -> String #

showList :: [Triangular lo diag up size] -> ShowS #

(Content lo, TriDiag diag, Content up, C size) => C (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

size :: Triangular lo diag up size -> Int #

uncheckedSize :: Triangular lo diag up size -> Int #

(Content lo, TriDiag diag, Content up, Indexed size) => Indexed (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type Index (Triangular lo diag up size) :: Type #

Methods

indices :: Triangular lo diag up size -> [Index (Triangular lo diag up size)] #

offset :: Triangular lo diag up size -> Index (Triangular lo diag up size) -> Int #

uncheckedOffset :: Triangular lo diag up size -> Index (Triangular lo diag up size) -> Int #

inBounds :: Triangular lo diag up size -> Index (Triangular lo diag up size) -> Bool #

sizeOffset :: Triangular lo diag up size -> (Int, Index (Triangular lo diag up size) -> Int) #

uncheckedSizeOffset :: Triangular lo diag up size -> (Int, Index (Triangular lo diag up size) -> Int) #

(Content lo, TriDiag diag, Content up, InvIndexed size) => InvIndexed (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

indexFromOffset :: Triangular lo diag up size -> Int -> Index (Triangular lo diag up size) #

uncheckedIndexFromOffset :: Triangular lo diag up size -> Int -> Index (Triangular lo diag up size) #

(Content lo, TriDiag diag, Content up, NFData size) => NFData (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

rnf :: Triangular lo diag up size -> () #

(Content lo, TriDiag diag, Content up, C size) => Box (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (Triangular lo diag up size) :: Type Source #

type WidthOf (Triangular lo diag up size) :: Type Source #

Methods

height :: Triangular lo diag up size -> HeightOf (Triangular lo diag up size) Source #

width :: Triangular lo diag up size -> WidthOf (Triangular lo diag up size) Source #

(Content lo, Content up, TriDiag diag, C size) => FormatArray (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Format

Methods

formatArray :: (Floating a, Output out) => String -> Array (Triangular lo diag up size) a -> out Source #

(Content lo, Content up, TriDiag diag, Eq shape, C shape) => MultiplySquare (Triangular lo diag up shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

transposableSquare :: (HeightOf (Triangular lo diag up shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Array (Triangular lo diag up shape) a -> Full vert horiz height width a -> Full vert horiz height width a

squareFull :: (HeightOf (Triangular lo diag up shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Array (Triangular lo diag up shape) a -> Full vert horiz height width a -> Full vert horiz height width a

fullSquare :: (WidthOf (Triangular lo diag up shape) ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Array (Triangular lo diag up shape) a -> Full vert horiz height width a

(Content lo, Content up, TriDiag diag, Eq shape, C shape) => MultiplyLeft (Triangular lo diag up shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

vectorMatrix :: Floating a => Vector (HeightOf (Triangular lo diag up shape)) a -> Array (Triangular lo diag up shape) a -> Vector (WidthOf (Triangular lo diag up shape)) a

(Content lo, Content up, TriDiag diag, Eq shape, C shape) => MultiplyRight (Triangular lo diag up shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

matrixVector :: Floating a => Array (Triangular lo diag up shape) a -> Vector (WidthOf (Triangular lo diag up shape)) a -> Vector (HeightOf (Triangular lo diag up shape)) a

(Content lo, Eq lo, NonUnit ~ diag, Content up, Eq up, C size, Eq size) => Additive (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

add :: Floating a => ArrayMatrix (Triangular lo diag up size) a -> ArrayMatrix (Triangular lo diag up size) a -> ArrayMatrix (Triangular lo diag up size) a Source #

sub :: Floating a => ArrayMatrix (Triangular lo diag up size) a -> ArrayMatrix (Triangular lo diag up size) a -> ArrayMatrix (Triangular lo diag up size) a Source #

(Content lo, TriDiag diag, Content up, C size) => ShapeOrder (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

forceOrder :: Floating a => Order -> ArrayMatrix (Triangular lo diag up size) a -> ArrayMatrix (Triangular lo diag up size) a Source #

shapeOrder :: Triangular lo diag up size -> Order Source #

(Content lo, NonUnit ~ diag, Content up, C size) => Homogeneous (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

zero :: Floating a => Triangular lo diag up size -> ArrayMatrix (Triangular lo diag up size) a Source #

negate :: Floating a => ArrayMatrix (Triangular lo diag up size) a -> ArrayMatrix (Triangular lo diag up size) a Source #

scaleReal :: Floating a => RealOf a -> ArrayMatrix (Triangular lo diag up size) a -> ArrayMatrix (Triangular lo diag up size) a Source #

(Content lo, TriDiag diag, Content up, C size) => Complex (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

conjugate :: Floating a => ArrayMatrix (Triangular lo diag up size) a -> ArrayMatrix (Triangular lo diag up size) a

fromReal :: Floating a => ArrayMatrix (Triangular lo diag up size) (RealOf a) -> ArrayMatrix (Triangular lo diag up size) a

toComplex :: Floating a => ArrayMatrix (Triangular lo diag up size) a -> ArrayMatrix (Triangular lo diag up size) (ComplexOf a)

(C sizeA, sizeA ~ sizeB, Eq sizeB, MultiplyTriangular loA upA loB upB, TriDiag diagA, TriDiag diagB) => Multiply (Triangular loA diagA upA sizeA) (Triangular loB diagB upB sizeB) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Triangular loA diagA upA sizeA) (Triangular loB diagB upB sizeB) :: Type

Methods

matrixMatrix :: Floating a => Array (Triangular loA diagA upA sizeA) a -> Array (Triangular loB diagB upB sizeB) a -> Array (Multiplied (Triangular loA diagA upA sizeA) (Triangular loB diagB upB sizeB)) a

(Content lo, Content up, TriDiag diag, C vert, C horiz, C size, size ~ height, Eq height, C width) => Multiply (Triangular lo diag up size) (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Triangular lo diag up size) (Full vert horiz height width) :: Type

Methods

matrixMatrix :: Floating a => Array (Triangular lo diag up size) a -> Array (Full vert horiz height width) a -> Array (Multiplied (Triangular lo diag up size) (Full vert horiz height width)) a

(Content lo, Content up, TriDiag diag, C vert, C horiz, C size, size ~ width, Eq width, C height) => Multiply (Full vert horiz height width) (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Full vert horiz height width) (Triangular lo diag up size) :: Type

Methods

matrixMatrix :: Floating a => Array (Full vert horiz height width) a -> Array (Triangular lo diag up size) a -> Array (Multiplied (Full vert horiz height width) (Triangular lo diag up size)) a

type Index (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type Index (Triangular lo diag up size) = (Index size, Index size)
type HeightOf (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (Triangular lo diag up size) = size
type WidthOf (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (Triangular lo diag up size) = size

type Identity = Triangular Empty Unit Empty Source #

type Diagonal = Triangular Empty NonUnit Empty Source #

type LowerTriangular diag = Triangular Filled diag Empty Source #

type UpperTriangular diag = Triangular Empty diag Filled Source #

type Symmetric = FlexSymmetric NonUnit Source #

diagonal :: Order -> size -> Triangular Empty NonUnit Empty size Source #

symmetric :: Order -> size -> Symmetric size Source #

autoDiag :: TriDiag diag => diag Source #

autoUplo :: (Content lo, Content up) => (lo, up) Source #

type DiagUpLo lo up = (DiagUpLoC lo up, DiagUpLoC up lo) Source #

switchDiagUpLoSym :: (Content lo, Content up) => f Empty Empty -> f Empty Filled -> f Filled Empty -> f Filled Filled -> f lo up Source #

class TriDiag diag Source #

Minimal complete definition

switchTriDiag

Instances
TriDiag NonUnit Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

switchTriDiag :: f Unit -> f NonUnit -> f NonUnit Source #

TriDiag Unit Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

switchTriDiag :: f Unit -> f NonUnit -> f Unit Source #

switchTriDiag :: TriDiag diag => f Unit -> f NonUnit -> f diag Source #

data Unit Source #

Constructors

Unit 
Instances
Eq Unit Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

(==) :: Unit -> Unit -> Bool #

(/=) :: Unit -> Unit -> Bool #

Show Unit Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

showsPrec :: Int -> Unit -> ShowS #

show :: Unit -> String #

showList :: [Unit] -> ShowS #

TriDiag Unit Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

switchTriDiag :: f Unit -> f NonUnit -> f Unit Source #

data NonUnit Source #

Constructors

NonUnit 
Instances
Eq NonUnit Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

(==) :: NonUnit -> NonUnit -> Bool #

(/=) :: NonUnit -> NonUnit -> Bool #

Show NonUnit Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

TriDiag NonUnit Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

switchTriDiag :: f Unit -> f NonUnit -> f NonUnit Source #

data Banded sub super vert horiz height width Source #

Constructors

Banded 

Fields

Instances
(Natural offDiag, Natural sub, Natural super, C vert, C horiz, C size, size ~ height, Eq height, C width, Eq width) => Multiply (BandedHermitian offDiag size) (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (BandedHermitian offDiag size) (Banded sub super vert horiz height width) :: Type

Methods

matrixMatrix :: Floating a => Array (BandedHermitian offDiag size) a -> Array (Banded sub super vert horiz height width) a -> Array (Multiplied (BandedHermitian offDiag size) (Banded sub super vert horiz height width)) a

(Natural sub, Natural super, C vertA, C horizA, C vertB, C horizB, C heightA, C widthA, C widthB, widthA ~ heightB, Eq heightB) => Multiply (Full vertA horizA heightA widthA) (Banded sub super vertB horizB heightB widthB) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Full vertA horizA heightA widthA) (Banded sub super vertB horizB heightB widthB) :: Type

Methods

matrixMatrix :: Floating a => Array (Full vertA horizA heightA widthA) a -> Array (Banded sub super vertB horizB heightB widthB) a -> Array (Multiplied (Full vertA horizA heightA widthA) (Banded sub super vertB horizB heightB widthB)) a

(C vert, C horiz, Eq height, Eq width) => Eq (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

(==) :: Banded sub super vert horiz height width -> Banded sub super vert horiz height width -> Bool #

(/=) :: Banded sub super vert horiz height width -> Banded sub super vert horiz height width -> Bool #

(Natural sub, Natural super, C vert, C horiz, Show height, Show width) => Show (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

showsPrec :: Int -> Banded sub super vert horiz height width -> ShowS #

show :: Banded sub super vert horiz height width -> String #

showList :: [Banded sub super vert horiz height width] -> ShowS #

(Natural sub, Natural super, C vert, C horiz, C height, C width) => C (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

size :: Banded sub super vert horiz height width -> Int #

uncheckedSize :: Banded sub super vert horiz height width -> Int #

(Natural sub, Natural super, C vert, C horiz, Indexed height, Indexed width) => Indexed (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type Index (Banded sub super vert horiz height width) :: Type #

Methods

indices :: Banded sub super vert horiz height width -> [Index (Banded sub super vert horiz height width)] #

offset :: Banded sub super vert horiz height width -> Index (Banded sub super vert horiz height width) -> Int #

uncheckedOffset :: Banded sub super vert horiz height width -> Index (Banded sub super vert horiz height width) -> Int #

inBounds :: Banded sub super vert horiz height width -> Index (Banded sub super vert horiz height width) -> Bool #

sizeOffset :: Banded sub super vert horiz height width -> (Int, Index (Banded sub super vert horiz height width) -> Int) #

uncheckedSizeOffset :: Banded sub super vert horiz height width -> (Int, Index (Banded sub super vert horiz height width) -> Int) #

(Natural sub, Natural super, C vert, C horiz, InvIndexed height, InvIndexed width) => InvIndexed (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

indexFromOffset :: Banded sub super vert horiz height width -> Int -> Index (Banded sub super vert horiz height width) #

uncheckedIndexFromOffset :: Banded sub super vert horiz height width -> Int -> Index (Banded sub super vert horiz height width) #

(Natural sub, Natural super, C vert, C horiz, NFData height, NFData width) => NFData (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

rnf :: Banded sub super vert horiz height width -> () #

(Natural sub, Natural super, C vert, C horiz, C height, C width) => Box (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (Banded sub super vert horiz height width) :: Type Source #

type WidthOf (Banded sub super vert horiz height width) :: Type Source #

Methods

height :: Banded sub super vert horiz height width -> HeightOf (Banded sub super vert horiz height width) Source #

width :: Banded sub super vert horiz height width -> WidthOf (Banded sub super vert horiz height width) Source #

(Natural sub, Natural super, C vert, C horiz, C height, C width) => FormatArray (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Format

Methods

formatArray :: (Floating a, Output out) => String -> Array (Banded sub super vert horiz height width) a -> out Source #

(Natural sub, Natural super, vert ~ Small, horiz ~ Small, C height, Eq height, height ~ width) => MultiplySquare (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

transposableSquare :: (HeightOf (Banded sub super vert horiz height width) ~ height0, Eq height0, C width0, C horiz0, C vert0, Floating a) => Transposition -> Array (Banded sub super vert horiz height width) a -> Full vert0 horiz0 height0 width0 a -> Full vert0 horiz0 height0 width0 a

squareFull :: (HeightOf (Banded sub super vert horiz height width) ~ height0, Eq height0, C width0, C horiz0, C vert0, Floating a) => Array (Banded sub super vert horiz height width) a -> Full vert0 horiz0 height0 width0 a -> Full vert0 horiz0 height0 width0 a

fullSquare :: (WidthOf (Banded sub super vert horiz height width) ~ width0, Eq width0, C height0, C horiz0, C vert0, Floating a) => Full vert0 horiz0 height0 width0 a -> Array (Banded sub super vert horiz height width) a -> Full vert0 horiz0 height0 width0 a

(Natural sub, Natural super, C vert, C horiz, Eq height, C width, C height) => MultiplyLeft (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

vectorMatrix :: Floating a => Vector (HeightOf (Banded sub super vert horiz height width)) a -> Array (Banded sub super vert horiz height width) a -> Vector (WidthOf (Banded sub super vert horiz height width)) a

(Natural sub, Natural super, C vert, C horiz, Eq width, C width, C height) => MultiplyRight (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

matrixVector :: Floating a => Array (Banded sub super vert horiz height width) a -> Vector (WidthOf (Banded sub super vert horiz height width)) a -> Vector (HeightOf (Banded sub super vert horiz height width)) a

(Natural sub, Natural super, C vert, C horiz, C height, C width) => Homogeneous (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

zero :: Floating a => Banded sub super vert horiz height width -> ArrayMatrix (Banded sub super vert horiz height width) a Source #

negate :: Floating a => ArrayMatrix (Banded sub super vert horiz height width) a -> ArrayMatrix (Banded sub super vert horiz height width) a Source #

scaleReal :: Floating a => RealOf a -> ArrayMatrix (Banded sub super vert horiz height width) a -> ArrayMatrix (Banded sub super vert horiz height width) a Source #

(Natural sub, Natural super, C vert, C horiz, C height, C width) => Complex (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

Methods

conjugate :: Floating a => ArrayMatrix (Banded sub super vert horiz height width) a -> ArrayMatrix (Banded sub super vert horiz height width) a

fromReal :: Floating a => ArrayMatrix (Banded sub super vert horiz height width) (RealOf a) -> ArrayMatrix (Banded sub super vert horiz height width) a

toComplex :: Floating a => ArrayMatrix (Banded sub super vert horiz height width) a -> ArrayMatrix (Banded sub super vert horiz height width) (ComplexOf a)

(Natural offDiag, Natural sub, Natural super, C vert, C horiz, C size, size ~ width, Eq width, C height, Eq height) => Multiply (Banded sub super vert horiz height width) (BandedHermitian offDiag size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Banded sub super vert horiz height width) (BandedHermitian offDiag size) :: Type

Methods

matrixMatrix :: Floating a => Array (Banded sub super vert horiz height width) a -> Array (BandedHermitian offDiag size) a -> Array (Multiplied (Banded sub super vert horiz height width) (BandedHermitian offDiag size)) a

(Natural sub, Natural super, C vertA, C horizA, C vertB, C horizB, C heightA, C widthA, C widthB, widthA ~ heightB, Eq heightB) => Multiply (Banded sub super vertA horizA heightA widthA) (Full vertB horizB heightB widthB) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Banded sub super vertA horizA heightA widthA) (Full vertB horizB heightB widthB) :: Type

Methods

matrixMatrix :: Floating a => Array (Banded sub super vertA horizA heightA widthA) a -> Array (Full vertB horizB heightB widthB) a -> Array (Multiplied (Banded sub super vertA horizA heightA widthA) (Full vertB horizB heightB widthB)) a

(Natural subA, Natural superA, Natural subB, Natural superB, C vertA, C horizA, C vertB, C horizB, C heightA, C widthA, C widthB, widthA ~ heightB, Eq heightB) => Multiply (Banded subA superA vertA horizA heightA widthA) (Banded subB superB vertB horizB heightB widthB) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Banded subA superA vertA horizA heightA widthA) (Banded subB superB vertB horizB heightB widthB) :: Type

Methods

matrixMatrix :: Floating a => Array (Banded subA superA vertA horizA heightA widthA) a -> Array (Banded subB superB vertB horizB heightB widthB) a -> Array (Multiplied (Banded subA superA vertA horizA heightA widthA) (Banded subB superB vertB horizB heightB widthB)) a

type Index (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type Index (Banded sub super vert horiz height width) = BandedIndex (Index height) (Index width)
type HeightOf (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (Banded sub super vert horiz height width) = height
type WidthOf (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (Banded sub super vert horiz height width) = width

type BandedGeneral sub super = Banded sub super Big Big Source #

type BandedSquare sub super size = Banded sub super Small Small size size Source #

type BandedLowerTriangular sub size = BandedSquare sub U0 size Source #

type BandedUpperTriangular super size = BandedSquare U0 super size Source #

data BandedIndex row column Source #

Constructors

InsideBox row column 
VertOutsideBox Int column 
HorizOutsideBox row Int 
Instances
(Eq row, Eq column) => Eq (BandedIndex row column) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

(==) :: BandedIndex row column -> BandedIndex row column -> Bool #

(/=) :: BandedIndex row column -> BandedIndex row column -> Bool #

(Show row, Show column) => Show (BandedIndex row column) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

showsPrec :: Int -> BandedIndex row column -> ShowS #

show :: BandedIndex row column -> String #

showList :: [BandedIndex row column] -> ShowS #

bandedGeneral :: (UnaryProxy sub, UnaryProxy super) -> Order -> height -> width -> Banded sub super Big Big height width Source #

bandedSquare :: (UnaryProxy sub, UnaryProxy super) -> Order -> size -> Banded sub super Small Small size size Source #

bandedFromFull :: (UnaryProxy sub, UnaryProxy super) -> Full vert horiz height width -> Banded sub super vert horiz height width Source #

type UnaryProxy a = Proxy (Un a) Source #

addOffDiagonals :: (Natural subA, Natural superA, Natural subB, Natural superB, (subA :+: subB) ~ subC, (superA :+: superB) ~ superC) => (UnaryProxy subA, UnaryProxy superA) -> (UnaryProxy subB, UnaryProxy superB) -> ((Nat subC, Nat superC), (UnaryProxy subC, UnaryProxy superC)) Source #

class Content c Source #

Minimal complete definition

switchContent

data BandedHermitian off size Source #

Instances
Eq size => Eq (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

(==) :: BandedHermitian off size -> BandedHermitian off size -> Bool #

(/=) :: BandedHermitian off size -> BandedHermitian off size -> Bool #

(Natural off, Show size) => Show (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

showsPrec :: Int -> BandedHermitian off size -> ShowS #

show :: BandedHermitian off size -> String #

showList :: [BandedHermitian off size] -> ShowS #

(Natural off, C size) => C (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

size :: BandedHermitian off size -> Int #

uncheckedSize :: BandedHermitian off size -> Int #

(Natural off, Indexed size) => Indexed (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type Index (BandedHermitian off size) :: Type #

Methods

indices :: BandedHermitian off size -> [Index (BandedHermitian off size)] #

offset :: BandedHermitian off size -> Index (BandedHermitian off size) -> Int #

uncheckedOffset :: BandedHermitian off size -> Index (BandedHermitian off size) -> Int #

inBounds :: BandedHermitian off size -> Index (BandedHermitian off size) -> Bool #

sizeOffset :: BandedHermitian off size -> (Int, Index (BandedHermitian off size) -> Int) #

uncheckedSizeOffset :: BandedHermitian off size -> (Int, Index (BandedHermitian off size) -> Int) #

(Natural off, InvIndexed size) => InvIndexed (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

(Natural off, NFData size) => NFData (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Methods

rnf :: BandedHermitian off size -> () #

(Natural off, C size) => Box (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (BandedHermitian off size) :: Type Source #

type WidthOf (BandedHermitian off size) :: Type Source #

Methods

height :: BandedHermitian off size -> HeightOf (BandedHermitian off size) Source #

width :: BandedHermitian off size -> WidthOf (BandedHermitian off size) Source #

(Natural offDiag, C size) => FormatArray (BandedHermitian offDiag size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Format

Methods

formatArray :: (Floating a, Output out) => String -> Array (BandedHermitian offDiag size) a -> out Source #

(Natural offDiag, C size, Eq size) => MultiplySquare (BandedHermitian offDiag size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

transposableSquare :: (HeightOf (BandedHermitian offDiag size) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Array (BandedHermitian offDiag size) a -> Full vert horiz height width a -> Full vert horiz height width a

squareFull :: (HeightOf (BandedHermitian offDiag size) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Array (BandedHermitian offDiag size) a -> Full vert horiz height width a -> Full vert horiz height width a

fullSquare :: (WidthOf (BandedHermitian offDiag size) ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Array (BandedHermitian offDiag size) a -> Full vert horiz height width a

(Natural offDiag, C size, Eq size) => MultiplyLeft (BandedHermitian offDiag size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

vectorMatrix :: Floating a => Vector (HeightOf (BandedHermitian offDiag size)) a -> Array (BandedHermitian offDiag size) a -> Vector (WidthOf (BandedHermitian offDiag size)) a

(Natural offDiag, C size, Eq size) => MultiplyRight (BandedHermitian offDiag size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Methods

matrixVector :: Floating a => Array (BandedHermitian offDiag size) a -> Vector (WidthOf (BandedHermitian offDiag size)) a -> Vector (HeightOf (BandedHermitian offDiag size)) a

(Natural off, C size) => Homogeneous (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

(Natural off, C size) => Complex (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array

(Natural offDiagA, Natural offDiagB, C sizeA, sizeA ~ sizeB, C sizeB, Eq sizeB) => Multiply (BandedHermitian offDiagA sizeA) (BandedHermitian offDiagB sizeB) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (BandedHermitian offDiagA sizeA) (BandedHermitian offDiagB sizeB) :: Type

Methods

matrixMatrix :: Floating a => Array (BandedHermitian offDiagA sizeA) a -> Array (BandedHermitian offDiagB sizeB) a -> Array (Multiplied (BandedHermitian offDiagA sizeA) (BandedHermitian offDiagB sizeB)) a

(Natural offDiag, C vert, C horiz, C size, size ~ height, Eq height, C width, Eq width) => Multiply (BandedHermitian offDiag size) (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (BandedHermitian offDiag size) (Full vert horiz height width) :: Type

Methods

matrixMatrix :: Floating a => Array (BandedHermitian offDiag size) a -> Array (Full vert horiz height width) a -> Array (Multiplied (BandedHermitian offDiag size) (Full vert horiz height width)) a

(Natural offDiag, Natural sub, Natural super, C vert, C horiz, C size, size ~ height, Eq height, C width, Eq width) => Multiply (BandedHermitian offDiag size) (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (BandedHermitian offDiag size) (Banded sub super vert horiz height width) :: Type

Methods

matrixMatrix :: Floating a => Array (BandedHermitian offDiag size) a -> Array (Banded sub super vert horiz height width) a -> Array (Multiplied (BandedHermitian offDiag size) (Banded sub super vert horiz height width)) a

(Natural offDiag, C vert, C horiz, C size, size ~ width, Eq width, C height, Eq height) => Multiply (Full vert horiz height width) (BandedHermitian offDiag size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Full vert horiz height width) (BandedHermitian offDiag size) :: Type

Methods

matrixMatrix :: Floating a => Array (Full vert horiz height width) a -> Array (BandedHermitian offDiag size) a -> Array (Multiplied (Full vert horiz height width) (BandedHermitian offDiag size)) a

(Natural offDiag, Natural sub, Natural super, C vert, C horiz, C size, size ~ width, Eq width, C height, Eq height) => Multiply (Banded sub super vert horiz height width) (BandedHermitian offDiag size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Array.Multiply

Associated Types

type Multiplied (Banded sub super vert horiz height width) (BandedHermitian offDiag size) :: Type

Methods

matrixMatrix :: Floating a => Array (Banded sub super vert horiz height width) a -> Array (BandedHermitian offDiag size) a -> Array (Multiplied (Banded sub super vert horiz height width) (BandedHermitian offDiag size)) a

type Index (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type Index (BandedHermitian off size) = BandedIndex (Index size) (Index size)
type HeightOf (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (BandedHermitian off size) = size
type WidthOf (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (BandedHermitian off size) = size

bandedHermitian :: UnaryProxy off -> Order -> size -> BandedHermitian off size Source #

class C shape => Box shape Source #

Minimal complete definition

height, width

Instances
C size => Box (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (Hermitian size) :: Type Source #

type WidthOf (Hermitian size) :: Type Source #

Methods

height :: Hermitian size -> HeightOf (Hermitian size) Source #

width :: Hermitian size -> WidthOf (Hermitian size) Source #

(Natural off, C size) => Box (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (BandedHermitian off size) :: Type Source #

type WidthOf (BandedHermitian off size) :: Type Source #

Methods

height :: BandedHermitian off size -> HeightOf (BandedHermitian off size) Source #

width :: BandedHermitian off size -> WidthOf (BandedHermitian off size) Source #

(Content lo, TriDiag diag, Content up, C size) => Box (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (Triangular lo diag up size) :: Type Source #

type WidthOf (Triangular lo diag up size) :: Type Source #

Methods

height :: Triangular lo diag up size -> HeightOf (Triangular lo diag up size) Source #

width :: Triangular lo diag up size -> WidthOf (Triangular lo diag up size) Source #

(C vert, C horiz, C height, C width) => Box (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (Full vert horiz height width) :: Type Source #

type WidthOf (Full vert horiz height width) :: Type Source #

Methods

height :: Full vert horiz height width -> HeightOf (Full vert horiz height width) Source #

width :: Full vert horiz height width -> WidthOf (Full vert horiz height width) Source #

(Eq lower, C vert, C horiz, C height, C width) => Box (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (Split lower vert horiz height width) :: Type Source #

type WidthOf (Split lower vert horiz height width) :: Type Source #

Methods

height :: Split lower vert horiz height width -> HeightOf (Split lower vert horiz height width) Source #

width :: Split lower vert horiz height width -> WidthOf (Split lower vert horiz height width) Source #

(Natural sub, Natural super, C vert, C horiz, C height, C width) => Box (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

Associated Types

type HeightOf (Banded sub super vert horiz height width) :: Type Source #

type WidthOf (Banded sub super vert horiz height width) :: Type Source #

Methods

height :: Banded sub super vert horiz height width -> HeightOf (Banded sub super vert horiz height width) Source #

width :: Banded sub super vert horiz height width -> WidthOf (Banded sub super vert horiz height width) Source #

type family HeightOf shape Source #

Instances
type HeightOf (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (Hermitian size) = size
type HeightOf (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (BandedHermitian off size) = size
type HeightOf (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (Triangular lo diag up size) = size
type HeightOf (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (Full vert horiz height width) = height
type HeightOf (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (Split lower vert horiz height width) = height
type HeightOf (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type HeightOf (Banded sub super vert horiz height width) = height

type family WidthOf shape Source #

Instances
type WidthOf (Hermitian size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (Hermitian size) = size
type WidthOf (BandedHermitian off size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (BandedHermitian off size) = size
type WidthOf (Triangular lo diag up size) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (Triangular lo diag up size) = size
type WidthOf (Full vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (Full vert horiz height width) = width
type WidthOf (Split lower vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (Split lower vert horiz height width) = width
type WidthOf (Banded sub super vert horiz height width) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Shape.Private

type WidthOf (Banded sub super vert horiz height width) = width

height :: Box shape => shape -> HeightOf shape Source #

width :: Box shape => shape -> WidthOf shape Source #