bed-and-breakfast-0.5: Efficient Matrix and Vector operations in 100% Haskell.

Safe HaskellTrustworthy
LanguageHaskell2010

Numeric.Matrix

Contents

Description

Efficient matrix operations in 100% pure Haskell.

This package uses miscellaneous implementations, depending on the type of its components. Typically unboxed arrays will perform best, while unboxed arrays give you certain features such as Rational or Complex components.

The following component types are supported by Matrix:

Int
Uses unboxed arrays internally. inv will always return Nothing.
Integer
Uses boxed arrays internally. inv will always return Nothing.
Double and Float
Uses unboxed arrays internally. All matrix operations will work as expected. Matrix Double will probably yield the best peformance.
Rational
Best choice if precision is what you aim for. Uses boxed arrays internally. All matrix operations will work as expected.
Complex
Experimental. Uses boxed arrays internally. All matrix operations will work as expected, though finding the inverse of a matrix isa tad less numerically stable than with a Double matrix.
Synopsis

Documentation

data family Matrix e Source #

Matrices are represented by a type which fits best the component type. For example a Matrix Double is represented by unboxed arrays, Matrix Integer by boxed arrays.

Data instances exist for Int, Float, Double, Integer, Ratio, and Complex. Certain types do have certain disadvantages, like for example you can not compute the inverse matrix of a Matrix Int.

Every matrix (regardless of the component type) has instances for Show, Read, Num, Fractional, Eq, Typeable, Binary, and NFData. This means that you can use arithmetic operations like +, *, and /, as well as functions like show, read, or typeOf.

Show (Matrix e)
Note that a Show instance for the component type e must exist.
Read (Matrix e)
You can read a matrix like so:
read "1 0\n0 1\n" :: Matrix Double
Num (Matrix e)
+, -, *, negate, abs, signum, and fromInteger.

signum will compute the determinant and return the signum of it.

abs applies map abs on the matrix (that is, it applies abs on every component in the matrix and returns a new matrix without negative components).

fromInteger yields a 1-x-1-matrix.

Fractional (Matrix e)
Only available if there exists an instance Fractional e (the component type needs to have a Fractional instance, too). Note that while the Num operations are safe, recip and / will fail (with an error) if the involved matrix is not invertible or not a square matrix.
NFData (Matrix e)
Matrices have instances for NFData so that you can use a matrix in parallel computations using the Control.Monad.Par monad (see the monad-par package for details).
Typeable (Matrix e)
Allows you to use matrices as Dynamic values.
Binary (Matrix e)
Serialize and unserialize matrices using the binary package. See encode and decode.
Instances
MatrixElement e => Eq (Matrix e) Source # 
Instance details

Defined in Numeric.Matrix

Methods

(==) :: Matrix e -> Matrix e -> Bool #

(/=) :: Matrix e -> Matrix e -> Bool #

(MatrixElement e, Fractional e) => Fractional (Matrix e) Source # 
Instance details

Defined in Numeric.Matrix

Methods

(/) :: Matrix e -> Matrix e -> Matrix e #

recip :: Matrix e -> Matrix e #

fromRational :: Rational -> Matrix e #

MatrixElement e => Num (Matrix e) Source # 
Instance details

Defined in Numeric.Matrix

Methods

(+) :: Matrix e -> Matrix e -> Matrix e #

(-) :: Matrix e -> Matrix e -> Matrix e #

(*) :: Matrix e -> Matrix e -> Matrix e #

negate :: Matrix e -> Matrix e #

abs :: Matrix e -> Matrix e #

signum :: Matrix e -> Matrix e #

fromInteger :: Integer -> Matrix e #

(Read e, MatrixElement e) => Read (Matrix e) Source # 
Instance details

Defined in Numeric.Matrix

(MatrixElement e, Show e) => Show (Matrix e) Source # 
Instance details

Defined in Numeric.Matrix

Methods

showsPrec :: Int -> Matrix e -> ShowS #

show :: Matrix e -> String #

showList :: [Matrix e] -> ShowS #

(MatrixElement e, Binary e) => Binary (Matrix e) Source # 
Instance details

