laop-0.1.1.1: Matrix programming library
Copyright(c) Armando Santos 2019-2020
Maintainerarmandoifsantos@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

LAoP.Matrix.Type

Description

The LAoP discipline generalises relations and functions treating them as Boolean matrices and in turn consider these as arrows.

LAoP is a library for algebraic (inductive) construction and manipulation of matrices in Haskell. See my Msc Thesis for the motivation behind the library, the underlying theory, and implementation details.

This module offers a newtype wrapper around Matrix that uses arbitrary types instead of canonical data types for the matrices dimensions.

NOTE: If the types in the dimensions are custom they must need to implement a Generic instance.

Synopsis

Documentation

LAoP (Linear Algebra of Programming) Inductive Matrix definition.

LAoP generalises relations and functions treating them as Boolean matrices and in turn consider these as arrows. This library offers many of the combinators mentioned in the work of Macedo (2012) and Oliveira (2012).

This definition is a wrapper around Type but dimensions are arbitrary data types. Type inference might not be as desired.

Type safe matrix representation

newtype Matrix e (cols :: Type) (rows :: Type) Source #

Constructors

M (Matrix e (Normalize cols) (Normalize rows)) 

Instances

Instances details
Num e => Category (Matrix e) Source #

It is possible to implement a constrained version of the category type class.

Instance details

Defined in LAoP.Matrix.Type

Associated Types

type Object (Matrix e) o Source #

Methods

id :: Object (Matrix e) a => Matrix e a a Source #

(.) :: Matrix e b c -> Matrix e a b -> Matrix e a c Source #

Eq e => Eq (Matrix e cols rows) Source # 
Instance details

Defined in LAoP.Matrix.Type

Methods

(==) :: Matrix e cols rows -> Matrix e cols rows -> Bool #

(/=) :: Matrix e cols rows -> Matrix e cols rows -> Bool #

Num e => Num (Matrix e cols rows) Source # 
Instance details

Defined in LAoP.Matrix.Type

Methods

(+) :: Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows #

(-) :: Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows #

(*) :: Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows #

negate :: Matrix e cols rows -> Matrix e cols rows #

abs :: Matrix e cols rows -> Matrix e cols rows #

signum :: Matrix e cols rows -> Matrix e cols rows #

fromInteger :: Integer -> Matrix e cols rows #

Ord e => Ord (Matrix e cols rows) Source # 
Instance details

Defined in LAoP.Matrix.Type

Methods

compare :: Matrix e cols rows -> Matrix e cols rows -> Ordering #

(<) :: Matrix e cols rows -> Matrix e cols rows -> Bool #

(<=) :: Matrix e cols rows -> Matrix e cols rows -> Bool #

(>) :: Matrix e cols rows -> Matrix e cols rows -> Bool #

(>=) :: Matrix e cols rows -> Matrix e cols rows -> Bool #

max :: Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows #

min :: Matrix e cols rows -> Matrix e cols rows -> Matrix e cols rows #

Show e => Show (Matrix e cols rows) Source # 
Instance details

Defined in LAoP.Matrix.Type

Methods

showsPrec :: Int -> Matrix e cols rows -> ShowS #

show :: Matrix e cols rows -> String #

showList :: [Matrix e cols rows] -> ShowS #

NFData e => NFData (Matrix e cols rows) Source # 
Instance details

Defined in LAoP.Matrix.Type

Methods

rnf :: Matrix e cols rows -> () #

type Object (Matrix e) a Source # 
Instance details

Defined in LAoP.Matrix.Type

type Object (Matrix e) a = (FLN a a, CountableN a)

Constraint type aliases

type Countable a = KnownNat (Count a) Source #

Constraint type synonyms to keep the type signatures less convoluted

type Liftable e a b = (Bounded a, Bounded b, Enum a, Enum b, Eq b, Num e, Ord e) Source #

Type aliases

type Zero = Void Source #

Zero type alias

type One = () Source #

One type alias

Primitives

one :: e -> Matrix e One One Source #

Unit matrix constructor

join :: Matrix e a rows -> Matrix e b rows -> Matrix e (Either a b) rows Source #

Matrix Join constructor

fork :: Matrix e cols a -> Matrix e cols b -> Matrix e cols (Either a b) Source #

Matrix Fork constructor

