Safe Haskell | None |
---|
- type Full vert horiz height width = Array (Full vert horiz height width)
- type General height width = Array (General height width)
- type Tall height width = Array (Tall height width)
- type Wide height width = Array (Wide height width)
- 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 shape => Array shape a -> HeightOf shape
- width :: Box shape => Array shape a -> WidthOf shape
- 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
- 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
- takeTopRows :: (C vert, C height0, C height1, C width, Floating a) => Full vert Big (height0 :+: height1) width a -> Full vert Big height0 width a
- takeBottomRows :: (C vert, C height0, C height1, C width, Floating a) => Full vert Big (height0 :+: height1) width a -> Full vert Big height1 width a
- takeLeftColumns :: (C vert, C height, C width0, C width1, Floating a) => Full Big vert height (width0 :+: width1) a -> Full Big vert height width0 a
- takeRightColumns :: (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 :: (C vert, C horiz, C height, C width, Floating a) => Order -> Full vert horiz height width a -> Full vert horiz height width a
- adaptOrder :: (C vert, C horiz, C height, C width, Floating a) => Full vert horiz height width a -> Full vert horiz height width a -> Full vert horiz height width a
- (|||) :: (C vert, C height, Eq height, C widtha, C widthb, Floating a) => Full vert Big height widtha a -> Full vert Big height widthb a -> Full vert Big height (widtha :+: widthb) a
- (===) :: (C horiz, C width, Eq width, C heighta, C heightb, Floating a) => Full Big horiz heighta width a -> Full Big horiz heightb width a -> Full Big horiz (heighta :+: heightb) width a
- 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
- sumRank1 :: (C height, Eq height, C width, Eq width, Floating a) => (height, width) -> [(a, (Vector height a, Vector width a))] -> General height width a
- type family RealOf x
- add :: (C vert, C horiz, C height, C width, Eq height, Eq width, Floating a) => Full vert horiz height width a -> Full vert horiz height width a -> Full vert horiz height width a
- sub :: (C vert, C horiz, C height, C width, Eq height, Eq width, Floating a) => Full vert horiz height width a -> Full vert horiz height width a -> Full vert horiz height width a
- 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
- 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
- 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)
- 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)
- 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
- 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
- class (C shapeA, C shapeB) => Multiply shapeA shapeB where
- class C shape => MultiplyLeft shape where
- class C shape => MultiplyRight shape where
- class Box sh => Indexed sh where
- class C shape => Solve shape where
- solveVector :: (Solve shape, HeightOf shape ~ height, Eq height, Floating a) => Array shape a -> Vector height a -> Vector height a
- class Solve shape => Inverse shape where
Documentation
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.
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
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 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
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
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.
(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
(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
(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
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
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
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