lapack-0.2.3.1: Numerical Linear Algebra using LAPACK

Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Matrix

Synopsis

Documentation

type Full vert horiz height width = Array (Full vert horiz height width) Source #

type General height width = Array (General height width) Source #

type Tall height width = Array (Tall height width) Source #

type Wide height width = Array (Wide height width) Source #

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

adjoint :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Full horiz vert width height a Source #

conjugate transpose

Problem: adjoint a # a is always square, but how to convince the type checker to choose the Square type? Anser: Use Hermitian.toSquare $ Hermitian.covariance a instead.

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

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

caseTallWide :: (C vert, C horiz, C height, C width) => Full vert horiz height width a -> Either (Tall height width a) (Wide height width a) Source #

Square matrices will be classified as Tall.

fromScalar :: Storable a => a -> General () () a Source #

toScalar :: Storable a => General () () a -> a Source #

fromList :: (C height, C width, Storable a) => height -> width -> [a] -> General height width a Source #

mapExtent :: (C vertA, C horizA) => (C vertB, C horizB) => Map vertA horizA vertB horizB height width -> Full vertA horizA height width a -> Full vertB horizB height width a Source #

fromFull :: (C vert, C horiz) => Full vert horiz height width a -> General height width a Source #

generalizeTall :: (C vert, C horiz) => Full vert Small height width a -> Full vert horiz height width a Source #

generalizeWide :: (C vert, C horiz) => Full Small horiz height width a -> Full vert horiz height width a Source #

mapHeight :: (C heightA, C heightB, GeneralTallWide vert horiz, GeneralTallWide horiz vert) => (heightA -> heightB) -> Full vert horiz heightA width a -> Full vert horiz heightB width a Source #

The number of rows must be maintained by the height mapping function.

mapWidth :: (C widthA, C widthB, GeneralTallWide vert horiz, GeneralTallWide horiz vert) => (widthA -> widthB) -> Full vert horiz height widthA a -> Full vert horiz height widthB a Source #

The number of columns must be maintained by the width mapping function.

identity :: (C sh, Floating a) => sh -> General sh sh a Source #

diagonal :: (C sh, Floating a) => Vector sh a -> General sh sh a Source #

fromRowsNonEmpty :: (C width, Eq width, Storable a) => T [] (Vector width a) -> General ZeroInt width a Source #

fromRowArray :: (C height, C width, Eq width, Storable a) => width -> Array height (Vector width a) -> General height width a Source #

fromRows :: (C width, Eq width, Storable a) => width -> [Vector width a] -> General ZeroInt width a Source #

fromColumnsNonEmpty :: (C height, Eq height, Storable a) => T [] (Vector height a) -> General height ZeroInt a Source #

fromColumnArray :: (C height, Eq height, C width, Storable a) => height -> Array width (Vector height a) -> General height width a Source #

fromColumns :: (C height, Eq height, Storable a) => height -> [Vector height a] -> General height ZeroInt a Source #

singleRow :: Order -> Vector width a -> General () width a Source #

singleColumn :: Order -> Vector height a -> General height () a Source #

flattenRow :: General () width a -> Vector width a Source #

flattenColumn :: General height () a -> Vector height a Source #

liftRow :: Order -> (Vector height0 a -> Vector height1 b) -> General () height0 a -> General () height1 b Source #

liftColumn :: Order -> (Vector height0 a -> Vector height1 b) -> General height0 () a -> General height1 () b Source #

unliftRow :: Order -> (General () height0 a -> General () height1 b) -> Vector height0 a -> Vector height1 b Source #

unliftColumn :: Order -> (General height0 () a -> General height1 () b) -> Vector height0 a -> Vector height1 b Source #

toRows :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> [Vector width a] Source #

toColumns :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> [Vector height a] Source #

toRowArray :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Array height (Vector width a) Source #

toColumnArray :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Array width (Vector height a) Source #

takeRow :: (C vert, C horiz, Indexed height, C width, Index height ~ ix, Floating a) => Full vert horiz height width a -> ix -> Vector width a Source #

takeColumn :: (C vert, C horiz, C height, Indexed width, Index width ~ ix, Floating a) => Full vert horiz height width a -> ix -> Vector height a Source #

takeRows :: (C vert, C width, Floating a) => Int -> Full vert Big ZeroInt width a -> Full vert Big ZeroInt width a Source #

takeColumns :: (C horiz, C height, Floating a) => Int -> Full Big horiz height ZeroInt a -> Full Big horiz height ZeroInt a Source #