Auxiliary type families

type family FromNat (n :: Nat) :: Type where ... Source #

Type family that computes of a given type dimension from a given natural

Thanks to Li-Yao Xia this type family is super fast.

Equations

FromNat 1 = () 
FromNat n = FromNat' (Mod n 2 == 0) (FromNat (Div n 2)) 

type family Count (d :: Type) :: Nat where ... Source #

Type family that computes the cardinality of a given type dimension.

It can also count the cardinality of custom types that implement the Generic instance.

Equations

Count (Natural n m) = (m - n) + 1 
Count (List a) = (^) 2 (Count a) 
Count (Either a b) = (+) (Count a) (Count b) 
Count (a, b) = * (Count a) (Count b) 
Count (a -> b) = (^) (Count b) (Count a) 
Count (M1 _ _ f p) = Count (f p) 
Count (K1 _ _ _) = 1 
Count (V1 _) = 0 
Count (U1 _) = 1 
Count ((:*:) a b p) = Count (a p) * Count (b p) 
Count ((:+:) a b p) = Count (a p) + Count (b p) 
Count d = Count (Rep d R) 

type family Normalize (d :: Type) :: Type where ... Source #

Type family that normalizes the representation of a given data structure

Equations

Normalize (Either a b) = Either (Normalize a) (Normalize b) 
Normalize d = FromNat (Count d) 

Matrix construction and conversion

class FromLists cols rows Source #

Type class for defining the fromList conversion function.

Given that it is not possible to branch on types at the term level type classes are needed very much like an inductive definition but on types.

Minimal complete definition

fromLists

Instances

Instances details
FromLists () () Source # 
Instance details

Defined in LAoP.Matrix.Internal

Methods

fromLists :: [[e]] -> Matrix e () () Source #

FromLists () rows => FromLists () (Either () rows) Source # 
Instance details

Defined in LAoP.Matrix.Internal

Methods

fromLists :: [[e]] -> Matrix e () (Either () rows) Source #

(FromLists () a, FromLists () b, Countable a) => FromLists () (Either a b) Source # 
Instance details

Defined in LAoP.Matrix.Internal

Methods

fromLists :: [[e]] -> Matrix e () (Either a b) Source #

FromLists cols () => FromLists (Either () cols) () Source # 
Instance details

Defined in LAoP.Matrix.Internal

Methods

fromLists :: [[e]] -> Matrix e (Either () cols) () Source #

(FromLists a (), FromLists b (), Countable a) => FromLists (Either a b) () Source # 
Instance details

Defined in LAoP.Matrix.Internal

Methods

fromLists :: [[e]] -> Matrix e (Either a b) () Source #

(FromLists (Either a b) c, FromLists (Either a b) d, Countable c) => FromLists (Either a b) (Either c d) Source # 
Instance details

Defined in LAoP.Matrix.Internal

Methods

fromLists :: [[e]] -> Matrix e (Either a b) (Either c d) Source #

fromLists :: FLN cols rows => [[e]] -> Matrix e cols rows Source #

Build a matrix out of a list of list of elements. Throws a runtime error if the dimensions do not match.

toLists :: Matrix e cols rows -> [[e]] Source #

Converts a matrix to a list of lists of elements.

toList :: Matrix e cols rows -> [e] Source #

Converts a matrix to a list of elements.

matrixBuilder' :: (FLN cols rows, CountableDimsN cols rows) => ((Int, Int) -> e) -> Matrix e cols rows Source #

Matrix builder function. Constructs a matrix provided with a construction function that operates with indices.

matrixBuilder :: (FLN a b, Enum a, Enum b, Bounded a, Bounded b, Eq a, CountableDimsN a b) => ((a, b) -> e) -> Matrix e a b Source #

Matrix builder function. Constructs a matrix provided with a construction function that operates with arbitrary types.

row :: FLN cols () => [e] -> Matrix e cols One Source #

Constructs a row vector matrix

col :: FLN () rows => [e] -> Matrix e One rows Source #

Constructs a column vector matrix

zeros :: (Num e, FLN cols rows, CountableDimsN cols rows) => Matrix e cols rows Source #

The zero matrix. A matrix wholly filled with zeros.

ones :: (Num e, FLN cols rows, CountableDimsN cols rows) => Matrix e cols rows Source #

