Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- 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)
- data Permutation sh
- type ZeroInt = ZeroBased Int
- zeroInt :: Int -> ZeroInt
- 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
- height :: Box typ => Matrix typ a -> HeightOf typ
- width :: Box typ => Matrix typ a -> WidthOf typ
- type family HeightOf typ
- type family WidthOf typ
- class Box typ
- 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
- 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 ZeroInt 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 ZeroInt width a
- fromColumnsNonEmpty :: (C height, Eq height, Storable a) => T [] (Vector height a) -> General height ZeroInt 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 ZeroInt 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)
- 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 ZeroInt width a -> Full vert Big ZeroInt width a
- takeColumns :: (C horiz, C height, Floating a) => Int -> Full Big horiz height ZeroInt a -> Full Big horiz height ZeroInt a
- takeEqually :: (C vert, C horiz, Floating a) => Int -> Full vert horiz ZeroInt ZeroInt a -> Full vert horiz ZeroInt ZeroInt a
- dropRows :: (C vert, C width, Floating a) => Int -> Full vert Big ZeroInt width a -> Full vert Big ZeroInt width a
- dropColumns :: (C horiz, C height, Floating a) => Int -> Full Big horiz height ZeroInt a -> Full Big horiz height ZeroInt a
- dropEqually :: (C vert, C horiz, Floating a) => Int -> Full vert horiz ZeroInt ZeroInt a -> Full vert horiz ZeroInt ZeroInt 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 ZeroInt width a -> Full vert horiz ZeroInt width a
- reverseColumns :: (C vert, C horiz, C height, Floating a) => Full vert horiz height ZeroInt a -> Full vert horiz height ZeroInt 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
- flatten :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Vector ZeroInt 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
- conjugate :: (Complex typ, Floating a) => Matrix typ a -> Matrix typ a
- fromReal :: (Complex typ, Floating a) => Matrix typ (RealOf a) -> Matrix typ a
- toComplex :: (Complex typ, Floating a) => Matrix typ a -> Matrix typ (ComplexOf 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
- 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, sub :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a
- add, 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 => MultiplyLeft typ
- (-*#) :: (MultiplyLeft typ, Floating a) => Vector (HeightOf typ) a -> Matrix typ a -> Vector (WidthOf typ) a
- class Box typ => MultiplyRight typ
- (#*|) :: (MultiplyRight typ, Floating a) => Matrix typ a -> Vector (WidthOf typ) a -> Vector (HeightOf 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
- (##*#) :: (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
- (#!) :: (Indexed typ, Floating a) => Matrix typ a -> (Index (HeightOf typ), Index (WidthOf typ)) -> a
- class (Box typ, HeightOf typ ~ WidthOf typ) => Solve typ
- solve :: (Solve 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
- solveLeft :: (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
- solveRight :: (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
- (##/#) :: (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 => Inverse typ
- inverse :: (Inverse typ, Floating a) => Matrix typ a -> Matrix typ a
- data Transposition
Documentation
data family Matrix typ a Source #
Instances
(C sh, Show sh) => Show (Matrix (Permutation sh) a) Source # | |
Defined in Numeric.LAPACK.Matrix.Type | |
(C shape, Storable a, Show shape, Show a) => Show (Matrix (Array shape) a) Source # | |
(MultiplySame typ, Floating a) => Semigroup (Matrix typ a) Source # | |
(NFData typ, NFData a) => NFData (Matrix typ a) Source # | |
Defined in Numeric.LAPACK.Matrix.Type | |
(FormatMatrix typ, Floating a) => Display (Matrix typ a) Source # | |
Defined in Numeric.LAPACK.Matrix.Type | |
(FormatMatrix typ, Floating a) => Format (Matrix typ a) Source # | |
newtype Matrix (Permutation sh) a Source # | |
Defined in Numeric.LAPACK.Matrix.Type | |
newtype Matrix (Array shape) a Source # | |
Defined in Numeric.LAPACK.Matrix.Array |
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 sh Source #
type Symmetric sh = FlexSymmetric NonUnit sh Source #
type Hermitian sh = ArrayMatrix (Hermitian sh) Source #
data Permutation sh Source #
Instances
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.gramian a
instead.
type family HeightOf typ Source #
Instances
type HeightOf (Permutation sh) Source # | |
Defined in Numeric.LAPACK.Matrix.Type | |
type HeightOf (Array sh) Source # | |
Defined in Numeric.LAPACK.Matrix.Array |
type family WidthOf typ Source #
Instances
type WidthOf (Permutation sh) Source # | |
Defined in Numeric.LAPACK.Matrix.Type | |
type WidthOf (Array sh) Source # | |
Defined in Numeric.LAPACK.Matrix.Array |
Instances
Box (Permutation sh) Source # | |
Defined in Numeric.LAPACK.Matrix.Type type HeightOf (Permutation sh) :: Type Source # type WidthOf (Permutation sh) :: Type Source # height :: Matrix (Permutation sh) a -> HeightOf (Permutation sh) Source # width :: Matrix (Permutation sh) a -> WidthOf (Permutation sh) Source # | |
Box sh => Box (Array sh) Source # | |
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 a Source #
mapShape :: (C sh0, C sh1) => (sh0 -> sh1) -> ArrayMatrix sh0 a -> ArrayMatrix sh1 a 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 #
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 #
tallFromGeneral :: (C height, C width, Storable a) => General height width a -> Tall height width a Source #
wideFromGeneral :: (C height, C width, Storable a) => General height width a -> Wide 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.
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 #
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.
takeTop :: (C vert, C height0, C height1, C width, Floating a) => Full vert Big (height0 :+: height1) width a -> Full vert Big height0 width a Source #
takeBottom :: (C vert, C height0, C height1, C width, Floating a) => Full vert Big (height0 :+: height1) width a -> Full vert Big height1 width a Source #
takeLeft :: (C vert, C height, C width0, C width1, Floating a) => Full Big vert height (width0 :+: width1) a -> Full Big vert height width0 a Source #
takeRight :: (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 #
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 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 :: (ShapeOrder shape, Floating a) => Order -> ArrayMatrix shape a -> ArrayMatrix shape a Source #
adaptOrder :: (ShapeOrder shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a Source #
adaptOrder x y
contains the data of y
with the layout of x
.
Instances
Enum OrderBias Source # | |
Defined in Numeric.LAPACK.Matrix.Plain succ :: OrderBias -> OrderBias # pred :: OrderBias -> OrderBias # fromEnum :: OrderBias -> Int # enumFrom :: OrderBias -> [OrderBias] # enumFromThen :: OrderBias -> OrderBias -> [OrderBias] # enumFromTo :: OrderBias -> OrderBias -> [OrderBias] # enumFromThenTo :: OrderBias -> OrderBias -> OrderBias -> [OrderBias] # | |
Eq OrderBias Source # | |
Ord OrderBias Source # | |
Defined in Numeric.LAPACK.Matrix.Plain | |
Show OrderBias Source # | |
contiguousBias :: OrderBias Source #
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) a infixr 3 Source #
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 Source #
(===) :: (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 infixr 2 Source #
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 Source #
(|*-) :: (C height, Eq height, C width, Eq width, Floating a) => Vector height a -> Vector width a -> General height width a infixl 7 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)
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 Source #
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 #
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 Source #
Instances
C shape => Complex (Permutation shape) Source # | |
Defined in Numeric.LAPACK.Matrix.Type conjugate :: Floating a => Matrix (Permutation shape) a -> Matrix (Permutation shape) a Source # fromReal :: Floating a => Matrix (Permutation shape) (RealOf a) -> Matrix (Permutation shape) a Source # toComplex :: Floating a => Matrix (Permutation shape) a -> Matrix (Permutation shape) (ComplexOf a) Source # | |
Complex sh => Complex (Array sh) 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 #
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 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 #
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 #
(\*#) :: (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 infixr 7 Source #
(#*\) :: (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 infixl 7 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 #
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 #
zero :: (Homogeneous shape, Floating a) => shape -> ArrayMatrix shape a Source #
negate :: (Homogeneous shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a Source #
scale :: (Scale shape, Floating a) => a -> ArrayMatrix shape a -> ArrayMatrix shape a Source #
scaleReal :: (Homogeneous shape, Floating a) => RealOf a -> ArrayMatrix shape a -> ArrayMatrix shape a Source #
scaleRealReal :: (Homogeneous shape, Real a) => a -> ArrayMatrix shape a -> ArrayMatrix shape a Source #
(.*#) :: (Scale shape, Floating a) => a -> ArrayMatrix shape a -> ArrayMatrix shape a infixl 7 Source #
add, sub :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a infixl 6 `add`, `sub` Source #
add, sub :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a infixl 6 `add`, `sub` Source #
(#+#) :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a infixl 6 Source #
(#-#) :: (Additive shape, Floating a) => ArrayMatrix shape a -> ArrayMatrix shape a -> ArrayMatrix shape a infixl 6 Source #
class (Box typA, Box typB) => Multiply typA typB Source #
matrixMatrix
Instances
(C shapeA, Eq shapeA, shapeA ~ shapeB, C shapeB) => Multiply (Permutation shapeA) (Permutation shapeB) Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply type Multiplied (Permutation shapeA) (Permutation shapeB) :: Type matrixMatrix :: Floating a => Matrix (Permutation shapeA) a -> Matrix (Permutation shapeB) a -> Matrix (Multiplied (Permutation shapeA) (Permutation shapeB)) a | |
(Box shapeA, Box shapeB, Multiply shapeA shapeB) => Multiply (Array shapeA) (Array shapeB) Source # | |
(#*#) :: (Multiply typA typB, Floating a) => Matrix typA a -> Matrix typB a -> Matrix (Multiplied typA typB) a infixl 7 Source #
class Box typ => MultiplyLeft typ Source #
vectorMatrix
Instances
(C shape, Eq shape) => MultiplyLeft (Permutation shape) Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply vectorMatrix :: Floating a => Vector (HeightOf (Permutation shape)) a -> Matrix (Permutation shape) a -> Vector (WidthOf (Permutation shape)) a | |
MultiplyLeft shape => MultiplyLeft (Array shape) Source # | |
(-*#) :: (MultiplyLeft typ, Floating a) => Vector (HeightOf typ) a -> Matrix typ a -> Vector (WidthOf typ) a infixl 7 Source #
class Box typ => MultiplyRight typ Source #
matrixVector
Instances
(C shape, Eq shape) => MultiplyRight (Permutation shape) Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply matrixVector :: Floating a => Matrix (Permutation shape) a -> Vector (WidthOf (Permutation shape)) a -> Vector (HeightOf (Permutation shape)) a | |
MultiplyRight shape => MultiplyRight (Array shape) Source # | |
(#*|) :: (MultiplyRight typ, Floating a) => Matrix typ a -> Vector (WidthOf typ) a -> Vector (HeightOf typ) a infixr 7 Source #
class (Box typ, HeightOf typ ~ WidthOf typ) => MultiplySquare typ Source #
transposableSquare | fullSquare, squareFull
Instances
C shape => MultiplySquare (Permutation shape) Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply transposableSquare :: (HeightOf (Permutation shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Matrix (Permutation shape) a -> Full vert horiz height width a -> Full vert horiz height width a squareFull :: (HeightOf (Permutation shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix (Permutation shape) a -> Full vert horiz height width a -> Full vert horiz height width a fullSquare :: (WidthOf (Permutation shape) ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix (Permutation shape) a -> Full vert horiz height width a | |
MultiplySquare shape => MultiplySquare (Array shape) Source # | |
Defined in Numeric.LAPACK.Matrix.Multiply transposableSquare :: (HeightOf (Array shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Matrix (Array shape) a -> Full vert horiz height width a -> Full vert horiz height width a squareFull :: (HeightOf (Array shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix (Array shape) a -> Full vert horiz height width a -> Full vert horiz height width a fullSquare :: (WidthOf (Array shape) ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix (Array shape) a -> Full vert horiz height width a |
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 Source #
(##*#) :: (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 infixl 7 Source #
(#*##) :: (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 infixr 7 Source #
class Box typ => Indexed typ Source #
Instances
Indexed size => Indexed (Permutation size) Source # | |
Defined in Numeric.LAPACK.Matrix.Indexed (#!) :: Floating a => Matrix (Permutation size) a -> (Index (HeightOf (Permutation size)), Index (WidthOf (Permutation size))) -> a Source # | |
Indexed sh => Indexed (Array sh) Source # | |
(#!) :: (Indexed typ, Floating a) => Matrix typ a -> (Index (HeightOf typ), Index (WidthOf typ)) -> a infixl 9 Source #
class (Box typ, HeightOf typ ~ WidthOf typ) => Solve typ Source #
Instances
C shape => Solve (Permutation shape) Source # | |
Defined in Numeric.LAPACK.Matrix.Divide solve :: (HeightOf (Permutation shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Matrix (Permutation shape) a -> Full vert horiz height width a -> Full vert horiz height width a Source # solveRight :: (HeightOf (Permutation shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix (Permutation shape) a -> Full vert horiz height width a -> Full vert horiz height width a Source # solveLeft :: (WidthOf (Permutation shape) ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix (Permutation shape) a -> Full vert horiz height width a Source # | |
Solve shape => Solve (Array shape) Source # | |
Defined in Numeric.LAPACK.Matrix.Divide solve :: (HeightOf (Array shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Transposition -> Matrix (Array shape) a -> Full vert horiz height width a -> Full vert horiz height width a Source # solveRight :: (HeightOf (Array shape) ~ height, Eq height, C width, C horiz, C vert, Floating a) => Matrix (Array shape) a -> Full vert horiz height width a -> Full vert horiz height width a Source # solveLeft :: (WidthOf (Array shape) ~ width, Eq width, C height, C horiz, C vert, Floating a) => Full vert horiz height width a -> Matrix (Array shape) a -> Full vert horiz height width a Source # |
solve :: (Solve 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 Source #
solveLeft :: (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 Source #
solveRight :: (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 Source #
(##/#) :: (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 infixl 7 Source #
(#\##) :: (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 infixr 7 Source #
solveVector :: (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Transposition -> Matrix typ a -> Vector height a -> Vector height a Source #
(-/#) :: (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Vector height a -> Matrix typ a -> Vector height a infixl 7 Source #
(#\|) :: (Solve typ, HeightOf typ ~ height, Eq height, Floating a) => Matrix typ a -> Vector height a -> Vector height a infixr 7 Source #
class Solve typ => Inverse typ Source #
Instances
C shape => Inverse (Permutation shape) Source # | |
Defined in Numeric.LAPACK.Matrix.Divide inverse :: Floating a => Matrix (Permutation shape) a -> Matrix (Permutation shape) a Source # | |
Inverse shape => Inverse (Array shape) Source # | |
data Transposition Source #