takeEqually :: (C vert, C horiz, Floating a) => Int -> Full vert horiz ZeroInt ZeroInt a -> Full vert horiz ZeroInt ZeroInt a Source #

Take a left-top aligned square or as much as possible of it. The advantange of this function is that it maintains the matrix size relation, e.g. Square remains Square, Tall remains Tall.

dropRows :: (C vert, C width, Floating a) => Int -> Full vert Big ZeroInt width a -> Full vert Big ZeroInt width a Source #

dropColumns :: (C horiz, C height, Floating a) => Int -> Full Big horiz height ZeroInt a -> Full Big horiz height ZeroInt a Source #

dropEqually :: (C vert, C horiz, Floating a) => Int -> Full vert horiz ZeroInt ZeroInt a -> Full vert horiz ZeroInt ZeroInt a Source #

Drop the same number of top-most rows and left-most columns. The advantange of this function is that it maintains the matrix size relation, e.g. Square remains Square, Tall remains Tall.

takeTopRows :: (C vert, C height0, C height1, C width, Floating a) => Full vert Big (height0 :+: height1) width a -> Full vert Big height0 width a Source #

takeBottomRows :: (C vert, C height0, C height1, C width, Floating a) => Full vert Big (height0 :+: height1) width a -> Full vert Big height1 width a Source #

takeLeftColumns :: (C vert, C height, C width0, C width1, Floating a) => Full Big vert height (width0 :+: width1) a -> Full Big vert height width0 a Source #

takeRightColumns :: (C vert, C height, C width0, C width1, Floating a) => Full Big vert height (width0 :+: width1) a -> Full Big vert height width1 a Source #

takeRowArray :: (Indexed height, C width, C sh, Floating a) => Array sh (Index height) -> General height width a -> General sh width a Source #

takeColumnArray :: (C height, Indexed width, C sh, Floating a) => Array sh (Index width) -> General height width a -> General height sh a Source #

swapRows :: (C vert, C horiz, Indexed height, C width, Floating a) => Index height -> Index height -> Full vert horiz height width a -> Full vert horiz height width a Source #

swapColumns :: (C vert, C horiz, C height, Indexed width, Floating a) => Index width -> Index width -> Full vert horiz height width a -> Full vert horiz height width a Source #

reverseRows :: (C vert, C horiz, C width, Floating a) => Full vert horiz ZeroInt width a -> Full vert horiz ZeroInt width a Source #

reverseColumns :: (C vert, C horiz, C height, Floating a) => Full vert horiz height ZeroInt a -> Full vert horiz height ZeroInt a Source #

fromRowMajor :: (C height, C width, Floating a) => Array (height, width) a -> General height width a Source #

toRowMajor :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Array (height, width) a Source #

flatten :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Vector ZeroInt a Source #

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

adaptOrder :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Full vert horiz height width a -> Full vert horiz height width a Source #

adaptOrder x y contains the data of y with the layout of x.

(|||) :: (C vert, C height, Eq height, C widtha, C widthb, Floating a) => Full vert Big height widtha a -> Full vert Big height widthb a -> Full vert Big height (widtha :+: widthb) a infixl 3 Source #

(===) :: (C horiz, C width, Eq width, C heighta, C heightb, Floating a) => Full Big horiz heighta width a -> Full Big horiz heightb width a -> Full Big horiz (heighta :+: heightb) width a infixl 2 Source #

tensorProduct :: (C height, Eq height, C width, Eq width, Floating a) => Order -> Vector height a -> Vector width a -> General height width a Source #

tensorProduct order x y = singleColumn order x <#> singleRow order y

outer :: (C height, Eq height, C width, Eq width, Floating a) => Order -> Vector height a -> Vector width a -> General height width a Source #

outer order x y = tensorProduct order x (Vector.conjugate y)

sumRank1 :: (C height, Eq height, C width, Eq width, Floating a) => (height, width) -> [(a, (Vector height a, Vector width a))] -> General height width a Source #

type family RealOf x Source #

Instances
type RealOf Double Source # 
Instance details

Defined in Numeric.LAPACK.Scalar

type RealOf Float Source # 
Instance details

Defined in Numeric.LAPACK.Scalar

type RealOf (Complex a) Source # 
Instance details

Defined in Numeric.LAPACK.Scalar

type RealOf (Complex a) = a

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

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

rowSums :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Vector height a Source #

columnSums :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Vector width a Source #

scaleRows :: (C vert, C horiz, C height, Eq height, C width, Floating a) => Vector height a -> Full vert horiz height width a -> Full vert horiz height width a Source #

