lapack-0.2.3: Numerical Linear Algebra using LAPACK

Safe HaskellNone

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 aSource

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

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 shapeSource

width :: Box shape => Array shape a -> WidthOf shapeSource

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.

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

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 aSource

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

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

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

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

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 aSource

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

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

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

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

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

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

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

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

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

singleRow :: Order -> Vector width a -> General () width aSource

singleColumn :: Order -> Vector height a -> General height () aSource

flattenRow :: General () width a -> Vector width aSource

flattenColumn :: General height () a -> Vector height aSource

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

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

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

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

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 aSource

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

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

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

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

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 aSource

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

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

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 aSource

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

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

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

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

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

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 aSource

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 aSource

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

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

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

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

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

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

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 aSource

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) aSource

(===) :: (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 aSource

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

 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 aSource

 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 aSource

type family RealOf x Source

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 aSource

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 aSource

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

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

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 aSource

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 aSource

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 aSource

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 aSource

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 aSource

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 aSource

class (C shapeA, C shapeB) => Multiply shapeA shapeB whereSource

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.

Methods

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

Instances

(C shapeA, ~ * shapeA shapeB, Eq shapeB) => Multiply (Hermitian shapeA) (Hermitian shapeB) 
(C vert, C horiz, C size, ~ * size height, Eq height, C width) => Multiply (Hermitian size) (Full vert horiz height width) 
(Natural offDiagA, Natural offDiagB, C sizeA, ~ * sizeA sizeB, C sizeB, Eq sizeB) => Multiply (BandedHermitian offDiagA sizeA) (BandedHermitian offDiagB sizeB) 
(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) 
(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) 
(C vert, C horiz, C size, ~ * size width, Eq width, C height) => Multiply (Full vert horiz height width) (Hermitian size) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 

class C shape => MultiplyLeft shape whereSource

Methods

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

Instances

(Eq shape, C shape) => MultiplyLeft (Hermitian shape) 
(Natural offDiag, C size, Eq size) => MultiplyLeft (BandedHermitian offDiag size) 
(Content lo, Content up, TriDiag diag, Eq shape, C shape) => MultiplyLeft (Triangular lo diag up shape) 
(C vert, C horiz, Eq height, C width, C height) => MultiplyLeft (Full vert horiz height width) 
(Natural sub, Natural super, C vert, C horiz, Eq height, C width, C height) => MultiplyLeft (Banded sub super vert horiz height width) 

class C shape => MultiplyRight shape whereSource

Methods

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

Instances

(Eq shape, C shape) => MultiplyRight (Hermitian shape) 
(Natural offDiag, C size, Eq size) => MultiplyRight (BandedHermitian offDiag size) 
(Content lo, Content up, TriDiag diag, Eq shape, C shape) => MultiplyRight (Triangular lo diag up shape) 
(C vert, C horiz, Eq width, C width, C height) => MultiplyRight (Full vert horiz height width) 
(Natural sub, Natural super, C vert, C horiz, Eq width, C width, C height) => MultiplyRight (Banded sub super vert horiz height width) 

class Box sh => Indexed sh whereSource

Methods

(#!) :: Floating a => Array sh a -> (Index (HeightOf sh), Index (WidthOf sh)) -> aSource

Instances

Indexed size => Indexed (Hermitian size) 
(Natural off, Indexed size) => Indexed (BandedHermitian off size) 
(Content lo, TriDiag diag, Content up, Indexed size) => Indexed (Triangular lo diag up size) 
(C vert, C horiz, Indexed height, Indexed width) => Indexed (Full vert horiz height width) 
(Natural sub, Natural super, C vert, C horiz, Indexed height, Indexed width) => Indexed (Banded sub super vert horiz height width) 

class C shape => Solve shape whereSource

Methods

solve :: (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 aSource

Instances

C shape => Solve (Hermitian shape) 
(Natural offDiag, C size) => Solve (BandedHermitian offDiag size)

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

(Content lo, Content up, TriDiag diag, C shape) => Solve (Triangular lo diag up shape) 
(~ * vert Small, ~ * horiz Small, C width, C height, ~ * height width) => Solve (Full vert horiz height width) 
(Natural sub, Natural super, ~ * vert Small, ~ * horiz Small, C width, C height, ~ * width height) => Solve (Banded sub super vert horiz height width) 

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

class Solve shape => Inverse shape whereSource

Methods

inverse :: Floating a => Array shape a -> Array shape aSource

Instances

C shape => Inverse (Hermitian shape) 
(DiagUpLo lo up, TriDiag diag, C shape) => Inverse (Triangular lo diag up shape) 
(~ * vert Small, ~ * horiz Small, C width, C height, ~ * height width) => Inverse (Full vert horiz height width)