neural-0.1.1.0: Neural Networks in native Haskell

Copyright(c) Lars Brünjes, 2016
LicenseMIT
Maintainerbrunjlar@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • TypeFamilies
  • DataKinds
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • KindSignatures
  • TypeOperators
  • ExplicitNamespaces

Data.Utils.Matrix

Description

This module defines fixed-size matrices and some basic typeclass instances and operations for them.

Synopsis

Documentation

newtype Matrix m n a Source

Matrix m n a is the type of matrices with m rows, n columns and entries of type a.

Constructors

Matrix (Vector m (Vector n a)) 

Instances

(<%%>) :: Num a => Matrix m n a -> Vector n a -> Vector m a Source

Multiplication of a matrix by a (column-)vector.

>>> :set -XDataKinds
>>> (pure 1 :: Matrix 1 2 Int) <%%> cons 1 (cons 2 nil)
[3]

row :: Matrix m n a -> Int -> Maybe (Vector n a) Source

Gives the matrix row with the specified index (starting at zero) if the index is valid, otherwise Nothing.

>>> :set -XDataKinds
>>> row (pure 42 :: Matrix 2 4 Int) 0
Just [42,42,42,42]
>>> row (pure 42 :: Matrix 2 4 Int) 2
Nothing

column :: Matrix m n a -> Int -> Maybe (Vector m a) Source

Gives the matrix column with the specified index (starting at zero) if the index is valid, otherwise Nothing.

>>> :set -XDataKinds
>>> column (pure 42 :: Matrix 2 4 Int) 3
Just [42,42]
>>> column (pure 42 :: Matrix 2 4 Int) 4
Nothing

mgenerate :: (KnownNat m, KnownNat n) => ((Int, Int) -> a) -> Matrix m n a Source

Generates a matrix by applying the given function to each index (row, column).

>>> :set -XDataKinds
>>> mgenerate id :: Matrix 3 2 (Int, Int)
Matrix [[(0,0),(0,1)],[(1,0),(1,1)],[(2,0),(2,1)]]

(!!?) :: Matrix m n a -> (Int, Int) -> Maybe a Source

Gives the matrix element with the specified index (row, column) if the index is valid, otherwise Nothing.

>>> :set -XDataKinds
>>> let m = mgenerate (uncurry (+)) :: Matrix 2 3 Int
>>> m !!? (0,0)
Just 0
>>> m !!? (1, 2)
Just 3
>>> m !!? (5, 7)
Nothing

transpose :: (KnownNat m, KnownNat n) => Matrix m n a -> Matrix n m a Source

Transposes a matrix.

>>> transpose (Matrix $ cons (cons 'a' nil) (cons (cons 'b' nil) nil))
Matrix ["ab"]