sized-types-0.5.1: Sized types in Haskell using the GHC Nat kind.

Safe HaskellNone
LanguageHaskell98

Data.Sized.Matrix

Description

Sized matrixes.

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

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

Synopsis

Documentation

newtype Matrix ix a Source

A Matrix is an array with the size determined uniquely by the type of the index type, ix, with every type in ix used.

Constructors

Matrix (Array ix a) 

Instances

IArray Matrix a 
Ix ix => Functor (Matrix ix) 
(Bounded i, Ix i) => Applicative (Matrix i) 
(Bounded ix, Ix ix) => Foldable (Matrix ix) 
(Bounded ix, Ix ix) => Traversable (Matrix ix) 
(Eq a, Ix ix) => Eq (Matrix ix a) 
(Ord a, Ix ix) => Ord (Matrix ix a) 
(Show a, Show ix, Bounded ix, Ix ix) => Show (Matrix ix a) 
Typeable (* -> * -> *) Matrix 

type Vector ix a = Matrix (Fin ix) a Source

A Vector is a 1D Matrix, using a TypeNat to define its length.

type Vector2 ix iy a = Matrix (Fin ix, Fin iy) a Source

A Vector2 is a 2D Matrix, using a TypeNat's to define its size.

matrix :: forall i a. (Bounded i, Ix i) => [a] -> Matrix i a Source

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

population :: forall i a. (Bounded i, Ix i) => Matrix i a -> Int Source

what is the population of a matrix?

allIndices :: (Bounded i, Ix i) => Matrix i a -> [i] Source

zeroOf :: (Bounded i, Ix i) => Matrix i a -> i Source

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

coord :: (Bounded i, Ix i) => Matrix i i Source

coord returns a matrix filled with indexes.

zipWith :: (Bounded i, Ix i) => (a -> b -> c) -> Matrix i a -> Matrix i b -> Matrix i c Source

Same as for lists.

forEach :: (Bounded i, Ix i) => Matrix i a -> (i -> a -> b) -> Matrix i b Source

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

forAll :: (Bounded i, Ix i) => (i -> a) -> Matrix i a Source

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

mm :: (Bounded m, Ix m, Bounded n, Ix n, Bounded o, Ix o, Num a) => Matrix (m, n) a -> Matrix (n, o) a -> Matrix (m, o) a Source

mm is the 2D matrix multiply.

transpose :: (Bounded x, Ix x, Bounded y, Ix y) => Matrix (x, y) a -> Matrix (y, x) a Source

transpose a 2D matrix.

identity :: (Bounded x, Ix x, Num a) => Matrix (x, x) a Source

return the identity for a specific matrix size.

append :: (SingI left, SingI right, SingI (left + right)) => Vector left a -> Vector right a -> Vector (left + right) a Source

append to 1D vectors

above :: (SingI top, SingI bottom, SingI y, SingI (top + bottom)) => Vector2 top y a -> Vector2 bottom y a -> Vector2 (top + bottom) y a Source

stack two matrixes above each other.

beside :: (SingI left, SingI right, SingI x, SingI (left + right)) => Vector2 x left a -> Vector2 x right a -> Vector2 x (left + right) a Source

stack two matrixes beside each other.

ixfmap :: (Bounded i, Ix i, Bounded j, Ix 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.

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

grab part of a matrix. cropAt :: (Index i ~ Index ix, Bounded i, Ix i, Bounded ix, Ix ix) => Matrix ix a -> ix -> Matrix i a cropAt m corner = ixmap ( i -> (addIndex corner (toIndex i))) m

slice a 2D matrix into rows.

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

slice a 2D matrix into columns.

joinRows :: (Bounded n, Ix n, Bounded m, Ix m) => Matrix m (Matrix n a) -> Matrix (m, n) a Source

join a matrix of matrixes into a single matrix.

joinColumns :: (Bounded n, Ix n, Bounded m, Ix m) => Matrix n (Matrix m a) -> Matrix (m, n) a Source

join a matrix of matrixes into a single matrix.

show2D :: (Bounded n, Ix n, Bounded m, Ix m, Show a) => Matrix (m, n) a -> String Source

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

GHCi> matrix [1..42] :: Matrix (Fin 7, Fin 6) 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 -> S Source

showAsF :: RealFloat a => Int -> a -> S Source