scaleColumns :: (C vert, C horiz, C height, C width, Eq width, Floating a) => Vector width a -> Full vert horiz height width a -> Full vert horiz height width a Source #

scaleRowsComplex :: (C vert, C horiz, C height, Eq height, C width, Real a) => Vector height a -> Full vert horiz height width (Complex a) -> Full vert horiz height width (Complex a) Source #

scaleColumnsComplex :: (C vert, C horiz, C height, C width, Eq width, Real a) => Vector width a -> Full vert horiz height width (Complex a) -> Full vert horiz height width (Complex a) Source #

scaleRowsReal :: (C vert, C horiz, C height, Eq height, C width, Floating a) => Vector height (RealOf a) -> Full vert horiz height width a -> Full vert horiz height width a Source #

scaleColumnsReal :: (C vert, C horiz, C height, C width, Eq width, Floating a) => Vector width (RealOf a) -> Full vert horiz height width a -> Full vert horiz height width a Source #

multiply :: (C vert, C horiz, C height, C fuse, Eq fuse, C width, Floating a) => Full vert horiz height fuse a -> Full vert horiz fuse width a -> Full vert horiz height width a Source #

Multiply two matrices with the same dimension constraints. E.g. you can multiply General and General matrices, or Square and Square matrices. It may seem to be overly strict in this respect, but that design supports type inference the best. You can lift the restrictions by generalizing operands with toFull, fromFull, generalizeTall or generalizeWide.

multiplyVector :: (C vert, C horiz, C height, C width, Eq width, Floating a) => Full vert horiz height width a -> Vector width a -> Vector height a Source #

class (C shapeA, C shapeB) => Multiply shapeA shapeB Source #

This class allows to multiply two matrices of arbitrary special features and returns the most special matrix type possible. At the first glance, this is handy. At the second glance, this has some problems. First of all, we may refine the types in future and then multiplication may return a different, more special type than before. Second, if you write code with polymorphic matrix types, then <#> may leave you with constraints like ExtentPriv.Multiply vert vert ~ vert. That constraint is always fulfilled but the compiler cannot infer that. Because of these problems you may instead consider using specialised multiply functions from the various modules for production use. Btw. MultiplyLeft and MultiplyRight are much less problematic, because the input and output are always dense vectors.

Minimal complete definition