Defined in Numeric.Matrix

Methods

put :: Matrix e -> Put #

get :: Get (Matrix e) #

putList :: [Matrix e] -> Put #

MatrixElement e => NFData (Matrix e) Source # 
Instance details

Defined in Numeric.Matrix

Methods

rnf :: Matrix e -> () #

data Matrix Double Source # 
Instance details

Defined in Numeric.Matrix

data Matrix Float Source # 
Instance details

Defined in Numeric.Matrix

data Matrix Int Source # 
Instance details

Defined in Numeric.Matrix

data Matrix Integer Source # 
Instance details

Defined in Numeric.Matrix

data Matrix (Ratio a) Source # 
Instance details

Defined in Numeric.Matrix

data Matrix (Complex a) Source # 
Instance details

Defined in Numeric.Matrix

class (Eq e, Num e) => MatrixElement e where Source #

Minimal complete definition

matrix, fromList, toList, det, rank

Methods

matrix :: (Int, Int) -> ((Int, Int) -> e) -> Matrix e Source #

Creates a matrix of the given size using a generator function for the value of each component.

select :: ((Int, Int) -> Bool) -> Matrix e -> [e] Source #

Builds a list from a matrix for the indices for which the given predicate matches.

trace == select (uncurry (==))

at :: Matrix e -> (Int, Int) -> e Source #

Returns the component at the given position in the matrix. Note that indices start at one, not at zero.

row :: Int -> Matrix e -> [e] Source #

Returns the row at the given index in the matrix. Note that indices start at one, not at zero.

col :: Int -> Matrix e -> [e] Source #

Returns the row at the given index in the matrix. Note that indices start at one, not at zero.

dimensions :: Matrix e -> (Int, Int) Source #

The dimensions of a given matrix.

numRows :: Matrix e -> Int Source #

The number of rows in the given matrix.

numCols :: Matrix e -> Int Source #

The number of columns in the given matrix.

fromList :: [[e]] -> Matrix e Source #

Builds a matrix from a list of lists.

The innermost lists represent the rows. This function will create a m-n-matrix, where m is the number of rows, which is the minimum length of the row lists and n is the number of columns, i.e. the length of the outer list.

fromList [[1,2,3],[2,1,3],[3,2,1]] :: Matrix Rational

toList :: Matrix e -> [[e]] Source #

Turns a matrix into a list of lists.

(toList . fromList) xs == xs
(fromList . toList) mat == mat

unit :: Int -> Matrix e Source #

An identity square matrix of the given size.

>>> unit 4
1 0 0 0
0 1 0 0
0 0 1 0
0 0 0 1

zero :: Int -> Matrix e Source #

A square matrix of the given size consisting of all zeros.

>>> zero 2
0 0
0 0

diag :: [e] -> Matrix e Source #

A square matrix which trace is the given list, all other components set to zero.

>>> diag [1,4,7,9]
1 0 0 0
0 4 0 0
0 0 7 0
0 0 0 9

empty :: Matrix e Source #

Check whether the matrix is the empty matrix.

dimensions empty == (0, 0)

minus :: Matrix e -> Matrix e -> Matrix e Source #

Subtract a matrix from another.

plus :: Matrix e -> Matrix e -> Matrix e Source #

Add two matrices.

You may also use the Num instance for matrices, i.e. matrix1 + matrix2 will work, too.

times :: Matrix e -> Matrix e -> Matrix e Source #

Multiply two matrices O(n^3).

You may also use the Num instance for matrices, i.e. matrix1 * matrix2 will work, too.

inv :: Matrix e -> Maybe (Matrix e) Source #

Compute the inverse of a matrix. Returns Nothing if the matrix is not invertible.

det :: Matrix e -> e Source #

Applies Bareiss multistep integer-preserving algorithm for finding the determinant of a matrix. Returns 0 if the matrix is not a square matrix.

transpose :: Matrix e -> Matrix e Source #

Flip rows and columns.

1 8 9                1 2 3
2 1 8  --transpose-> 8 1 2
3 2 1                9 8 1 

