Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Matrix a b where
- type MatrixXf = Matrix Float CFloat
- type MatrixXd = Matrix Double CDouble
- type MatrixXcf = Matrix (Complex Float) (CComplex CFloat)
- type MatrixXcd = Matrix (Complex Double) (CComplex CDouble)
- class (Num a, Cast a b, Cast b a, Storable b, Code b) => Elem a b | a -> b
- data CComplex a
- valid :: Elem a b => Matrix a b -> Bool
- fromList :: Elem a b => [[a]] -> Matrix a b
- toList :: Elem a b => Matrix a b -> [[a]]
- fromFlatList :: Elem a b => Int -> Int -> [a] -> Matrix a b
- toFlatList :: Elem a b => Matrix a b -> [a]
- generate :: Elem a b => Int -> Int -> (Int -> Int -> a) -> Matrix a b
- empty :: Elem a b => Matrix a b
- null :: Elem a b => Matrix a b -> Bool
- square :: Elem a b => Matrix a b -> Bool
- zero :: Elem a b => Int -> Int -> Matrix a b
- ones :: Elem a b => Int -> Int -> Matrix a b
- identity :: Elem a b => Int -> Int -> Matrix a b
- constant :: Elem a b => Int -> Int -> a -> Matrix a b
- random :: Elem a b => Int -> Int -> IO (Matrix a b)
- cols :: Elem a b => Matrix a b -> Int
- rows :: Elem a b => Matrix a b -> Int
- dims :: Elem a b => Matrix a b -> (Int, Int)
- (!) :: forall a b. Elem a b => Matrix a b -> (Int, Int) -> a
- coeff :: Elem a b => Int -> Int -> Matrix a b -> a
- unsafeCoeff :: Elem a b => Int -> Int -> Matrix a b -> a
- col :: Elem a b => Int -> Matrix a b -> [a]
- row :: Elem a b => Int -> Matrix a b -> [a]
- block :: Elem a b => Int -> Int -> Int -> Int -> Matrix a b -> Matrix a b
- topRows :: Elem a b => Int -> Matrix a b -> Matrix a b
- bottomRows :: Elem a b => Int -> Matrix a b -> Matrix a b
- leftCols :: Elem a b => Int -> Matrix a b -> Matrix a b
- rightCols :: Elem a b => Int -> Matrix a b -> Matrix a b
- sum :: Elem a b => Matrix a b -> a
- prod :: Elem a b => Matrix a b -> a
- mean :: Elem a b => Matrix a b -> a
- minCoeff :: (Elem a b, Ord a) => Matrix a b -> a
- maxCoeff :: (Elem a b, Ord a) => Matrix a b -> a
- trace :: Elem a b => Matrix a b -> a
- norm :: Elem a b => Matrix a b -> a
- squaredNorm :: Elem a b => Matrix a b -> a
- blueNorm :: Elem a b => Matrix a b -> a
- hypotNorm :: Elem a b => Matrix a b -> a
- determinant :: Elem a b => Matrix a b -> a
- fold :: Elem a b => (c -> a -> c) -> c -> Matrix a b -> c
- fold' :: Elem a b => (c -> a -> c) -> c -> Matrix a b -> c
- ifold :: Elem a b => (Int -> Int -> c -> a -> c) -> c -> Matrix a b -> c
- ifold' :: Elem a b => (Int -> Int -> c -> a -> c) -> c -> Matrix a b -> c
- fold1 :: Elem a b => (a -> a -> a) -> Matrix a b -> a
- fold1' :: Elem a b => (a -> a -> a) -> Matrix a b -> a
- all :: Elem a b => (a -> Bool) -> Matrix a b -> Bool
- any :: Elem a b => (a -> Bool) -> Matrix a b -> Bool
- count :: Elem a b => (a -> Bool) -> Matrix a b -> Int
- add :: Elem a b => Matrix a b -> Matrix a b -> Matrix a b
- sub :: Elem a b => Matrix a b -> Matrix a b -> Matrix a b
- mul :: Elem a b => Matrix a b -> Matrix a b -> Matrix a b
- map :: Elem a b => (a -> a) -> Matrix a b -> Matrix a b
- imap :: Elem a b => (Int -> Int -> a -> a) -> Matrix a b -> Matrix a b
- filter :: Elem a b => (a -> Bool) -> Matrix a b -> Matrix a b
- ifilter :: Elem a b => (Int -> Int -> a -> Bool) -> Matrix a b -> Matrix a b
- diagonal :: Elem a b => Matrix a b -> Matrix a b
- transpose :: Elem a b => Matrix a b -> Matrix a b
- inverse :: Elem a b => Matrix a b -> Matrix a b
- adjoint :: Elem a b => Matrix a b -> Matrix a b
- conjugate :: Elem a b => Matrix a b -> Matrix a b
- normalize :: Elem a b => Matrix a b -> Matrix a b
- modify :: Elem a b => (forall s. MMatrix a b s -> ST s ()) -> Matrix a b -> Matrix a b
- convert :: (Elem a b, Elem c d) => (a -> c) -> Matrix a b -> Matrix c d
- data TriangularMode
- triangularView :: Elem a b => TriangularMode -> Matrix a b -> Matrix a b
- lowerTriangle :: Elem a b => Matrix a b -> Matrix a b
- upperTriangle :: Elem a b => Matrix a b -> Matrix a b
- encode :: Elem a b => Matrix a b -> ByteString
- decode :: Elem a b => ByteString -> Matrix a b
- thaw :: Elem a b => PrimMonad m => Matrix a b -> m (MMatrix a b (PrimState m))
- freeze :: Elem a b => PrimMonad m => MMatrix a b (PrimState m) -> m (Matrix a b)
- unsafeThaw :: Elem a b => PrimMonad m => Matrix a b -> m (MMatrix a b (PrimState m))
- unsafeFreeze :: Elem a b => PrimMonad m => MMatrix a b (PrimState m) -> m (Matrix a b)
- unsafeWith :: Elem a b => Matrix a b -> (Ptr b -> CInt -> CInt -> IO c) -> IO c
Matrix type
Matrix aliases follows Eigen naming convention
data Matrix a b where Source #
Matrix to be used in pure computations, uses column major memory layout, features copy-free FFI with C++ Eigen library.
Instances
Elem a b => Num (Matrix a b) Source # | Basic matrix math exposed through Num instance: |
Defined in Data.Eigen.Matrix | |
(Elem a b, Show a) => Show (Matrix a b) Source # | Pretty prints the matrix |
Elem a b => Binary (Matrix a b) Source # | Matrix binary serialization |
type MatrixXcf = Matrix (Complex Float) (CComplex CFloat) Source #
Alias for single previsiom matrix of complex numbers
type MatrixXcd = Matrix (Complex Double) (CComplex CDouble) Source #
Alias for double prevision matrix of complex numbers
Complex number for FFI with the same memory layout as std::complex<T>
Instances
Show a => Show (CComplex a) Source # | |
Storable a => Storable (CComplex a) Source # | |
Defined in Data.Eigen.Internal | |
Code (CComplex CFloat) Source # | |
Code (CComplex CDouble) Source # | |
Cast (Complex Double) (CComplex CDouble) Source # | |
Cast (Complex Float) (CComplex CFloat) Source # | |
Cast (CComplex CFloat) (Complex Float) Source # | |
Cast (CComplex CDouble) (Complex Double) Source # | |
Elem (Complex Double) (CComplex CDouble) Source # | |
Defined in Data.Eigen.Internal | |
Elem (Complex Float) (CComplex CFloat) Source # | |
Defined in Data.Eigen.Internal |
Matrix conversions
fromList :: Elem a b => [[a]] -> Matrix a b Source #
Construct matrix from a list of rows, column count is detected as maximum row length. Missing values are filled with 0
fromFlatList :: Elem a b => Int -> Int -> [a] -> Matrix a b Source #
Build matrix of given dimensions and values from given list split on rows. Invalid list length results in error.
toFlatList :: Elem a b => Matrix a b -> [a] Source #
Convert matrix to a list by concatenating rows
generate :: Elem a b => Int -> Int -> (Int -> Int -> a) -> Matrix a b Source #
- generate rows cols (λ row col -> val)
Create matrix using generator function λ row col -> val
Standard matrices and special cases
identity :: Elem a b => Int -> Int -> Matrix a b Source #
The identity matrix (not necessarily square).
constant :: Elem a b => Int -> Int -> a -> Matrix a b Source #
Matrix where all coeffs are filled with given value
Accessing matrix data
(!) :: forall a b. Elem a b => Matrix a b -> (Int, Int) -> a Source #
Matrix coefficient at specific row and col
coeff :: Elem a b => Int -> Int -> Matrix a b -> a Source #
Matrix coefficient at specific row and col
unsafeCoeff :: Elem a b => Int -> Int -> Matrix a b -> a Source #
Unsafe version of coeff function. No bounds check performed so SEGFAULT possible
block :: Elem a b => Int -> Int -> Int -> Int -> Matrix a b -> Matrix a b Source #
Extract rectangular block from matrix defined by startRow startCol blockRows blockCols
Matrix properties
trace :: Elem a b => Matrix a b -> a Source #
The trace of a matrix is the sum of the diagonal coefficients and can also be computed as sum (diagonal m)
norm :: Elem a b => Matrix a b -> a Source #
For vectors, the l2 norm, and for matrices the Frobenius norm. In both cases, it consists in the square root of the sum of the square of all the matrix entries. For vectors, this is also equals to the square root of the dot product of this with itself.
squaredNorm :: Elem a b => Matrix a b -> a Source #
For vectors, the squared l2 norm, and for matrices the Frobenius norm. In both cases, it consists in the sum of the square of all the matrix entries. For vectors, this is also equals to the dot product of this with itself.
blueNorm :: Elem a b => Matrix a b -> a Source #
The l2 norm of the matrix using the Blue's algorithm. A Portable Fortran Program to Find the Euclidean Norm of a Vector, ACM TOMS, Vol 4, Issue 1, 1978.
hypotNorm :: Elem a b => Matrix a b -> a Source #
The l2 norm of the matrix avoiding undeflow and overflow. This version use a concatenation of hypot calls, and it is very slow.
determinant :: Elem a b => Matrix a b -> a Source #
The determinant of the matrix
Generic reductions
fold :: Elem a b => (c -> a -> c) -> c -> Matrix a b -> c Source #
Reduce matrix using user provided function applied to each element.
fold' :: Elem a b => (c -> a -> c) -> c -> Matrix a b -> c Source #
Reduce matrix using user provided function applied to each element. This is strict version of fold
ifold :: Elem a b => (Int -> Int -> c -> a -> c) -> c -> Matrix a b -> c Source #
Reduce matrix using user provided function applied to each element and it's index
ifold' :: Elem a b => (Int -> Int -> c -> a -> c) -> c -> Matrix a b -> c Source #
Reduce matrix using user provided function applied to each element and it's index. This is strict version of ifold
fold1 :: Elem a b => (a -> a -> a) -> Matrix a b -> a Source #
Reduce matrix using user provided function applied to each element.
fold1' :: Elem a b => (a -> a -> a) -> Matrix a b -> a Source #
Reduce matrix using user provided function applied to each element. This is strict version of fold
Boolean reductions
all :: Elem a b => (a -> Bool) -> Matrix a b -> Bool Source #
Applied to a predicate and a matrix, all determines if all elements of the matrix satisfies the predicate
any :: Elem a b => (a -> Bool) -> Matrix a b -> Bool Source #
Applied to a predicate and a matrix, any determines if any element of the matrix satisfies the predicate
count :: Elem a b => (a -> Bool) -> Matrix a b -> Int Source #
Returns the number of coefficients in a given matrix that evaluate to true
Basic matrix algebra
add :: Elem a b => Matrix a b -> Matrix a b -> Matrix a b Source #
Adding two matrices by adding the corresponding entries together. You can use (+)
function as well.
sub :: Elem a b => Matrix a b -> Matrix a b -> Matrix a b Source #
Subtracting two matrices by subtracting the corresponding entries together. You can use (-)
function as well.
mul :: Elem a b => Matrix a b -> Matrix a b -> Matrix a b Source #
Matrix multiplication. You can use (*)
function as well.
Mapping over elements
map :: Elem a b => (a -> a) -> Matrix a b -> Matrix a b Source #
Apply a given function to each element of the matrix.
Here is an example how to implement scalar matrix multiplication:
>>>
let a = fromList [[1,2],[3,4]] :: MatrixXf
>>>
a
Matrix 2x2 1.0 2.0 3.0 4.0
>>>
map (*10) a
Matrix 2x2 10.0 20.0 30.0 40.0
imap :: Elem a b => (Int -> Int -> a -> a) -> Matrix a b -> Matrix a b Source #
Apply a given function to each element of the matrix.
Here is an example how upper triangular matrix can be implemented:
>>>
let a = fromList [[1,2,3],[4,5,6],[7,8,9]] :: MatrixXf
>>>
a
Matrix 3x3 1.0 2.0 3.0 4.0 5.0 6.0 7.0 8.0 9.0
>>>
imap (\row col val -> if row <= col then val else 0) a
Matrix 3x3 1.0 2.0 3.0 0.0 5.0 6.0 0.0 0.0 9.0
filter :: Elem a b => (a -> Bool) -> Matrix a b -> Matrix a b Source #
Filter elements in the matrix. Filtered elements will be replaced by 0
ifilter :: Elem a b => (Int -> Int -> a -> Bool) -> Matrix a b -> Matrix a b Source #
Filter elements in the matrix. Filtered elements will be replaced by 0
Matrix transformations
inverse :: Elem a b => Matrix a b -> Matrix a b Source #
Inverse of the matrix
For small fixed sizes up to 4x4, this method uses cofactors. In the general case, this method uses PartialPivLU decomposition
normalize :: Elem a b => Matrix a b -> Matrix a b Source #
Nomalize the matrix by deviding it on its norm
modify :: Elem a b => (forall s. MMatrix a b s -> ST s ()) -> Matrix a b -> Matrix a b Source #
Apply a destructive operation to a matrix. The operation will be performed in place if it is safe to do so and will modify a copy of the matrix otherwise.
convert :: (Elem a b, Elem c d) => (a -> c) -> Matrix a b -> Matrix c d Source #
Convert matrix to different type using user provided element converter
data TriangularMode Source #
Lower | View matrix as a lower triangular matrix. |
Upper | View matrix as an upper triangular matrix. |
StrictlyLower | View matrix as a lower triangular matrix with zeros on the diagonal. |
StrictlyUpper | View matrix as an upper triangular matrix with zeros on the diagonal. |
UnitLower | View matrix as a lower triangular matrix with ones on the diagonal. |
UnitUpper | View matrix as an upper triangular matrix with ones on the diagonal. |
Instances
Enum TriangularMode Source # | |
Defined in Data.Eigen.Matrix succ :: TriangularMode -> TriangularMode # pred :: TriangularMode -> TriangularMode # toEnum :: Int -> TriangularMode # fromEnum :: TriangularMode -> Int # enumFrom :: TriangularMode -> [TriangularMode] # enumFromThen :: TriangularMode -> TriangularMode -> [TriangularMode] # enumFromTo :: TriangularMode -> TriangularMode -> [TriangularMode] # enumFromThenTo :: TriangularMode -> TriangularMode -> TriangularMode -> [TriangularMode] # | |
Eq TriangularMode Source # | |
Defined in Data.Eigen.Matrix (==) :: TriangularMode -> TriangularMode -> Bool # (/=) :: TriangularMode -> TriangularMode -> Bool # | |
Read TriangularMode Source # | |
Defined in Data.Eigen.Matrix readsPrec :: Int -> ReadS TriangularMode # readList :: ReadS [TriangularMode] # | |
Show TriangularMode Source # | |
Defined in Data.Eigen.Matrix showsPrec :: Int -> TriangularMode -> ShowS # show :: TriangularMode -> String # showList :: [TriangularMode] -> ShowS # |
triangularView :: Elem a b => TriangularMode -> Matrix a b -> Matrix a b Source #
Triangular view extracted from the current matrix
lowerTriangle :: Elem a b => Matrix a b -> Matrix a b Source #
Lower trinagle of the matrix. Shortcut for triangularView Lower
upperTriangle :: Elem a b => Matrix a b -> Matrix a b Source #
Upper trinagle of the matrix. Shortcut for triangularView Upper
Matrix serialization
Mutable matrices
thaw :: Elem a b => PrimMonad m => Matrix a b -> m (MMatrix a b (PrimState m)) Source #
Yield a mutable copy of the immutable matrix
freeze :: Elem a b => PrimMonad m => MMatrix a b (PrimState m) -> m (Matrix a b) Source #
Yield an immutable copy of the mutable matrix
unsafeThaw :: Elem a b => PrimMonad m => Matrix a b -> m (MMatrix a b (PrimState m)) Source #
Unsafely convert an immutable matrix to a mutable one without copying. The immutable matrix may not be used after this operation.
unsafeFreeze :: Elem a b => PrimMonad m => MMatrix a b (PrimState m) -> m (Matrix a b) Source #
Unsafe convert a mutable matrix to an immutable one without copying. The mutable matrix may not be used after this operation.