Copyright | (c) Henning Thielemann 2009 Mikael Johansson 2006 |
---|---|
Maintainer | numericprelude@henning-thielemann.de |
Stability | provisional |
Portability | requires multi-parameter type classes |
Safe Haskell | None |
Language | Haskell98 |
MathObj.Matrix
Description
Routines and abstractions for Matrices and basic linear algebra over fields or rings.
We stick to simple Int indices. Although advanced indices would be nice e.g. for matrices with sub-matrices, this is not easily implemented since arrays do only support a lower and an upper bound but no additional parameters.
ToDo: - Matrix inverse, determinant (see htam:Matrix)
Synopsis
- data T a
- type Dimension = Int
- format :: Show a => T a -> String
- transpose :: T a -> T a
- rows :: T a -> [[a]]
- columns :: T a -> [[a]]
- index :: T a -> Dimension -> Dimension -> a
- fromRows :: Dimension -> Dimension -> [[a]] -> T a
- fromColumns :: Dimension -> Dimension -> [[a]] -> T a
- fromList :: Dimension -> Dimension -> [a] -> T a
- dimension :: T a -> (Dimension, Dimension)
- numRows :: T a -> Dimension
- numColumns :: T a -> Dimension
- zipWith :: (a -> b -> c) -> T a -> T b -> T c
- zero :: C a => Dimension -> Dimension -> T a
- one :: C a => Dimension -> T a
- diagonal :: C a => [a] -> T a
- scale :: C a => a -> T a -> T a
- random :: (RandomGen g, Random a) => Dimension -> Dimension -> g -> (T a, g)
- randomR :: (RandomGen g, Random a) => Dimension -> Dimension -> (a, a) -> g -> (T a, g)
Documentation
A matrix is a twodimensional array, indexed by integers.
Instances
Functor T Source # | |
C T Source # | |
C a b => C a (T b) Source # | |
Eq a => Eq (T a) Source # | |
Ord a => Ord (T a) Source # | |
Read a => Read (T a) Source # | |
Show a => Show (T a) Source # | |
C a => C (T a) Source # | genIntMatrix /\ \a -> genSameMatrix a /\ \b -> Laws.commutative (+) a b genIntMatrix /\ \a -> genSameMatrix a /\ \b -> genSameMatrix b /\ \c -> Laws.associative (+) a b c |
C a => C (T a) Source # | genIntMatrix /\ \a -> Laws.leftIdentity (*) (Matrix.one (Matrix.numRows a)) a genIntMatrix /\ \a -> Laws.rightIdentity (*) (Matrix.one (Matrix.numColumns a)) a genIntMatrix /\ \a -> genFactorMatrix a /\ \b -> Laws.homomorphism Matrix.transpose (*) (flip (*)) a b genIntMatrix /\ \a -> genFactorMatrix a /\ \b -> genFactorMatrix b /\ \c -> Laws.associative (*) a b c genIntMatrix /\ \b -> genSameMatrix b /\ \c -> genFactorMatrix b /\ \a -> Laws.leftDistributive (*) (+) a b c genIntMatrix /\ \a -> genFactorMatrix a /\ \b -> genSameMatrix b /\ \c -> Laws.rightDistributive (*) (+) a b c QC.choose (0,10) /\ \k -> genDimension /\ \n -> genMatrixFor n n /\ \a -> a^k == nest (fromInteger k) ((a::Matrix.T Integer)*) (Matrix.one n) |
transpose :: T a -> T a Source #
Transposition of matrices is just transposition in the sense of Data.List.
genIntMatrix /\ \a -> Matrix.rows a == Matrix.columns (Matrix.transpose a)
genIntMatrix /\ \a -> Matrix.columns a == Matrix.rows (Matrix.transpose a)
genIntMatrix /\ \a -> genSameMatrix a /\ \b -> Laws.homomorphism Matrix.transpose (+) (+) a b
fromRows :: Dimension -> Dimension -> [[a]] -> T a Source #
genIntMatrix /\ \a -> a == uncurry Matrix.fromRows (Matrix.dimension a) (Matrix.rows a)
fromColumns :: Dimension -> Dimension -> [[a]] -> T a Source #
genIntMatrix /\ \a -> a == uncurry Matrix.fromColumns (Matrix.dimension a) (Matrix.columns a)
numColumns :: T a -> Dimension Source #
zero :: C a => Dimension -> Dimension -> T a Source #
genIntMatrix /\ \a -> Laws.identity (+) (uncurry Matrix.zero $ Matrix.dimension a) a