rank :: Matrix e -> e Source #

Compute the rank of a matrix.

trace :: Matrix e -> [e] Source #

Select the diagonal elements of a matrix as a list.

1 8 3
3 6 5 --trace-> [1, 6, 2]
7 4 2

minor :: MatrixElement e => (Int, Int) -> Matrix e -> e Source #

Select the minor of a matrix, that is the determinant of the minorMatrix.

minor = det . minorMatrix

minorMatrix :: MatrixElement e => (Int, Int) -> Matrix e -> Matrix e Source #

Select the minor matrix of a matrix, a matrix that is obtained by deleting the i-th row and j-th column.

10  9 95 45
 8  7  3 27                        8  3 27
13 17 19 23 --minorMatrix (1,2)-> 13 19 23
 1  2  5  8                        1  5  8

cofactors :: MatrixElement e => Matrix e -> Matrix e Source #

adjugate :: MatrixElement e => Matrix e -> Matrix e Source #

map :: MatrixElement f => (e -> f) -> Matrix e -> Matrix f Source #

Apply a function on every component in the matrix.

all :: (e -> Bool) -> Matrix e -> Bool Source #

Apply a predicate on every component in the matrix and returns True iff all components satisfy it.

any :: (e -> Bool) -> Matrix e -> Bool Source #

Apply a predicate on every component in the matrix and return True if one or more components satisfy it.

sum :: Matrix e -> e Source #

Compute the sum of the components of the matrix.

foldMap :: Monoid m => (e -> m) -> Matrix e -> m Source #

Map each component of the matrix to a monoid, and combine the results.

mapWithIndex :: MatrixElement f => ((Int, Int) -> e -> f) -> Matrix e -> Matrix f Source #

allWithIndex :: ((Int, Int) -> e -> Bool) -> Matrix e -> Bool Source #

anyWithIndex :: ((Int, Int) -> e -> Bool) -> Matrix e -> Bool Source #

foldMapWithIndex :: Monoid m => ((Int, Int) -> e -> m) -> Matrix e -> m Source #

Instances
MatrixElement Double Source # 
Instance details

Defined in Numeric.Matrix

Methods

matrix :: (Int, Int) -> ((Int, Int) -> Double) -> Matrix Double Source #

select :: ((Int, Int) -> Bool) -> Matrix Double -> [Double] Source #

at :: Matrix Double -> (Int, Int) -> Double Source #

row :: Int -> Matrix Double -> [Double] Source #

col :: Int -> Matrix Double -> [Double] Source #

dimensions :: Matrix Double -> (Int, Int) Source #

numRows :: Matrix Double -> Int Source #

numCols :: Matrix Double -> Int Source #

fromList :: [[Double]] -> Matrix Double Source #

toList :: Matrix Double -> [[Double]] Source #

unit :: Int -> Matrix Double Source #

zero :: Int -> Matrix Double Source #

diag :: [Double] -> Matrix Double Source #

empty :: Matrix Double Source #

minus :: Matrix Double -> Matrix Double -> Matrix Double Source #

plus :: Matrix Double -> Matrix Double -> Matrix Double Source #

times :: Matrix Double -> Matrix Double -> Matrix Double Source #

inv :: Matrix Double -> Maybe (Matrix Double) Source #

det :: Matrix Double -> Double Source #

transpose :: Matrix Double -> Matrix Double Source #

rank :: Matrix Double -> Double Source #

trace :: Matrix Double -> [Double] Source #

minor :: (Int, Int) -> Matrix Double -> Double Source #

minorMatrix :: (Int, Int) -> Matrix Double -> Matrix Double Source #

cofactors :: Matrix Double -> Matrix Double Source #

adjugate :: Matrix Double -> Matrix Double Source #

map :: MatrixElement f => (Double -> f) -> Matrix Double -> Matrix f Source #

all :: (Double -> Bool) -> Matrix Double -> Bool Source #

any :: (Double -> Bool) -> Matrix Double -> Bool Source #

sum :: Matrix Double -> Double Source #

foldMap :: Monoid m => (Double -> m) -> Matrix Double -> m Source #

