eigen-3.3.4.2: Eigen C++ library (linear algebra: matrices, sparse matrices, vectors, numerical solvers).

Safe HaskellNone
LanguageHaskell2010

Eigen.Matrix

Contents

Synopsis

Types

newtype Matrix :: Nat -> Nat -> Type -> Type where Source #

Matrix to be used in pure computations.

  • Uses column majour memory layout.
  • Has a copy-free FFI using the Eigen library.

Constructors

Matrix :: Vec (n * m) a -> Matrix n m a 
Instances
(Elem a, Show a, KnownNat n, KnownNat m) => Show (Matrix n m a) Source # 
Instance details

Defined in Eigen.Matrix

Methods

showsPrec :: Int -> Matrix n m a -> ShowS #

show :: Matrix n m a -> String #

showList :: [Matrix n m a] -> ShowS #

(KnownNat n, KnownNat m, Elem a) => Binary (Matrix n m a) Source # 
Instance details

Defined in Eigen.Matrix

Methods

put :: Matrix n m a -> Put #

get :: Get (Matrix n m a) #

putList :: [Matrix n m a] -> Put #

newtype Vec :: Nat -> Type -> Type where Source #

Used internally to track the size and corresponding C type of the matrix.

Constructors

Vec :: Vector (C a) -> Vec n a 

type MatrixXf n m = Matrix n m Float Source #

Alias for single precision matrix

type MatrixXd n m = Matrix n m Double Source #

Alias for double precision matrix

type MatrixXcf n m = Matrix n m (Complex Float) Source #

Alias for single precision matrix of complex numbers

type MatrixXcd n m = Matrix n m (Complex Double) Source #

Alias for double precision matrix of complex numbers

Common API

class (Num a, Cast a, Storable a, Storable (C a), Code (C a)) => Elem a Source #

Elem is a closed typeclass that encompasses the properties eigen expects its values to possess, and simplifies the external API quite a bit.

Instances
Elem Double Source # 
Instance details

Defined in Eigen.Internal

Elem Float Source # 
Instance details

Defined in Eigen.Internal

Elem (Complex Double) Source # 
Instance details

Defined in Eigen.Internal

Elem (Complex Float) Source # 
Instance details

Defined in Eigen.Internal

type family C a = (result :: Type) | result -> a Source #

Instances
type C Double Source # 
Instance details

Defined in Eigen.Internal

type C Float Source # 
Instance details

Defined in Eigen.Internal

type C Float = CFloat
type C Int Source # 
Instance details

Defined in Eigen.Internal

type C Int = CInt
type C (Complex a) Source # 
Instance details

Defined in Eigen.Internal

type C (Complex a) = CComplex (C a)
type C (Int, Int, a) Source # 
Instance details

Defined in Eigen.Internal

type C (Int, Int, a) = CTriplet a

natToInt :: forall n. KnownNat n => Int Source #

Used internally. Given a KnownNat constraint, turn the type-level Nat into an Int.

data Row (r :: Nat) Source #

Like Proxy, but specialised to Nat.

Constructors

Row 

data Col (c :: Nat) Source #

Like Proxy, but specialised to Nat.

Constructors

Col 

Encode/Decode a Matrix

encode :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> ByteString Source #

Encode the sparse matrix as a lazy bytestring

decode :: (Elem a, KnownNat n, KnownNat m) => ByteString -> Matrix n m a Source #

Decode the sparse matrix from a lazy bytestring

Querying a Matrix

null :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> Bool Source #

Is matrix empty?

square :: forall n m a. (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> Bool Source #

Is matrix square?

rows :: forall n m a. KnownNat n => Matrix n m a -> Int Source #

The number of rows in the matrix

cols :: forall n m a. KnownNat m => Matrix n m a -> Int Source #

The number of colums in the matrix

dims :: forall n m a. (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> (Int, Int) Source #

Return Matrix size as a pair of (rows, cols)

Constructing a Matrix

empty :: Elem a => Matrix 0 0 a Source #

Construct an empty 0x0 matrix

constant :: forall n m a. (Elem a, KnownNat n, KnownNat m) => a -> Matrix n m a Source #

Matrix where all coeffs are filled with the given value

zero :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a Source #

Matrix where all coeffs are filled with 0

ones :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a Source #

Matrix where all coeffs are filled with 1

identity :: forall n m a. (Elem a, KnownNat n, KnownNat m) => Matrix n m a Source #

The identity matrix (not necessarily square)

random :: forall n m a. (Elem a, KnownNat n, KnownNat m) => IO (Matrix n m a) Source #

The random matrix of a given size

diagonal :: (Elem a, KnownNat n, KnownNat m, r ~ Min n m, KnownNat r) => Matrix n m a -> Matrix r 1 a Source #

Return the diagonal of a matrix.

(!) :: forall n m a r c. (Elem a, KnownNat n, KnownNat r, KnownNat c, r <= n, c <= m) => Row r -> Col c -> Matrix n m a -> a Source #

Return the value at the given position.

coeff :: forall n m a r c. (Elem a, KnownNat n, KnownNat r, KnownNat c, r <= n, c <= m) => Row r -> Col c -> Matrix n m a -> a Source #

Return the value at the given position.

generate :: forall n m a. (Elem a, KnownNat n, KnownNat m) => (Int -> Int -> a) -> Matrix n m a Source #

Given a generation function `f :: Int -> Int -> a`, construct a Matrix of known size using points in the matrix as inputs.

sum :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> a Source #

The sum of all coefficients in the matrix

prod :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> a Source #

The product of all coefficients in the matrix

mean :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> a Source #

The arithmetic mean of all coefficients in the matrix

trace :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> a Source #

The trace of a matrix is the sum of the diagonal coefficients.

trace m == sum (diagonal m)

all :: (Elem a, KnownNat n, KnownNat m) => (a -> Bool) -> Matrix n m a -> Bool Source #

Given a predicate p, determine if all values in the Matrix satisfy p.

any :: (Elem a, KnownNat n, KnownNat m) => (a -> Bool) -> Matrix n m a -> Bool Source #

Given a predicate p, determine if any values in the Matrix satisfy p.

count :: (Elem a, KnownNat n, KnownNat m) => (a -> Bool) -> Matrix n m a -> Int Source #

Given a predicate p, determine how many values in the Matrix satisfy p.

norm :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> 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, KnownNat n, KnownNat m) => Matrix n m a -> 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, KnownNat n, KnownNat m) => Matrix n m a -> 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, KnownNat n, KnownNat m) => Matrix n m a -> 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 :: forall n a. (Elem a, KnownNat n) => Matrix n n a -> a Source #