(<#>)

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

Defined in Numeric.LAPACK.Matrix.Multiply

Associated Types

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

Methods

(<#>) :: Floating a => Array (Hermitian shapeA) a -> Array (Hermitian shapeB) a -> Array (Multiplied (Hermitian shapeA) (Hermitian shapeB)) a Source #

(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.Multiply

Associated Types

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

Methods

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

(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.Multiply

Associated Types

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

Methods

(<#>) :: Floating a => Array (BandedHermitian offDiagA sizeA) a -> Array (BandedHermitian offDiagB sizeB) a -> Array (Multiplied (BandedHermitian offDiagA sizeA) (BandedHermitian offDiagB sizeB)) a Source #

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(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.Multiply

Associated Types

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

Methods

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

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(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.Multiply

Associated Types

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

Methods

(<#>) :: 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 Source #

(<#>) :: (Multiply shapeA shapeB, Floating a) => Array shapeA a -> Array shapeB a -> Array (Multiplied shapeA shapeB) a infixl 7 Source #

class C shape => MultiplyLeft shape Source #

Minimal complete definition

(<#)

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

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

(<#) :: Floating a => Vector (HeightOf (Hermitian shape)) a -> Array (Hermitian shape) a -> Vector (WidthOf (Hermitian shape)) a Source #

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

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

(<#) :: Floating a => Vector (HeightOf (BandedHermitian offDiag size)) a -> Array (BandedHermitian offDiag size) a -> Vector (WidthOf (BandedHermitian offDiag size)) a Source #

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

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

(<#) :: 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 Source #

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

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

(<#) :: 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 Source #

(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.Multiply

Methods

(<#) :: 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 Source #

(<#) :: (MultiplyLeft shape, Floating a) => Vector (HeightOf shape) a -> Array shape a -> Vector (WidthOf shape) a infixl 7 Source #

class C shape => MultiplyRight shape Source #

Minimal complete definition

(#>)

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

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

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

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

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

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

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

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

(#>) :: 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 Source #

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

Defined in Numeric.LAPACK.Matrix.Multiply

Methods

(#>) :: 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 Source #

(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.Multiply

Methods

(#>) :: 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 Source #

(#>) :: (MultiplyRight shape, Floating a) => Array shape a -> Vector (WidthOf shape) a -> Vector (HeightOf shape) a infixr 7 Source #

class Box sh => Indexed sh Source #

Minimal complete definition

(#!)

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

Defined in Numeric.LAPACK.Matrix.Indexed

Methods

(#!) :: Floating a => Array (Hermitian size) a -> (Index (HeightOf (Hermitian size)), Index (WidthOf (Hermitian size))) -> a Source #

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

Defined in Numeric.LAPACK.Matrix.Indexed

Methods

(#!) :: Floating a => Array (BandedHermitian off size) a -> (Index (HeightOf (BandedHermitian off size)), Index (WidthOf (BandedHermitian off size))) -> a Source #

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

Defined in Numeric.LAPACK.Matrix.Indexed

Methods

(#!) :: Floating a => Array (Triangular lo diag up size) a -> (Index (HeightOf (Triangular lo diag up size)), Index (WidthOf (Triangular lo diag up size))) -> a Source #

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

Defined in Numeric.LAPACK.Matrix.Indexed

Methods

(#!) :: Floating a => Array (Full vert horiz height width) a -> (Index (HeightOf (Full vert horiz height width)), Index (WidthOf (Full vert horiz height width))) -> a Source #

(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.Indexed

Methods

(#!) :: Floating a => Array (Banded sub super vert horiz height width) a -> (Index (HeightOf (Banded sub super vert horiz height width)), Index (WidthOf (Banded sub super vert horiz height width))) -> a Source #

(#!) :: (Indexed sh, Floating a) => Array sh a -> (Index (HeightOf sh), Index (WidthOf sh)) -> a infixl 9 Source #

class C shape => Solve shape Source #

Minimal complete definition

solve

Instances
C shape => Solve (Hermitian shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Methods

solve :: (Floating a, HeightOf (Hermitian shape) ~ height, Eq height, C horiz, C vert, C nrhs) => Array (Hermitian shape) a -> Full vert horiz height nrhs a -> Full vert horiz height nrhs a Source #

(Natural offDiag, C size) => Solve (BandedHermitian offDiag size) Source #

There is no solver for indefinite matrices. Thus the instance will fail for indefinite but solvable systems.

Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Methods

solve :: (Floating a, HeightOf (BandedHermitian offDiag size) ~ height, Eq height, C horiz, C vert, C nrhs) => Array (BandedHermitian offDiag size) a -> Full vert horiz height nrhs a -> Full vert horiz height nrhs a Source #

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

Defined in Numeric.LAPACK.Matrix.Divide

Methods

solve :: (Floating a, HeightOf (Triangular lo diag up shape) ~ height, Eq height, C horiz, C vert, C nrhs) => Array (Triangular lo diag up shape) a -> Full vert horiz height nrhs a -> Full vert horiz height nrhs a Source #

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

Defined in Numeric.LAPACK.Matrix.Divide

Methods

solve :: (Floating a, HeightOf (Full vert horiz height width) ~ height0, Eq height0, C horiz0, C vert0, C nrhs) => Array (Full vert horiz height width) a -> Full0 vert0 horiz0 height0 nrhs a -> Full0 vert0 horiz0 height0 nrhs a Source #

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

Defined in Numeric.LAPACK.Matrix.Divide

Methods

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

solve :: (Solve shape, Floating a, HeightOf shape ~ height, Eq height, C horiz, C vert, C nrhs) => Array shape a -> Full vert horiz height nrhs a -> Full vert horiz height nrhs a Source #

solveVector :: (Solve shape, HeightOf shape ~ height, Eq height, Floating a) => Array shape a -> Vector height a -> Vector height a Source #

class Solve shape => Inverse shape Source #

Minimal complete definition

inverse

Instances
C shape => Inverse (Hermitian shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Methods

inverse :: Floating a => Array (Hermitian shape) a -> Array (Hermitian shape) a Source #

(DiagUpLo lo up, TriDiag diag, C shape) => Inverse (Triangular lo diag up shape) Source # 
Instance details

Defined in Numeric.LAPACK.Matrix.Divide

Methods

inverse :: Floating a => Array (Triangular lo diag up shape) a -> Array (Triangular lo diag up shape) a Source #

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

Defined in Numeric.LAPACK.Matrix.Divide

Methods

inverse :: Floating a => Array (Full vert horiz height width) a -> Array (Full vert horiz height width) a Source #

inverse :: (Inverse shape, Floating a) => Array shape a -> Array shape a Source #