mapWithIndex :: MatrixElement f => ((Int, Int) -> Double -> f) -> Matrix Double -> Matrix f Source #

allWithIndex :: ((Int, Int) -> Double -> Bool) -> Matrix Double -> Bool Source #

anyWithIndex :: ((Int, Int) -> Double -> Bool) -> Matrix Double -> Bool Source #

foldMapWithIndex :: Monoid m => ((Int, Int) -> Double -> m) -> Matrix Double -> m Source #

MatrixElement Float Source # 
Instance details

Defined in Numeric.Matrix

Methods

matrix :: (Int, Int) -> ((Int, Int) -> Float) -> Matrix Float Source #

select :: ((Int, Int) -> Bool) -> Matrix Float -> [Float] Source #

at :: Matrix Float -> (Int, Int) -> Float Source #

row :: Int -> Matrix Float -> [Float] Source #

col :: Int -> Matrix Float -> [Float] Source #

dimensions :: Matrix Float -> (Int, Int) Source #

numRows :: Matrix Float -> Int Source #

numCols :: Matrix Float -> Int Source #

fromList :: [[Float]] -> Matrix Float Source #

toList :: Matrix Float -> [[Float]] Source #

unit :: Int -> Matrix Float Source #

zero :: Int -> Matrix Float Source #

diag :: [Float] -> Matrix Float Source #

empty :: Matrix Float Source #

minus :: Matrix Float -> Matrix Float -> Matrix Float Source #

plus :: Matrix Float -> Matrix Float -> Matrix Float Source #

times :: Matrix Float -> Matrix Float -> Matrix Float Source #

inv :: Matrix Float -> Maybe (Matrix Float) Source #

det :: Matrix Float -> Float Source #

transpose :: Matrix Float -> Matrix Float Source #

rank :: Matrix Float -> Float Source #

trace :: Matrix Float -> [Float] Source #

minor :: (Int, Int) -> Matrix Float -> Float Source #

minorMatrix :: (Int, Int) -> Matrix Float -> Matrix Float Source #

cofactors :: Matrix Float -> Matrix Float Source #

adjugate :: Matrix Float -> Matrix Float Source #

map :: MatrixElement f => (Float -> f) -> Matrix Float -> Matrix f Source #

all :: (Float -> Bool) -> Matrix Float -> Bool Source #

any :: (Float -> Bool) -> Matrix Float -> Bool Source #

sum :: Matrix Float -> Float Source #

foldMap :: Monoid m => (Float -> m) -> Matrix Float -> m Source #

mapWithIndex :: MatrixElement f => ((Int, Int) -> Float -> f) -> Matrix Float -> Matrix f Source #

allWithIndex :: ((Int, Int) -> Float -> Bool) -> Matrix Float -> Bool Source #

anyWithIndex :: ((Int, Int) -> Float -> Bool) -> Matrix Float -> Bool Source #

foldMapWithIndex :: Monoid m => ((Int, Int) -> Float -> m) -> Matrix Float -> m Source #

MatrixElement Int Source # 
Instance details

Defined in Numeric.Matrix

Methods

matrix :: (Int, Int) -> ((Int, Int) -> Int) -> Matrix Int Source #

select :: ((Int, Int) -> Bool) -> Matrix Int -> [Int] Source #

at :: Matrix Int -> (Int, Int) -> Int Source #

row :: Int -> Matrix Int -> [Int] Source #

col :: Int -> Matrix Int -> [Int] Source #

dimensions :: Matrix Int -> (Int, Int) Source #

numRows :: Matrix Int -> Int Source #

numCols :: Matrix Int -> Int Source #

fromList :: [[Int]] -> Matrix Int Source #

toList :: Matrix Int -> [[Int]] Source #

unit :: Int -> Matrix Int Source #

zero :: Int -> Matrix Int Source #

diag :: [Int] -> Matrix Int Source #

empty :: Matrix Int Source #

minus :: Matrix Int -> Matrix Int -> Matrix Int Source #

plus :: Matrix Int -> Matrix Int -> Matrix Int Source #

times :: Matrix Int -> Matrix Int -> Matrix Int Source #

