| Safe Haskell | Trustworthy |
|---|
Numeric.Matrix
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.
invwill always returnNothing. Integer- Uses boxed arrays internally.
invwill always returnNothing. DoubleandFloat- Uses unboxed arrays internally.
All matrix operations will work as expected.
Matrix Doublewill 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.
The current implementation of
invrequires an instance ofOrdfor the component type, therefor it is currently not possible to calculate the inverse of a complex matrix (on my to do list).
- data family Matrix e
- class (Eq e, Num e) => MatrixElement e where
- matrix :: (Int, Int) -> ((Int, Int) -> e) -> Matrix e
- select :: ((Int, Int) -> Bool) -> Matrix e -> [e]
- at :: Matrix e -> (Int, Int) -> e
- row :: Int -> Matrix e -> [e]
- col :: Int -> Matrix e -> [e]
- dimensions :: Matrix e -> (Int, Int)
- numRows :: Matrix e -> Int
- numCols :: Matrix e -> Int
- fromList :: [[e]] -> Matrix e
- toList :: Matrix e -> [[e]]
- unit :: Int -> Matrix e
- zero :: Int -> Matrix e
- diag :: [e] -> Matrix e
- empty :: Matrix e
- minus :: Matrix e -> Matrix e -> Matrix e
- plus :: Matrix e -> Matrix e -> Matrix e
- times :: Matrix e -> Matrix e -> Matrix e
- inv :: Matrix e -> Maybe (Matrix e)
- det :: Matrix e -> e
- transpose :: Matrix e -> Matrix e
- rank :: Matrix e -> e
- trace :: Matrix e -> [e]
- minor :: MatrixElement e => Matrix e -> (Int, Int) -> e
- cofactors :: MatrixElement e => Matrix e -> Matrix e
- adjugate :: MatrixElement e => Matrix e -> Matrix e
- minorMatrix :: MatrixElement e => Matrix e -> (Int, Int) -> Matrix e
- map :: MatrixElement f => (e -> f) -> Matrix e -> Matrix f
- all :: (e -> Bool) -> Matrix e -> Bool
- any :: (e -> Bool) -> Matrix e -> Bool
- mapWithIndex :: MatrixElement f => ((Int, Int) -> e -> f) -> Matrix e -> Matrix f
- allWithIndex :: ((Int, Int) -> e -> Bool) -> Matrix e -> Bool
- anyWithIndex :: ((Int, Int) -> e -> Bool) -> Matrix e -> Bool
- (<|>) :: MatrixElement e => Matrix e -> Matrix e -> Matrix e
- (<->) :: MatrixElement e => Matrix e -> Matrix e -> Matrix e
- scale :: MatrixElement e => Matrix e -> e -> Matrix e
- isUnit :: MatrixElement e => Matrix e -> Bool
- isZero :: MatrixElement e => Matrix e -> Bool
- isDiagonal :: MatrixElement e => Matrix e -> Bool
- isEmpty :: MatrixElement e => Matrix e -> Bool
- isSquare :: MatrixElement e => Matrix e -> Bool
Documentation
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, 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
emust exist. Read (Matrix e)- You can read a matrix like so:
read "1 0\n0 1\n" :: Matrix Double
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 aFractionalinstance, too). Note that while theNumoperations are safe,recipand/will fail (with anerror) 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.Parmonad (see themonad-parpackage for details). Typeable (Matrix e)-
Allows you to use matrices as
Dynamicvalues.
class (Eq e, Num e) => MatrixElement e whereSource
Methods
matrix :: (Int, Int) -> ((Int, Int) -> e) -> Matrix eSource
select :: ((Int, Int) -> Bool) -> Matrix e -> [e]Source
at :: Matrix e -> (Int, Int) -> eSource
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 -> IntSource
numCols :: Matrix e -> IntSource
fromList :: [[e]] -> Matrix eSource
Builds a matrix from a list of lists.
fromList [[1,2,3],[2,1,3],[3,2,1]] :: Matrix Rational
toList :: Matrix e -> [[e]]Source
An identity square matrix of the given size.
A square matrix of the given size consisting of all zeros.
Check whether the matrix is the empty matrix.
dimensions empty == (0, 0)
minus :: Matrix e -> Matrix e -> Matrix eSource
plus :: Matrix e -> Matrix e -> Matrix eSource
times :: Matrix e -> Matrix e -> Matrix eSource
inv :: Matrix e -> Maybe (Matrix 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 eSource
Flips rows and columns.
1 8 9 1 2 3 2 1 8 --transpose-> 8 1 2 3 2 1 9 8 1
trace :: Matrix e -> [e]Source
minor :: MatrixElement e => Matrix e -> (Int, Int) -> eSource
cofactors :: MatrixElement e => Matrix e -> Matrix eSource
adjugate :: MatrixElement e => Matrix e -> Matrix eSource
minorMatrix :: MatrixElement e => Matrix e -> (Int, Int) -> Matrix eSource
map :: MatrixElement f => (e -> f) -> Matrix e -> Matrix fSource
Applies a function on every component in the matrix.
all :: (e -> Bool) -> Matrix e -> BoolSource
Applies a predicate on every component in the matrix and returns True if all components satisfy it.
any :: (e -> Bool) -> Matrix e -> BoolSource
Applies a predicate on every component in the matrix and returns True if one or more components satisfy it.
mapWithIndex :: MatrixElement f => ((Int, Int) -> e -> f) -> Matrix e -> Matrix fSource
allWithIndex :: ((Int, Int) -> e -> Bool) -> Matrix e -> BoolSource
anyWithIndex :: ((Int, Int) -> e -> Bool) -> Matrix e -> BoolSource
Instances
| MatrixElement Double | |
| MatrixElement Float | |
| MatrixElement Int | |
| MatrixElement Integer | |
| (Show a, Integral a) => MatrixElement (Ratio a) | |
| (Show a, RealFloat a) => MatrixElement (Complex a) |
Matrix property and utility functions.
(<|>) :: MatrixElement e => Matrix e -> Matrix e -> Matrix eSource
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 eSource
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 eSource
Scales a matrix by the given factor.
scale s == map (*s)
Matrix properties
isUnit :: MatrixElement e => Matrix e -> BoolSource
Check whether the matrix is an identity matrix.
1 0 0 0 1 0 0 0 1 (True)
isZero :: MatrixElement e => Matrix e -> BoolSource
Check whether the matrix consists of all zeros.
isZero == all (== 0)
isDiagonal :: MatrixElement e => Matrix e -> BoolSource
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 -> BoolSource
Checks whether the matrix is empty.
isEmpty m = numCols == 0 || numRows == 0
isSquare :: MatrixElement e => Matrix e -> BoolSource
Checks whether the matrix is a square matrix.
isSquare == uncurry (==) . dimensions