Safe Haskell | None |
---|
- data family Matrix typ a
- type Full vert horiz height width = ArrayMatrix (Full vert horiz height width)
- type General height width = ArrayMatrix (General height width)
- type Tall height width = ArrayMatrix (Tall height width)
- type Wide height width = ArrayMatrix (Wide height width)
- type Square sh = ArrayMatrix (Square sh)
- type Triangular lo diag up sh = ArrayMatrix (Triangular lo diag up sh)
- type Upper sh = FlexUpper NonUnit sh
- type Lower sh = FlexLower NonUnit sh
- type Diagonal sh = FlexDiagonal NonUnit sh
- type Symmetric sh = FlexSymmetric NonUnit sh
- type Hermitian sh = ArrayMatrix (Hermitian sh)
- type Permutation sh = Matrix (Permutation sh)
- type ShapeInt = ZeroBased Int
- shapeInt :: Int -> ShapeInt
- transpose :: (C vert, C horiz) => Full vert horiz height width a -> Full horiz vert width height a
- adjoint :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Full horiz vert width height a
- class Box typ where
- indices :: (Box typ, HeightOf typ ~ height, Indexed height, WidthOf typ ~ width, Indexed width) => Matrix typ a -> [(Index height, Index width)]
- reshape :: (C sh0, C sh1) => sh1 -> ArrayMatrix sh0 a -> ArrayMatrix sh1 a
- mapShape :: (C sh0, C sh1) => (sh0 -> sh1) -> ArrayMatrix sh0 a -> ArrayMatrix sh1 a
- caseTallWide :: (C vert, C horiz, C height, C width) => Full vert horiz height width a -> Either (Tall height width a) (Wide height width a)
- fromScalar :: Storable a => a -> General () () a
- toScalar :: Storable a => General () () a -> a
- fromList :: (C height, C width, Storable a) => height -> width -> [a] -> General height width a
- 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
- fromFull :: (C vert, C horiz) => Full vert horiz height width a -> General height width a
- asGeneral :: General height width a -> General height width a
- asTall :: Tall height width a -> Tall height width a
- asWide :: Wide height width a -> Wide height width a
- tallFromGeneral :: (C height, C width, Storable a) => General height width a -> Tall height width a
- wideFromGeneral :: (C height, C width, Storable a) => General height width a -> Wide height width a
- generalizeTall :: (C vert, C horiz) => Full vert Small height width a -> Full vert horiz height width a
- generalizeWide :: (C vert, C horiz) => Full Small horiz height width a -> Full vert horiz height width a
- 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
- 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
- identity :: (C sh, Floating a) => sh -> General sh sh a
- diagonal :: (C sh, Floating a) => Vector sh a -> General sh sh a
- fromRowsNonEmpty :: (C width, Eq width, Storable a) => T [] (Vector width a) -> General ShapeInt width a
- fromRowArray :: (C height, C width, Eq width, Storable a) => width -> Array height (Vector width a) -> General height width a
- fromRows :: (C width, Eq width, Storable a) => width -> [Vector width a] -> General ShapeInt width a
- fromRowsNonEmptyContainer :: (f ~ T g, C g, C width, Eq width, Storable a) => f (Vector width a) -> General (Shape f) width a
- fromRowContainer :: (C f, C width, Eq width, Storable a) => width -> f (Vector width a) -> General (Shape f) width a
- fromColumnsNonEmpty :: (C height, Eq height, Storable a) => T [] (Vector height a) -> General height ShapeInt a
- fromColumnArray :: (C height, Eq height, C width, Storable a) => height -> Array width (Vector height a) -> General height width a
- fromColumns :: (C height, Eq height, Storable a) => height -> [Vector height a] -> General height ShapeInt a
- fromColumnsNonEmptyContainer :: (f ~ T g, C g, C height, Eq height, Storable a) => f (Vector height a) -> General height (Shape f) a
- fromColumnContainer :: (C f, C height, Eq height, Storable a) => height -> f (Vector height a) -> General height (Shape f) a
- singleRow :: Order -> Vector width a -> General () width a
- singleColumn :: Order -> Vector height a -> General height () a
- flattenRow :: General () width a -> Vector width a
- flattenColumn :: General height () a -> Vector height a
- liftRow :: Order -> (Vector height0 a -> Vector height1 b) -> General () height0 a -> General () height1 b
- liftColumn :: Order -> (Vector height0 a -> Vector height1 b) -> General height0 () a -> General height1 () b
- unliftRow :: Order -> (General () height0 a -> General () height1 b) -> Vector height0 a -> Vector height1 b
- unliftColumn :: Order -> (General height0 () a -> General height1 () b) -> Vector height0 a -> Vector height1 b
- toRows :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> [Vector width a]
- toColumns :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> [Vector height a]
- toRowArray :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Array height (Vector width a)
- toColumnArray :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Array width (Vector height a)
- toRowContainer :: (C vert, C horiz, C f, C width, Floating a) => Full vert horiz (Shape f) width a -> f (Vector width a)
- toColumnContainer :: (C vert, C horiz, C height, C f, Floating a) => Full vert horiz height (Shape f) a -> f (Vector height a)
- takeRow :: (C vert, C horiz, Indexed height, C width, Index height ~ ix, Floating a) => Full vert horiz height width a -> ix -> Vector width a
- takeColumn :: (C vert, C horiz, C height, Indexed width, Index width ~ ix, Floating a) => Full vert horiz height width a -> ix -> Vector height a
- takeRows :: (C vert, C width, Floating a) => Int -> Full vert Big ShapeInt width a -> Full vert Big ShapeInt width a
- takeColumns :: (C horiz, C height, Floating a) => Int -> Full Big horiz height ShapeInt a -> Full Big horiz height ShapeInt a
- takeEqually :: (C vert, C horiz, Floating a) => Int -> Full vert horiz ShapeInt ShapeInt a -> Full vert horiz ShapeInt ShapeInt a
- dropRows :: (C vert, C width, Floating a) => Int -> Full vert Big ShapeInt width a -> Full vert Big ShapeInt width a
- dropColumns :: (C horiz, C height, Floating a) => Int -> Full Big horiz height ShapeInt a -> Full Big horiz height ShapeInt a
- dropEqually :: (C vert, C horiz, Floating a) => Int -> Full vert horiz ShapeInt ShapeInt a -> Full vert horiz ShapeInt ShapeInt a
- takeTop :: (C vert, C height0, C height1, C width, Floating a) => Full vert Big (height0 :+: height1) width a -> Full vert Big height0 width a
- takeBottom :: (C vert, C height0, C height1, C width, Floating a) => Full vert Big (height0 :+: height1) width a -> Full vert Big height1 width a
- takeLeft :: (C vert, C height, C width0, C width1, Floating a) => Full Big vert height (width0 :+: width1) a -> Full Big vert height width0 a
- takeRight :: (C vert, C height, C width0, C width1, Floating a) => Full Big vert height (width0 :+: width1) a -> Full Big vert height width1 a
- takeRowArray :: (Indexed height, C width, C sh, Floating a) => Array sh (Index height) -> General height width a -> General sh width a
- takeColumnArray :: (C height, Indexed width, C sh, Floating a) => Array sh (Index width) -> General height width a -> General height sh a
- 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
- 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
- reverseRows :: (C vert, C horiz, C width, Floating a) => Full vert horiz ShapeInt width a -> Full vert horiz ShapeInt width a
- reverseColumns :: (C vert, C horiz, C height, Floating a) => Full vert horiz height ShapeInt a -> Full vert horiz height ShapeInt a
- fromRowMajor :: (C height, C width, Floating a) => Array (height, width) a -> General height width a
- toRowMajor :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Array (height, width) a
- forceOrder :: (ShapeOrder shape, Floating a) => Order -> ArrayMatrix shape a -> ArrayMatrix shape a
- adaptOrder :: (ShapeOrder shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
- data OrderBias
- leftBias :: OrderBias
- rightBias :: OrderBias
- contiguousBias :: OrderBias
- (|||) :: (C vertA, C vertB, C vertC, Append vertA vertB ~ vertC, C height, Eq height, C widthA, C widthB, Floating a) => Full vertA Big height widthA a -> Full vertB Big height widthB a -> Full vertC Big height (widthA :+: widthB) a
- beside :: (C vertA, C vertB, C vertC, C height, Eq height, C widthA, C widthB, Floating a) => OrderBias -> AppendMode vertA vertB vertC height widthA widthB -> Full vertA Big height widthA a -> Full vertB Big height widthB a -> Full vertC Big height (widthA :+: widthB) a
- (===) :: (C horizA, C horizB, C horizC, Append horizA horizB ~ horizC, C width, Eq width, C heightA, C heightB, Floating a) => Full Big horizA heightA width a -> Full Big horizB heightB width a -> Full Big horizC (heightA :+: heightB) width a
- above :: (C horizA, C horizB, C horizC, C width, Eq width, C heightA, C heightB, Floating a) => OrderBias -> AppendMode horizA horizB horizC width heightA heightB -> Full Big horizA heightA width a -> Full Big horizB heightB width a -> Full Big horizC (heightA :+: heightB) width a
- (|*-) :: (C height, Eq height, C width, Eq width, Floating a) => Vector height a -> Vector width a -> General height width a
- tensorProduct :: (C height, Eq height, C width, Eq width, Floating a) => Order -> Vector height a -> Vector width a -> General height width a
- outer :: (C height, Eq height, C width, Eq width, Floating a) => Order -> Vector height a -> Vector width a -> General height width a
- kronecker :: (C vert, C horiz, C heightA, C widthA, C heightB, C widthB, Floating a) => Full vert horiz heightA widthA a -> Full vert horiz heightB widthB a -> Full vert horiz (heightA, heightB) (widthA, widthB) a
- sumRank1 :: (C height, Eq height, C width, Eq width, Floating a) => (height, width) -> [(a, (Vector height a, Vector width a))] -> General height width a
- map :: (C vert, C horiz, C height, C width, Storable a, Storable b) => (a -> b) -> Full vert horiz height width a -> Full vert horiz height width b
- class Complex typ where
- class SquareShape typ where
- identityFrom :: (SquareShape shape, ShapeOrder shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a
- identityFromHeight :: (ShapeOrder shape, Box shape, HeightOf shape ~ HeightOf typ, SquareShape typ, Floating a) => ArrayMatrix shape a -> Matrix typ a
- identityFromWidth :: (ShapeOrder shape, Box shape, WidthOf shape ~ HeightOf typ, SquareShape typ, Floating a) => ArrayMatrix shape a -> Matrix typ a
- trace :: (SquareShape typ, HeightOf typ ~ sh, C sh, Floating a) => Matrix typ a -> a
- type family RealOf x
- rowSums :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Vector height a
- columnSums :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Vector width a
- rowArgAbsMaximums :: (C vert, C horiz, C height, InvIndexed width, Index width ~ ix, Storable ix, Floating a) => Full vert horiz height width a -> (Vector height ix, Vector height a)
- columnArgAbsMaximums :: (C vert, C horiz, InvIndexed height, C width, Index height ~ ix, Storable ix, Floating a) => Full vert horiz height width a -> (Vector width ix, Vector width a)
- 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
- 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
- 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
- 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
- (\*#) :: (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
- (#*\) :: (C vert, C horiz, C height, C width, Eq width, Floating a) => Full vert horiz height width a -> Vector width a -> Full vert horiz height width a
- (\\#) :: (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
- (#/\) :: (C vert, C horiz, C height, C width, Eq width, Floating a) => Full vert horiz height width a -> Vector width a -> Full vert horiz height width a
- 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
- 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
- zero :: (Homogeneous shape, Floating a) => shape -> ArrayMatrix shape a
- negate :: (Homogeneous shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a
- scale :: (Scale shape, Floating a) => a -> ArrayMatrix shape a -> ArrayMatrix shape a
- scaleReal :: (Homogeneous shape, Floating a) => RealOf a -> ArrayMatrix shape a -> ArrayMatrix shape a
- scaleRealReal :: (Homogeneous shape, Real a) => a -> ArrayMatrix shape a -> ArrayMatrix shape a
- (.*#) :: (Scale shape, Floating a) => a -> ArrayMatrix shape a -> ArrayMatrix shape a
- add :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
- sub :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
- (#+#) :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
- (#-#) :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
- class (Box typA, Box typB) => Multiply typA typB
- (#*#) :: (Multiply typA typB, Floating a) => Matrix typA a -> Matrix typB a -> Matrix (Multiplied typA typB) a
- class Box typ => MultiplyVector typ
- (#*|) :: (MultiplyVector typ, WidthOf typ ~ width, Eq width, Floating a) => Matrix typ a -> Vector width a -> Vector (HeightOf typ) a
- (-*#) :: (MultiplyVector typ, HeightOf typ ~ height, Eq height, Floating a) => Vector height a -> Matrix typ a -> Vector (WidthOf typ) a
- class (Box typ, HeightOf typ ~ WidthOf typ) => MultiplySquare typ
- multiplySquare :: (MultiplySquare typ, HeightOf typ ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a
- class (Box typ, HeightOf typ ~ WidthOf typ) => Power typ where
- (##*#) :: (MultiplySquare typ, WidthOf typ ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width a
- (#*##) :: (MultiplySquare typ, HeightOf typ ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a
- class Box typ => Indexed typ where
- class (Box typ, HeightOf typ ~ WidthOf typ) => Determinant typ where
- determinant :: Floating a => Matrix typ a -> a
- class (Box typ, HeightOf typ ~ WidthOf typ) => Solve typ where
- solve :: (HeightOf typ ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a
- solveRight :: (HeightOf typ ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a
- solveLeft :: (WidthOf typ ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width a
- (##/#) :: (Solve typ, WidthOf typ ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width a
- (#\##) :: (Solve typ, HeightOf typ ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width a
- solveVector :: (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Transposition -> Matrix typ a -> Vector height a -> Vector height a
- (-/#) :: (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Vector height a -> Matrix typ a -> Vector height a
- (#\|) :: (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Matrix typ a -> Vector height a -> Vector height a
- class (Solve typ, Power typ) => Inverse typ where
- data Transposition
Documentation
type Full vert horiz height width = ArrayMatrix (Full vert horiz height width)Source
type General height width = ArrayMatrix (General height width)Source
type Tall height width = ArrayMatrix (Tall height width)Source
type Wide height width = ArrayMatrix (Wide height width)Source
type Square sh = ArrayMatrix (Square sh)Source
type Triangular lo diag up sh = ArrayMatrix (Triangular lo diag up sh)Source
type Diagonal sh = FlexDiagonal NonUnit shSource
type Symmetric sh = FlexSymmetric NonUnit shSource
type Hermitian sh = ArrayMatrix (Hermitian sh)Source
type Permutation sh = Matrix (Permutation sh)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.gramian a
instead.
indices :: (Box typ, HeightOf typ ~ height, Indexed height, WidthOf typ ~ width, Indexed width) => Matrix typ a -> [(Index height, Index width)]Source
reshape :: (C sh0, C sh1) => sh1 -> ArrayMatrix sh0 a -> ArrayMatrix sh1 aSource
mapShape :: (C sh0, C sh1) => (sh0 -> sh1) -> ArrayMatrix sh0 a -> ArrayMatrix sh1 aSource
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
tallFromGeneral :: (C height, C width, Storable a) => General height width a -> Tall height width aSource
wideFromGeneral :: (C height, C width, Storable a) => General height width a -> Wide 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.
fromRowsNonEmpty :: (C width, Eq width, Storable a) => T [] (Vector width a) -> General ShapeInt 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 ShapeInt width aSource
fromRowsNonEmptyContainer :: (f ~ T g, C g, C width, Eq width, Storable a) => f (Vector width a) -> General (Shape f) width aSource
fromRowContainer :: (C f, C width, Eq width, Storable a) => width -> f (Vector width a) -> General (Shape f) width aSource
fromColumnsNonEmpty :: (C height, Eq height, Storable a) => T [] (Vector height a) -> General height ShapeInt 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 ShapeInt aSource
fromColumnsNonEmptyContainer :: (f ~ T g, C g, C height, Eq height, Storable a) => f (Vector height a) -> General height (Shape f) aSource
fromColumnContainer :: (C f, C height, Eq height, Storable a) => height -> f (Vector height a) -> General height (Shape f) 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
toRowContainer :: (C vert, C horiz, C f, C width, Floating a) => Full vert horiz (Shape f) width a -> f (Vector width a)Source
toColumnContainer :: (C vert, C horiz, C height, C f, Floating a) => Full vert horiz height (Shape f) a -> f (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 ShapeInt width a -> Full vert Big ShapeInt width aSource
takeColumns :: (C horiz, C height, Floating a) => Int -> Full Big horiz height ShapeInt a -> Full Big horiz height ShapeInt aSource
takeEqually :: (C vert, C horiz, Floating a) => Int -> Full vert horiz ShapeInt ShapeInt a -> Full vert horiz ShapeInt ShapeInt 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 ShapeInt width a -> Full vert Big ShapeInt width aSource
dropColumns :: (C horiz, C height, Floating a) => Int -> Full Big horiz height ShapeInt a -> Full Big horiz height ShapeInt aSource
dropEqually :: (C vert, C horiz, Floating a) => Int -> Full vert horiz ShapeInt ShapeInt a -> Full vert horiz ShapeInt ShapeInt 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.
takeTop :: (C vert, C height0, C height1, C width, Floating a) => Full vert Big (height0 :+: height1) width a -> Full vert Big height0 width aSource
takeBottom :: (C vert, C height0, C height1, C width, Floating a) => Full vert Big (height0 :+: height1) width a -> Full vert Big height1 width aSource
takeLeft :: (C vert, C height, C width0, C width1, Floating a) => Full Big vert height (width0 :+: width1) a -> Full Big vert height width0 aSource
takeRight :: (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
The function is optimized for blocks of consecutive rows. For scattered rows in column major order the function has quite ugly memory access patterns.
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 ShapeInt width a -> Full vert horiz ShapeInt width aSource
reverseColumns :: (C vert, C horiz, C height, Floating a) => Full vert horiz height ShapeInt a -> Full vert horiz height ShapeInt 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
forceOrder :: (ShapeOrder shape, Floating a) => Order -> ArrayMatrix shape a -> ArrayMatrix shape aSource
adaptOrder :: (ShapeOrder shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape aSource
adaptOrder x y
contains the data of y
with the layout of x
.
contiguousBias :: OrderBiasSource
Choose element order such that, if possible,
one part can be copied as one block.
For above
this means that RowMajor
is chosen
whenever at least one operand is RowMajor
and ColumnMajor
is chosen when both operands are ColumnMajor
.
(|||) :: (C vertA, C vertB, C vertC, Append vertA vertB ~ vertC, C height, Eq height, C widthA, C widthB, Floating a) => Full vertA Big height widthA a -> Full vertB Big height widthB a -> Full vertC Big height (widthA :+: widthB) aSource
beside :: (C vertA, C vertB, C vertC, C height, Eq height, C widthA, C widthB, Floating a) => OrderBias -> AppendMode vertA vertB vertC height widthA widthB -> Full vertA Big height widthA a -> Full vertB Big height widthB a -> Full vertC Big height (widthA :+: widthB) aSource
(===) :: (C horizA, C horizB, C horizC, Append horizA horizB ~ horizC, C width, Eq width, C heightA, C heightB, Floating a) => Full Big horizA heightA width a -> Full Big horizB heightB width a -> Full Big horizC (heightA :+: heightB) width aSource
above :: (C horizA, C horizB, C horizC, C width, Eq width, C heightA, C heightB, Floating a) => OrderBias -> AppendMode horizA horizB horizC width heightA heightB -> Full Big horizA heightA width a -> Full Big horizB heightB width a -> Full Big horizC (heightA :+: heightB) width aSource
(|*-) :: (C height, Eq height, C width, Eq width, Floating a) => Vector height a -> Vector width a -> General height 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)
kronecker :: (C vert, C horiz, C heightA, C widthA, C heightB, C widthB, Floating a) => Full vert horiz heightA widthA a -> Full vert horiz heightB widthB a -> Full vert horiz (heightA, heightB) (widthA, widthB) aSource
sumRank1 :: (C height, Eq height, C width, Eq width, Floating a) => (height, width) -> [(a, (Vector height a, Vector width a))] -> General height width aSource
map :: (C vert, C horiz, C height, C width, Storable a, Storable b) => (a -> b) -> Full vert horiz height width a -> Full vert horiz height width bSource
class SquareShape typ whereSource
toSquare :: (HeightOf typ ~ sh, Floating a) => Matrix typ a -> Square sh aSource
takeDiagonal :: (HeightOf typ ~ sh, Floating a) => Matrix typ a -> Vector sh aSource
C sh => SquareShape (Permutation sh) | |
C sh => SquareShape (Scale sh) | |
SquareShape sh => SquareShape (Array sh) |
identityFrom :: (SquareShape shape, ShapeOrder shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape aSource
identityFromHeight :: (ShapeOrder shape, Box shape, HeightOf shape ~ HeightOf typ, SquareShape typ, Floating a) => ArrayMatrix shape a -> Matrix typ aSource
identityFromWidth :: (ShapeOrder shape, Box shape, WidthOf shape ~ HeightOf typ, SquareShape typ, Floating a) => ArrayMatrix shape a -> Matrix typ 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
rowArgAbsMaximums :: (C vert, C horiz, C height, InvIndexed width, Index width ~ ix, Storable ix, Floating a) => Full vert horiz height width a -> (Vector height ix, Vector height a)Source
columnArgAbsMaximums :: (C vert, C horiz, InvIndexed height, C width, Index height ~ ix, Storable ix, Floating a) => Full vert horiz height width a -> (Vector width ix, 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 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
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
(\*#) :: (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
(#*\) :: (C vert, C horiz, C height, C width, Eq width, Floating a) => Full vert horiz height width a -> Vector width a -> Full vert horiz height width aSource
(\\#) :: (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
(#/\) :: (C vert, C horiz, C height, C width, Eq width, Floating a) => Full vert horiz height width a -> Vector 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
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
zero :: (Homogeneous shape, Floating a) => shape -> ArrayMatrix shape aSource
negate :: (Homogeneous shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape aSource
scale :: (Scale shape, Floating a) => a -> ArrayMatrix shape a -> ArrayMatrix shape aSource
scaleReal :: (Homogeneous shape, Floating a) => RealOf a -> ArrayMatrix shape a -> ArrayMatrix shape aSource
scaleRealReal :: (Homogeneous shape, Real a) => a -> ArrayMatrix shape a -> ArrayMatrix shape aSource
(.*#) :: (Scale shape, Floating a) => a -> ArrayMatrix shape a -> ArrayMatrix shape aSource
add :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape aSource
sub :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape aSource
(#+#) :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape aSource
(#-#) :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape aSource
class (Box typA, Box typB) => Multiply typA typB Source
(C shapeA, Eq shapeA, ~ * shapeA shapeB, C shapeB) => Multiply (Permutation shapeA) (Permutation shapeB) | |
(C shapeA, Eq shapeA, ~ * shapeA (HeightOf shapeB), Box shapeB, Scale shapeB) => Multiply (Scale shapeA) (Array shapeB) | |
(C shapeA, Eq shapeA, ~ * shapeA shapeB, C shapeB) => Multiply (Scale shapeA) (Scale shapeB) | |
(Box shapeA, Scale shapeA, ~ * (WidthOf shapeA) shapeB, C shapeB, Eq shapeB) => Multiply (Array shapeA) (Scale shapeB) | |
(Box shapeA, Box shapeB, Multiply shapeA shapeB) => Multiply (Array shapeA) (Array shapeB) |
(#*#) :: (Multiply typA typB, Floating a) => Matrix typA a -> Matrix typB a -> Matrix (Multiplied typA typB) aSource
class Box typ => MultiplyVector typ Source
C shape => MultiplyVector (Permutation shape) | |
C shape => MultiplyVector (Scale shape) | |
MultiplyVector shape => MultiplyVector (Array shape) | |
Solve typ => MultiplyVector (Inverse typ) | |
(C vert, C horiz, C height, Eq height, C width, Eq width) => MultiplyVector (Hh vert horiz height width) | |
(C vert, C horiz, C height, Eq height, C width, Eq width) => MultiplyVector (LU vert horiz height width) |
(#*|) :: (MultiplyVector typ, WidthOf typ ~ width, Eq width, Floating a) => Matrix typ a -> Vector width a -> Vector (HeightOf typ) aSource
(-*#) :: (MultiplyVector typ, HeightOf typ ~ height, Eq height, Floating a) => Vector height a -> Matrix typ a -> Vector (WidthOf typ) aSource
class (Box typ, HeightOf typ ~ WidthOf typ) => MultiplySquare typ Source
C shape => MultiplySquare (Permutation shape) | |
C shape => MultiplySquare (Scale shape) | |
MultiplySquare shape => MultiplySquare (Array shape) | |
Solve typ => MultiplySquare (Inverse typ) | |
(~ * vert Small, ~ * horiz Small, C height, ~ * height width) => MultiplySquare (Hh vert horiz height width) | |
(~ * vert Small, ~ * horiz Small, C height, ~ * height width) => MultiplySquare (LU vert horiz height width) |
multiplySquare :: (MultiplySquare typ, HeightOf typ ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width aSource
class (Box typ, HeightOf typ ~ WidthOf typ) => Power typ whereSource
(##*#) :: (MultiplySquare typ, WidthOf typ ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width aSource
(#*##) :: (MultiplySquare typ, HeightOf typ ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width aSource
class (Box typ, HeightOf typ ~ WidthOf typ) => Determinant typ whereSource
determinant :: Floating a => Matrix typ a -> aSource
C shape => Determinant (Permutation shape) | |
(C shape, Eq shape) => Determinant (Scale shape) | |
Determinant shape => Determinant (Array shape) | |
Determinant typ => Determinant (Inverse typ) | |
(~ * vert Small, ~ * horiz Small, C height, ~ * height width) => Determinant (Hh vert horiz height width) | |
(~ * vert Small, ~ * horiz Small, C height, ~ * height width) => Determinant (LU vert horiz height width) |
class (Box typ, HeightOf typ ~ WidthOf typ) => Solve typ whereSource
solve :: (HeightOf typ ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width aSource
solveRight :: (HeightOf typ ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width aSource
solveLeft :: (WidthOf typ ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width aSource
C shape => Solve (Permutation shape) | |
(C shape, Eq shape) => Solve (Scale shape) | |
Solve shape => Solve (Array shape) | |
MultiplySquare typ => Solve (Inverse typ) | |
(~ * vert Small, ~ * horiz Small, C height, ~ * height width) => Solve (Hh vert horiz height width) | |
(~ * vert Small, ~ * horiz Small, C height, ~ * height width) => Solve (LU vert horiz height width) |
(##/#) :: (Solve typ, WidthOf typ ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix typ a -> Full vert horiz height width aSource
(#\##) :: (Solve typ, HeightOf typ ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix typ a -> Full vert horiz height width a -> Full vert horiz height width aSource
solveVector :: (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Transposition -> Matrix typ a -> Vector height a -> Vector height aSource
(-/#) :: (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Vector height a -> Matrix typ a -> Vector height aSource
(#\|) :: (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Matrix typ a -> Vector height a -> Vector height aSource