inv :: Matrix Int -> Maybe (Matrix Int) Source #

det :: Matrix Int -> Int Source #

transpose :: Matrix Int -> Matrix Int Source #

rank :: Matrix Int -> Int Source #

trace :: Matrix Int -> [Int] Source #

minor :: (Int, Int) -> Matrix Int -> Int Source #

minorMatrix :: (Int, Int) -> Matrix Int -> Matrix Int Source #

cofactors :: Matrix Int -> Matrix Int Source #

adjugate :: Matrix Int -> Matrix Int Source #

map :: MatrixElement f => (Int -> f) -> Matrix Int -> Matrix f Source #

all :: (Int -> Bool) -> Matrix Int -> Bool Source #

any :: (Int -> Bool) -> Matrix Int -> Bool Source #

sum :: Matrix Int -> Int Source #

foldMap :: Monoid m => (Int -> m) -> Matrix Int -> m Source #

mapWithIndex :: MatrixElement f => ((Int, Int) -> Int -> f) -> Matrix Int -> Matrix f Source #

allWithIndex :: ((Int, Int) -> Int -> Bool) -> Matrix Int -> Bool Source #

anyWithIndex :: ((Int, Int) -> Int -> Bool) -> Matrix Int -> Bool Source #

foldMapWithIndex :: Monoid m => ((Int, Int) -> Int -> m) -> Matrix Int -> m Source #

MatrixElement Integer Source # 
Instance details

Defined in Numeric.Matrix

Methods

matrix :: (Int, Int) -> ((Int, Int) -> Integer) -> Matrix Integer Source #

select :: ((Int, Int) -> Bool) -> Matrix Integer -> [Integer] Source #

at :: Matrix Integer -> (Int, Int) -> Integer Source #

row :: Int -> Matrix Integer -> [Integer] Source #

col :: Int -> Matrix Integer -> [Integer] Source #

dimensions :: Matrix Integer -> (Int, Int) Source #

numRows :: Matrix Integer -> Int Source #

numCols :: Matrix Integer -> Int Source #

fromList :: [[Integer]] -> Matrix Integer Source #

toList :: Matrix Integer -> [[Integer]] Source #

unit :: Int -> Matrix Integer Source #

zero :: Int -> Matrix Integer Source #

diag :: [Integer] -> Matrix Integer Source #

empty :: Matrix Integer Source #

minus :: Matrix Integer -> Matrix Integer -> Matrix Integer Source #

plus :: Matrix Integer -> Matrix Integer -> Matrix Integer Source #

times :: Matrix Integer -> Matrix Integer -> Matrix Integer Source #

inv :: Matrix Integer -> Maybe (Matrix Integer) Source #

det :: Matrix Integer -> Integer Source #

transpose :: Matrix Integer -> Matrix Integer Source #

rank :: Matrix Integer -> Integer Source #

trace :: Matrix Integer -> [Integer] Source #

minor :: (Int, Int) -> Matrix Integer -> Integer Source #

minorMatrix :: (Int, Int) -> Matrix Integer -> Matrix Integer Source #

cofactors :: Matrix Integer -> Matrix Integer Source #

adjugate :: Matrix Integer -> Matrix Integer Source #

map :: MatrixElement f => (Integer -> f) -> Matrix Integer -> Matrix f Source #

all :: (Integer -> Bool) -> Matrix Integer -> Bool Source #

any :: (Integer -> Bool) -> Matrix Integer -> Bool Source #

sum :: Matrix Integer -> Integer Source #

foldMap :: Monoid m => (Integer -> m) -> Matrix Integer -> m Source #

mapWithIndex :: MatrixElement f => ((Int, Int) -> Integer -> f) -> Matrix Integer -> Matrix f Source #

allWithIndex :: ((Int, Int) -> Integer -> Bool) -> Matrix Integer -> Bool Source #

anyWithIndex :: ((Int, Int) -> Integer -> Bool) -> Matrix Integer -> Bool Source #

foldMapWithIndex :: Monoid m => ((Int, Int) -> Integer -> m) -> Matrix Integer -> m Source #

