sized-types-0.3.4.0: Sized types in Haskell.

Data.Sized.Matrix

Description

Sized matrixes.

Copyright: (c) 2009 University of Kansas License: BSD3

Maintainer: Andy Gill andygill@ku.edu Stability: unstable Portability: ghc

Synopsis

Documentation

data Matrix ix a Source

A Matrix is an array with the sized determined uniquely by the type of the index type, ix.

Constructors

Matrix (Array ix a) 
NullMatrix 

Instances

Size i => Functor (Matrix i) 
Size i => Applicative (Matrix i) 
Size ix => Foldable (Matrix ix) 
Size ix => Traversable (Matrix ix) 
(Eq a, Ix ix) => Eq (Matrix ix a) 
(Ord a, Ix ix) => Ord (Matrix ix a) 
(Show a, Size ix) => Show (Matrix ix a) 

(!) :: Size n => Matrix n a -> n -> aSource

! looks up an element in the matrix.

toList :: Size i => Matrix i a -> [a]Source

toList turns a matrix into an always finite list.

fromList :: forall i a. Size i => [a] -> Matrix i aSource

fromList turns a finite list into a matrix. You often need to give the type of the result.

matrix :: Size i => [a] -> Matrix i aSource

matrix turns a finite list into a matrix. You often need to give the type of the result.

indices :: Size i => Matrix i a -> [i]Source

indices is a version of all that takes a type, for forcing the result type using the Matrix type.

length :: Size i => Matrix i a -> IntSource

what is the length of a matrix?

assocs :: Size i => Matrix i a -> [(i, a)]Source

assocs extracts the index/value pairs.

(//) :: Size i => Matrix i e -> [(i, e)] -> Matrix i eSource

accum :: Size i => (e -> a -> e) -> Matrix i e -> [(i, a)] -> Matrix i eSource

zeroOf :: Size i => Matrix i a -> iSource

zeroOf is for use to force typing issues, and is 0.

coord :: Size i => Matrix i iSource

coord returns a matrix filled with indexes.

zipWith :: Size i => (a -> b -> c) -> Matrix i a -> Matrix i b -> Matrix i cSource

Same as for lists.

forEach :: Size i => Matrix i a -> (i -> a -> b) -> Matrix i bSource

forEach takes a matrix, and calls a function for each element, to give a new matrix of the same size.

forAll :: Size i => (i -> a) -> Matrix i aSource

forAll creates a matrix out of a mapping from the coordinates.

mm :: (Size m, Size n, Size m', Size n', n ~ m', Num a) => Matrix (m, n) a -> Matrix (m', n') a -> Matrix (m, n') aSource

mm is the 2D matrix multiply.

transpose :: (Size x, Size y) => Matrix (x, y) a -> Matrix (y, x) aSource

transpose a 2D matrix.

identity :: (Size x, Num a) => Matrix (x, x) aSource

return the identity for a specific matrix size.

above :: (Size m, Size top, Size bottom, Size both, ADD top bottom ~ both, SUB both top ~ bottom, SUB both bottom ~ top) => Matrix (top, m) a -> Matrix (bottom, m) a -> Matrix (both, m) aSource

stack two matrixes above each other.

beside :: (Size m, Size left, Size right, Size both, ADD left right ~ both, SUB both left ~ right, SUB both right ~ left) => Matrix (m, left) a -> Matrix (m, right) a -> Matrix (m, both) aSource

stack two matrixes beside each other.

append :: (Size left, Size right, Size both, ADD left right ~ both, SUB both left ~ right, SUB both right ~ left) => Matrix left a -> Matrix right a -> Matrix both aSource

append two 1-d matrixes

ixmap :: (Size i, Size j) => (i -> j) -> Matrix j a -> Matrix i aSource

look at a matrix through a lens to another matrix.

ixfmap :: (Size i, Size j, Functor f) => (i -> f j) -> Matrix j a -> Matrix i (f a)Source

look at a matrix through a functor lens, to another matrix.

cropAt :: (Index i ~ Index ix, Size i, Size ix) => Matrix ix a -> ix -> Matrix i aSource

grab part of a matrix.

rows :: (Bounded n, Size n, Bounded m, Size m) => Matrix (m, n) a -> Matrix m (Matrix n a)Source

slice a 2D matrix into rows.

columns :: (Bounded n, Size n, Bounded m, Size m) => Matrix (m, n) a -> Matrix n (Matrix m a)Source

slice a 2D matrix into columns.

joinRows :: (Bounded n, Size n, Bounded m, Size m) => Matrix m (Matrix n a) -> Matrix (m, n) aSource

join a matrix of matrixes into a single matrix.

joinColumns :: (Bounded n, Size n, Bounded m, Size m) => Matrix n (Matrix m a) -> Matrix (m, n) aSource

join a matrix of matrixes into a single matrix.

unitRow :: (Size m, Bounded m) => Matrix m a -> Matrix (X1, m) aSource

generate a 2D single row from a 1D matrix.

unRow :: (Size m, Bounded m) => Matrix (X1, m) a -> Matrix m aSource

generate a 1D matrix from a 2D matrix.

unitColumn :: (Size m, Bounded m) => Matrix m a -> Matrix (m, X1) aSource

generate a 2D single column from a 1D matrix.

unColumn :: (Size m, Bounded m) => Matrix (m, X1) a -> Matrix m aSource

generate a 1D matrix from a 2D matrix.

squash :: (Size n, Size m) => Matrix m a -> Matrix n aSource

very general; required that m and n have the same number of elements, rebundle please.

showMatrix :: (Size n, Size m) => Matrix (m, n) String -> StringSource

showMatrix displays a 2D matrix, and is the worker for show.

 GHCi> matrix [1..42] :: Matrix (X7,X6) Int
 [  1,  2,  3,  4,  5,  6,
    7,  8,  9, 10, 11, 12,
   13, 14, 15, 16, 17, 18,
   19, 20, 21, 22, 23, 24,
   25, 26, 27, 28, 29, 30,
   31, 32, 33, 34, 35, 36,
   37, 38, 39, 40, 41, 42 ]

newtype S Source

S is shown as the contents, without the quotes. One use is a matrix of S, so that you can do show-style functions using fmap.

Constructors

S String 

Instances

showAsE :: RealFloat a => Int -> a -> SSource

showAsF :: RealFloat a => Int -> a -> SSource

scanM :: (Size ix, Bounded ix, Enum ix) => ((left, a, right) -> (right, b, left)) -> (left, Matrix ix a, right) -> (right, Matrix ix b, left)Source

scanL :: (Size ix, Bounded ix, Enum ix) => ((a, right) -> (right, b)) -> (Matrix ix a, right) -> (right, Matrix ix b)Source

scanR :: (Size ix, Bounded ix, Enum ix) => ((left, a) -> (b, left)) -> (left, Matrix ix a) -> (Matrix ix b, left)Source