The determinant of the matrix

add :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> Matrix n m a -> Matrix n m a Source #

Add two matrices.

sub :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> Matrix n m a -> Matrix n m a Source #

Subtract two matrices.

mul :: (Elem a, KnownNat p, KnownNat q, KnownNat r) => Matrix p q a -> Matrix q r a -> Matrix p r a Source #

Multiply two matrices.

map :: Elem a => (a -> a) -> Matrix n m a -> Matrix n m a 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 2 2 >>> 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, KnownNat n, KnownNat m) => (Int -> Int -> a -> a) -> Matrix n m a -> Matrix n m a 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

data TriangularMode Source #

Provide a view of the matrix for extraction of a subset.

Constructors

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.

triangularView :: (Elem a, KnownNat n, KnownNat m) => TriangularMode -> Matrix n m a -> Matrix n m a Source #

Triangular view extracted from the current matrix

filter :: Elem a => (a -> Bool) -> Matrix n m a -> Matrix n m a Source #

Filter elements in the matrix. Filtered elements will be replaced by 0.

ifilter :: (Elem a, KnownNat n, KnownNat m) => (Int -> Int -> a -> Bool) -> Matrix n m a -> Matrix n m a Source #

Filter elements in the matrix with an indexed predicate. Filtered elements will be replaces by 0.

length :: forall n m a r. (Elem a, KnownNat n, KnownNat m, r ~ (n * m), KnownNat r) => Matrix n m a -> Int Source #

The length of the matrix.

foldl :: (Elem a, KnownNat n, KnownNat m) => (b -> a -> b) -> b -> Matrix n m a -> b Source #

Left fold of a matrix, where accumulation is lazy.

foldl' :: Elem a => (b -> a -> b) -> b -> Matrix n m a -> b Source #

Right fold of a matrix, where accumulation is strict.

inverse :: forall n a. (Elem a, KnownNat n) => Matrix n n a -> Matrix n n a 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

adjoint :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> Matrix m n a Source #

Adjoint of the matrix

transpose :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> Matrix m n a Source #

Transpose of the matrix

conjugate :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> Matrix n m a Source #

Conjugate of the matrix

normalize :: forall n m a. (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> Matrix n m a Source #

Normalise the matrix by dividing it on its norm

modify :: (Elem a, KnownNat n, KnownNat m) => (forall s. MMatrix n m s a -> ST s ()) -> Matrix n m a -> Matrix n m a Source #

Apply a destructive operation to a matrix. The operation will be performed in-place, if it is safe to do so - otherwise, it will create a copy of the matrix.

block Source #

Arguments

:: (Elem a, KnownNat sr, KnownNat sc, KnownNat br, KnownNat bc, KnownNat n, KnownNat m) 
=> (sr <= n, sc <= m, br <= n, bc <= m) 
=> Row sr

starting row

-> Col sc

starting col

-> Row br

block of rows

-> Col bc

block of cols

-> Matrix n m a

extract from this

-> Matrix br bc a

extraction

Extract rectangular block from matrix defined by startRow startCol blockRows blockCols

unsafeFreeze :: (Elem a, KnownNat n, KnownNat m, PrimMonad p) => MMatrix n m (PrimState p) a -> p (Matrix n m a) Source #

Turn a mutable matrix into an immutable matrix without copying. The mutable matrix should not be modified after this conversion.

unsafeWith :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> (Ptr (C a) -> CInt -> CInt -> IO b) -> IO b Source #

Pass a pointer to the matrix's data to the IO action. The data may not be modified through the pointer.

fromList :: forall n m a. (Elem a, KnownNat n, KnownNat m) => [[a]] -> Maybe (Matrix n m a) Source #

Convert a list to a matrix. Returns Nothing if the dimensions of the list do not match that of the matrix.

toList :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> [[a]] Source #

Convert a matrix to a list.