(Show a, Integral a) => MatrixElement (Ratio a) Source # 
Instance details

Defined in Numeric.Matrix

Methods

matrix :: (Int, Int) -> ((Int, Int) -> Ratio a) -> Matrix (Ratio a) Source #

select :: ((Int, Int) -> Bool) -> Matrix (Ratio a) -> [Ratio a] Source #

at :: Matrix (Ratio a) -> (Int, Int) -> Ratio a Source #

row :: Int -> Matrix (Ratio a) -> [Ratio a] Source #

col :: Int -> Matrix (Ratio a) -> [Ratio a] Source #

dimensions :: Matrix (Ratio a) -> (Int, Int) Source #

numRows :: Matrix (Ratio a) -> Int Source #

numCols :: Matrix (Ratio a) -> Int Source #

fromList :: [[Ratio a]] -> Matrix (Ratio a) Source #

toList :: Matrix (Ratio a) -> [[Ratio a]] Source #

unit :: Int -> Matrix (Ratio a) Source #

zero :: Int -> Matrix (Ratio a) Source #

diag :: [Ratio a] -> Matrix (Ratio a) Source #

empty :: Matrix (Ratio a) Source #

minus :: Matrix (Ratio a) -> Matrix (Ratio a) -> Matrix (Ratio a) Source #

plus :: Matrix (Ratio a) -> Matrix (Ratio a) -> Matrix (Ratio a) Source #

times :: Matrix (Ratio a) -> Matrix (Ratio a) -> Matrix (Ratio a) Source #

inv :: Matrix (Ratio a) -> Maybe (Matrix (Ratio a)) Source #

det :: Matrix (Ratio a) -> Ratio a Source #

transpose :: Matrix (Ratio a) -> Matrix (Ratio a) Source #

rank :: Matrix (Ratio a) -> Ratio a Source #

trace :: Matrix (Ratio a) -> [Ratio a] Source #

minor :: (Int, Int) -> Matrix (Ratio a) -> Ratio a Source #

minorMatrix :: (Int, Int) -> Matrix (Ratio a) -> Matrix (Ratio a) Source #

cofactors :: Matrix (Ratio a) -> Matrix (Ratio a) Source #

adjugate :: Matrix (Ratio a) -> Matrix (Ratio a) Source #

map :: MatrixElement f => (Ratio a -> f) -> Matrix (Ratio a) -> Matrix f Source #

all :: (Ratio a -> Bool) -> Matrix (Ratio a) -> Bool Source #

any :: (Ratio a -> Bool) -> Matrix (Ratio a) -> Bool Source #

sum :: Matrix (Ratio a) -> Ratio a Source #

foldMap :: Monoid m => (Ratio a -> m) -> Matrix (Ratio a) -> m Source #

mapWithIndex :: MatrixElement f => ((Int, Int) -> Ratio a -> f) -> Matrix (Ratio a) -> Matrix f Source #

allWithIndex :: ((Int, Int) -> Ratio a -> Bool) -> Matrix (Ratio a) -> Bool Source #

anyWithIndex :: ((Int, Int) -> Ratio a -> Bool) -> Matrix (Ratio a) -> Bool Source #

foldMapWithIndex :: Monoid m => ((Int, Int) -> Ratio a -> m) -> Matrix (Ratio a) -> m Source #

(Show a, RealFloat a) => MatrixElement (Complex a) Source # 
Instance details

Defined in Numeric.Matrix

Methods

matrix :: (Int, Int) -> ((Int, Int) -> Complex a) -> Matrix (Complex a) Source #

select :: ((Int, Int) -> Bool) -> Matrix (Complex a) -> [Complex a] Source #

at :: Matrix (Complex a) -> (Int, Int) -> Complex a Source #

row :: Int -> Matrix (Complex a) -> [Complex a] Source #

col :: Int -> Matrix (Complex a) -> [Complex a] Source #

dimensions :: Matrix (Complex a) -> (Int, Int) Source #

numRows :: Matrix (Complex a) -> Int Source #

numCols :: Matrix (Complex a) -> Int Source #

