Copyright | (c) Wanja Chresta 2018 |
---|---|
License | GPL-3 |
Maintainer | wanja dot hs at chrummibei dot ch |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Math.Algebra.Matrix wraps matrix
's Data.Matrix functions and adds size
information on the type level. Additionally, it fixes some issues that makes
the library work well with finite fields. The name of most functions is the
same as in Data.Matrix
- newtype Matrix (m :: Nat) (n :: Nat) (f :: *) = Matrix (Matrix f)
- matrix :: forall m n a. (KnownNat m, KnownNat n) => ((Int, Int) -> a) -> Matrix (m :: Nat) (n :: Nat) a
- type Vector = Matrix 1
- transpose :: forall m n a. Matrix m n a -> Matrix n m a
- (<|>) :: forall m n k a. (KnownNat n, KnownNat k) => Matrix m n a -> Matrix m k a -> Matrix m (k + n) a
- (<->) :: forall m k n a. (KnownNat m, KnownNat k) => Matrix m n a -> Matrix k n a -> Matrix (m + k) n a
- identity :: forall n a. (Num a, KnownNat n) => Matrix n n a
- zero :: forall m n a. (Num a, KnownNat n, KnownNat m) => Matrix m n a
- fromList :: forall m n a. (KnownNat m, KnownNat n) => [a] -> Matrix m n a
- fromLists :: forall m n a. (KnownNat m, KnownNat n) => [[a]] -> Matrix m n a
- toList :: forall m n a. Matrix m n a -> [a]
- toLists :: forall m n a. Matrix m n a -> [[a]]
- (.*) :: forall m k n a. Num a => Matrix m k a -> Matrix k n a -> Matrix m n a
- (^*) :: forall m n a. Num a => a -> Matrix m n a -> Matrix m n a
- rref :: forall m n a. (KnownNat m, KnownNat n, m <= n, Fractional a, Eq a) => Matrix m n a -> Matrix m n a
- submatrix :: forall m n m' n' a. (KnownNat m, KnownNat n, KnownNat m', KnownNat n', m' <= m, n' <= n) => Int -> Int -> Matrix m n a -> Matrix m' n' a
Documentation
newtype Matrix (m :: Nat) (n :: Nat) (f :: *) Source #
A matrix over the type f
with m
rows and n
columns. This just wraps
the Matrix
constructor and adds size information to the type
Matrix (Matrix f) |
Functor (Matrix m n) Source # | |
Applicative (Matrix m n) Source # | |
Foldable (Matrix m n) Source # | |
Traversable (Matrix m n) Source # | |
Eq f => Eq (Matrix m n f) Source # | |
Num f => Num (Matrix m n f) Source # | |
Ord f => Ord (Matrix m n f) Source # | |
Show f => Show (Matrix m n f) Source # | |
Monoid f => Monoid (Matrix m n f) Source # | |
(KnownNat m, KnownNat n, Random a) => Random (Matrix m n a) Source # | |
matrix :: forall m n a. (KnownNat m, KnownNat n) => ((Int, Int) -> a) -> Matrix (m :: Nat) (n :: Nat) a Source #
O(rows*cols). Generate a matrix from a generator function.
| The elements are 1-indexed, i.e. top-left element is (1,1)
.
transpose :: forall m n a. Matrix m n a -> Matrix n m a Source #
O(rows*cols). The transpose of a matrix.
(<|>) :: forall m n k a. (KnownNat n, KnownNat k) => Matrix m n a -> Matrix m k a -> Matrix m (k + n) a Source #
Horizontally join two matrices. Visually:
( A ) <|> ( B ) = ( A | B )
(<->) :: forall m k n a. (KnownNat m, KnownNat k) => Matrix m n a -> Matrix k n a -> Matrix (m + k) n a Source #
Horizontally join two matrices. Visually:
( A ) ( A ) <-> ( B ) = ( - ) ( B )
zero :: forall m n a. (Num a, KnownNat n, KnownNat m) => Matrix m n a Source #
O(rows*cols). The zero matrix
fromList :: forall m n a. (KnownNat m, KnownNat n) => [a] -> Matrix m n a Source #
Create a matrix from a list of elements.
The list must have exactly length n*m
. This is checked or else an
exception is thrown.
fromLists :: forall m n a. (KnownNat m, KnownNat n) => [[a]] -> Matrix m n a Source #
Create a matrix from a list of rows. The list must have exactly m
lists of length n
. An exception is thrown otherwise.
toLists :: forall m n a. Matrix m n a -> [[a]] Source #
Get the elements of a matrix stored in a list of lists, where each list contains the elements of a single row.
(.*) :: forall m k n a. Num a => Matrix m k a -> Matrix k n a -> Matrix m n a Source #
Type safe matrix multiplication
(^*) :: forall m n a. Num a => a -> Matrix m n a -> Matrix m n a Source #
Type safe scalar multiplication
rref :: forall m n a. (KnownNat m, KnownNat n, m <= n, Fractional a, Eq a) => Matrix m n a -> Matrix m n a Source #
Reduced row echelon form. Taken from rosettacode. This is not the
implementation provided by the matrix
package.
https://rosettacode.org/wiki/Reduced_row_echelon_form#Haskell
submatrix :: forall m n m' n' a. (KnownNat m, KnownNat n, KnownNat m', KnownNat n', m' <= m, n' <= n) => Int -> Int -> Matrix m n a -> Matrix m' n' a Source #
O(1). Extract a submatrix from the given position. The size of the extract is determined by the types, i.e. the parameters define which element is the top-left element of the extract. CAUTION: It is not checked if an extract is possible. Wrong parameters will cause an exception.