The ones matrix. A matrix wholly filled with ones.

Also known as T (Top) matrix.

bang :: forall e cols. (Num e, Enum e, FLN cols (), CountableN cols) => Matrix e cols One Source #

The T (Top) row vector matrix.

point :: (Bounded a, Enum a, Eq a, Num e, Ord e, CountableN a, FLN a One) => a -> Matrix e One a Source #

Point constant relation

constant :: (Num e, FLN cols rows, CountableDimsN cols rows) => e -> Matrix e cols rows Source #

The constant matrix constructor. A matrix wholly filled with a given value.

Functor instance equivalent function

fmapM :: (Liftable e a b, CountableDimsN a b, FLN b a) => (a -> b) -> Matrix e c a -> Matrix e c b Source #

Functor instance equivalent function

bimapM :: (Liftable e a b, Liftable e c d, CountableDimsN a c, CountableDimsN b d, FLN d c, FLN b a) => (a -> b) -> (c -> d) -> Matrix e a c -> Matrix e b d Source #

Bifunctor equivalent function

Applicative/Monoidal instance equivalent functions

unitM :: Num e => Matrix e () () Source #

Applicative instance equivalent unit function,

multM :: (CountableDimsN a b, CountableN (a, b), Num e, FLN (a, b) a, FLN (a, b) b, TrivialP a b) => Matrix e c a -> Matrix e c b -> Matrix e c (a, b) Source #

Applicative instance equivalent unit function,

Selective equivalent instance function

selectM :: (Num e, FLN b b, CountableN b) => Matrix e cols (Either a b) -> Matrix e a b -> Matrix e cols b Source #

Selective functors select operator equivalent inspired by the ArrowMonad solution presented in the paper.

Monad equivalent instance function

returnM :: forall e a. (Num e, Enum e, Enum a, FLN () a, Countable a) => a -> Matrix e One a Source #

Monad instance equivalent return function,

bindM :: Num e => Matrix e a b -> Matrix e b c -> Matrix e a c Source #

Monad instance equivalent (>>=) function,

Misc

Get dimensions

columns :: CountableN cols => Matrix e cols rows -> Int Source #

Obtain the number of columns.

NOTE: The KnownNat constraint is needed in order to obtain the dimensions in constant time. For a version that doesn't require the constraint see columns'.

columns' :: Matrix e cols rows -> Int Source #

Obtain the number of columns in an inefficient manner, but without any constraints.

For a more efficient version see columns.

rows :: CountableN rows => Matrix e cols rows -> Int Source #

Obtain the number of rows.

NOTE: The KnownNat constraint is needed in order to obtain the dimensions in constant time. For a version that doesn't require the constraint see rows'.

rows' :: Matrix e cols rows -> Int Source #

Obtain the number of rows in an inefficient manner, but without any constraints.

For a more efficient version see rows.

Matrix Transposition

tr :: Matrix e cols rows -> Matrix e rows cols Source #

Matrix transposition.

Scalar multiplication/division of matrices

(.|) :: Num e => e -> Matrix e cols rows -> Matrix e cols rows infixl 7 Source #

Scalar multiplication of matrices.

(./) :: Fractional e => Matrix e cols rows -> e -> Matrix e cols rows infixl 7 Source #

Scalar multiplication of matrices.

McCarthy's Conditional

cond :: (Trivial a, Trivial2 a, Trivial3 a, CountableN a, FLN () a, FLN a (), FLN a a, Liftable e a Bool) => (a -> Bool) -> Matrix e a b -> Matrix e a b -> Matrix e a b Source #

McCarthy's Conditional expresses probabilistic choice.

Matrix "abiding"

abideJF :: Matrix e cols rows -> Matrix e cols rows Source #

Matrix "abiding" followin the Join-Fork abide law.

Law:

Join (Fork a c) (Fork b d) == Fork (Join a b) (Join c d)

abideFJ :: Matrix e cols rows -> Matrix e cols rows Source #

Matrix "abiding" followin the Fork-Join abide law.

Law:

Fork (Join a b) (Join c d) == Join (Fork a c) (Fork b d)

Zip Matrices

zipWithM :: (e -> f -> g) -> Matrix e a b -> Matrix f a b -> Matrix g a b Source #

Zip two matrices with a given binary function