fromList :: [[Complex a]] -> Matrix (Complex a) Source #

toList :: Matrix (Complex a) -> [[Complex a]] Source #

unit :: Int -> Matrix (Complex a) Source #

zero :: Int -> Matrix (Complex a) Source #

diag :: [Complex a] -> Matrix (Complex a) Source #

empty :: Matrix (Complex a) Source #

minus :: Matrix (Complex a) -> Matrix (Complex a) -> Matrix (Complex a) Source #

plus :: Matrix (Complex a) -> Matrix (Complex a) -> Matrix (Complex a) Source #

times :: Matrix (Complex a) -> Matrix (Complex a) -> Matrix (Complex a) Source #

inv :: Matrix (Complex a) -> Maybe (Matrix (Complex a)) Source #

det :: Matrix (Complex a) -> Complex a Source #

transpose :: Matrix (Complex a) -> Matrix (Complex a) Source #

rank :: Matrix (Complex a) -> Complex a Source #

trace :: Matrix (Complex a) -> [Complex a] Source #

minor :: (Int, Int) -> Matrix (Complex a) -> Complex a Source #

minorMatrix :: (Int, Int) -> Matrix (Complex a) -> Matrix (Complex a) Source #

cofactors :: Matrix (Complex a) -> Matrix (Complex a) Source #

adjugate :: Matrix (Complex a) -> Matrix (Complex a) Source #

map :: MatrixElement f => (Complex a -> f) -> Matrix (Complex a) -> Matrix f Source #

all :: (Complex a -> Bool) -> Matrix (Complex a) -> Bool Source #

any :: (Complex a -> Bool) -> Matrix (Complex a) -> Bool Source #

sum :: Matrix (Complex a) -> Complex a Source #

foldMap :: Monoid m => (Complex a -> m) -> Matrix (Complex a) -> m Source #

mapWithIndex :: MatrixElement f => ((Int, Int) -> Complex a -> f) -> Matrix (Complex a) -> Matrix f Source #

allWithIndex :: ((Int, Int) -> Complex a -> Bool) -> Matrix (Complex a) -> Bool Source #

anyWithIndex :: ((Int, Int) -> Complex a -> Bool) -> Matrix (Complex a) -> Bool Source #

foldMapWithIndex :: Monoid m => ((Int, Int) -> Complex a -> m) -> Matrix (Complex a) -> m Source #

Matrix property and utility functions.

(<|>) :: MatrixElement e => Matrix e -> Matrix e -> Matrix e Source #

Joins two matrices horizontally.

1 2 3     1 0 0      1 2 3 1 0 0
3 4 5 <|> 2 1 0  ->  3 4 5 2 1 0
5 6 7     3 2 1      5 6 7 3 2 1

(<->) :: MatrixElement e => Matrix e -> Matrix e -> Matrix e Source #

Joins two matrices vertically.

1 2 3     1 0 0      1 2 3
3 4 5 <-> 2 1 0  ->  3 4 5
5 6 7     3 2 1      5 6 7
                     1 0 0
                     2 1 0
                     3 2 1

scale :: MatrixElement e => Matrix e -> e -> Matrix e Source #

Scales a matrix by the given factor.

scale s == map (*s)

Matrix properties

isUnit :: MatrixElement e => Matrix e -> Bool Source #

Check whether the matrix is an identity matrix.

1 0 0
0 1 0
0 0 1 (True)

isZero :: MatrixElement e => Matrix e -> Bool Source #

Check whether the matrix consists of all zeros.

isZero == all (== 0)

isDiagonal :: MatrixElement e => Matrix e -> Bool Source #

Checks whether the matrix is a diagonal matrix.

4 0 0 0
0 7 0 0
0 0 3 0
0 0 0 9 (True)

isEmpty :: MatrixElement e => Matrix e -> Bool Source #

Checks whether the matrix is empty.

isEmpty m = numCols == 0 || numRows == 0

isSquare :: MatrixElement e => Matrix e -> Bool Source #

Checks whether the matrix is a square matrix.

isSquare == uncurry (==) . dimensions

Conversions