Biproduct approach

Fork

(===) :: Matrix e cols a -> Matrix e cols b -> Matrix e cols (Either a b) infixl 2 Source #

Matrix Fork constructor

Projections

p1 :: (Num e, CountableDimsN n m, FLN n m, FLN m m) => Matrix e (Either m n) m Source #

Biproduct first component projection

p2 :: (Num e, CountableDimsN n m, FLN m n, FLN n n) => Matrix e (Either m n) n Source #

Biproduct second component projection

Join

(|||) :: Matrix e a rows -> Matrix e b rows -> Matrix e (Either a b) rows infixl 3 Source #

Matrix Join constructor

Injections

i1 :: (Num e, CountableDimsN n m, FLN n m, FLN m m) => Matrix e m (Either m n) Source #

Biproduct first component injection

i2 :: (Num e, CountableDimsN n m, FLN m n, FLN n n) => Matrix e n (Either m n) Source #

Biproduct second component injection

Bifunctors

(-|-) :: (Num e, CountableDimsN j k, FLN k k, FLN j k, FLN k j, FLN j j) => Matrix e n k -> Matrix e m j -> Matrix e (Either n m) (Either k j) infixl 5 Source #

Matrix coproduct functor also known as matrix direct sum.

(><) :: forall e m p n q. (Num e, CountableDimsN m n, CountableDimsN p q, CountableDimsN (m, n) (p, q), FLN (m, n) m, FLN (m, n) n, FLN (p, q) p, FLN (p, q) q, TrivialP m n, TrivialP p q) => Matrix e m p -> Matrix e n q -> Matrix e (m, n) (p, q) infixl 4 Source #

Matrix product functor also known as Kronecker product

Applicative matrix combinators

Note that given the restrictions imposed it is not possible to implement the standard type classes present in standard Haskell. *** Matrix pairing projections

fstM :: forall e m k. (Num e, CountableDimsN m k, CountableN (m, k), FLN (m, k) m, TrivialP m k) => Matrix e (m, k) m Source #

Khatri Rao product first component projection matrix.

sndM :: forall e m k. (Num e, CountableDimsN k m, CountableN (m, k), FLN (m, k) k, TrivialP m k) => Matrix e (m, k) k Source #

Khatri Rao product second component projection matrix.

Matrix pairing

kr :: forall e cols a b. (Num e, CountableDimsN a b, CountableN (a, b), FLN (a, b) a, FLN (a, b) b, TrivialP a b) => Matrix e cols a -> Matrix e cols b -> Matrix e cols (a, b) Source #

Khatri Rao Matrix product also known as matrix pairing.

NOTE: That this is not a true categorical product, see for instance:

           | fstM . kr a b == a
kr a b ==> |
           | sndM . kr a b == b

Emphasis on the implication symbol.

Matrix composition and lifting

Arrow matrix combinators

Note that given the restrictions imposed it is not possible to implement the standard type classes present in standard Haskell.

iden :: (Num e, FLN a a, CountableN a) => Matrix e a a Source #

iden matrix

comp :: Num e => Matrix e cr rows -> Matrix e cols cr -> Matrix e cols rows Source #

Matrix composition. Equivalent to matrix-matrix multiplication.

This definition takes advantage of divide-and-conquer and fusion laws from LAoP.

fromF' :: (Liftable e a b, CountableDimsN cols rows, FLN rows cols) => (a -> b) -> Matrix e cols rows Source #

Lifts functions to matrices with arbitrary dimensions.

NOTE: Be careful to not ask for a matrix bigger than the cardinality of types a or b allows.

fromF :: (Liftable e a b, CountableDimsN a b, FLN b a) => (a -> b) -> Matrix e a b Source #

Lifts functions to matrices with dimensions matching a and b cardinality's.

Relation

toRel :: (Liftable (Natural 0 1) a b, CountableDimsN a b, FLN b a) => (a -> b -> Bool) -> Matrix (Natural 0 1) a b Source #

Lifts relation functions to Boolean Matrix

Matrix printing

pretty :: (CountableDimsN cols rows, Show e) => Matrix e cols rows -> String Source #

Matrix pretty printer

prettyPrint :: (CountableDimsN cols rows, Show e) => Matrix e cols rows -> IO () Source #

Matrix pretty printer