BNFC-2.8.3.1: A compiler front-end generator.
Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Matrix.Quad

Synopsis

Documentation

data Shape Source #

Constructors

Bin Shape Shape 
Leaf 

data Shape' :: Shape -> * where Source #

Constructors

Bin' :: !Int -> Shape' s -> Shape' s' -> Shape' (Bin s s') 
Leaf' :: Shape' Leaf 

data SomeShape where Source #

Constructors

S :: Shape' s -> SomeShape 

data Mat :: Shape -> Shape -> * -> * where Source #

Constructors

Quad :: !(Mat x1 y1 a) -> !(Mat x2 y1 a) -> !(Mat x1 y2 a) -> !(Mat x2 y2 a) -> Mat (Bin x1 x2) (Bin y1 y2) a 
Zero :: Mat x y a 
One :: !a -> Mat Leaf Leaf a 
Row :: Mat x1 Leaf a -> Mat x2 Leaf a -> Mat (Bin x1 x2) Leaf a 
Col :: Mat Leaf y1 a -> Mat Leaf y2 a -> Mat Leaf (Bin y1 y2) a 

Instances

Instances details
AbelianGroupZ a => AbelianGroup (Mat x y a) Source # 
Instance details

Defined in Data.Matrix.Quad

Methods

zero :: Mat x y a Source #

(+) :: Mat x y a -> Mat x y a -> Mat x y a Source #

data Vec :: Shape -> * -> * where Source #

Constructors

Z :: Vec s a 
O :: a -> Vec Leaf a 
(:!) :: Vec s a -> Vec s' a -> Vec (Bin s s') a 

Instances

Instances details
AbelianGroup a => AbelianGroup (Vec x a) Source # 
Instance details

Defined in Data.Matrix.Quad

Methods

zero :: Vec x a Source #

(+) :: Vec x a -> Vec x a -> Vec x a Source #

row :: forall {x1 :: Shape} {a} {x2 :: Shape}. Mat x1 'Leaf a -> Mat x2 'Leaf a -> Mat ('Bin x1 x2) 'Leaf a Source #

col :: Mat Leaf y1 a -> Mat Leaf y2 a -> Mat Leaf (Bin y1 y2) a Source #

quad :: forall {x1 :: Shape} {y1 :: Shape} {a} {x2 :: Shape} {y2 :: Shape}. Mat x1 y1 a -> Mat x2 y1 a -> Mat x1 y2 a -> Mat x2 y2 a -> Mat ('Bin x1 x2) ('Bin y1 y2) a Source #

(.+.) :: AbelianGroupZ a => Mat x y a -> Mat x y a -> Mat x y a Source #

mult :: RingP a => Bool -> Mat x y a -> Mat z x a -> Mat z y (Pair a) Source #

trav :: AbelianGroupZ a => Mat y x (Pair a) -> Pair (Mat y x a) Source #

q0 :: Mat (Bin x x') (Bin y y') a Source #

closeDisjointP :: RingP a => Bool -> Mat x x a -> Mat y x (Pair a) -> Mat y y a -> Pair (Mat y x a) Source #

showR :: Mat x y a -> String Source #

bin' :: Shape' s -> Shape' s' -> Shape' (Bin s s') Source #

mkSing :: AbelianGroupZ a => Shape' x -> Shape' y -> a -> Mat x y a Source #

data SomeTri a where Source #

Constructors

T :: Shape' s -> Pair (Mat s s a) -> SomeTri a 

type Q a = SomeTri a Source #

mkUpDiag :: AbelianGroupZ a => [a] -> Shape' s -> Mat s s a Source #

close :: RingP a => Bool -> Mat s s (Pair a) -> Pair (Mat s s a) Source #

mkTree :: RingP a => [Pair a] -> SomeTri a Source #

quad' :: forall {f} {x1 :: Shape} {y1 :: Shape} {a} {x2 :: Shape} {y2 :: Shape}. Applicative f => f (Mat x1 y1 a) -> f (Mat x2 y1 a) -> f (Mat x1 y2 a) -> f (Mat x2 y2 a) -> f (Mat ('Bin x1 x2) ('Bin y1 y2) a) Source #

mergein :: RingP a => Bool -> SomeTri a -> Pair a -> SomeTri a -> SomeTri a Source #

zw :: (AbelianGroup a, AbelianGroup b) => (a -> b -> c) -> Vec y a -> Vec y b -> Vec y c Source #

A variant of zipWith on vectors

lk :: AbelianGroup a => Int -> Shape' x -> Vec x a -> a Source #

Lookup in a vector

lin' :: AbelianGroup a => Mat x y a -> Vec y (Vec x a) Source #

Linearize a matrix

contents :: Shape' x -> Vec x a -> [(Int, a)] Source #

Contents of a vector

first :: (t -> a) -> (t, b) -> (a, b) Source #

second :: (t -> b) -> (a, t) -> (a, b) Source #

data Path :: Shape -> * where Source #

Constructors

Here :: Path Leaf 
Low :: Path s -> Path (Bin s s') 
High :: Path s -> Path (Bin s' s) 

(<||>) :: Maybe (a, Path x) -> Maybe (a, Path x') -> Maybe (a, Path (Bin x x')) Source #

rightmostOnLine :: Path y -> Mat x y a -> Maybe (a, Path x) Source #

What is, and where is the rightmost non-zero element on a given line of the matrix?

isRightmost :: Path x -> Bool Source #

Is this the rightmost path?

results' :: AbelianGroup a => Mat y y a -> Path y -> [(Path y, a, Path y)] Source #

results :: AbelianGroupZ a => SomeTri a -> [(Int, a, Int)] Source #

root' :: AbelianGroup a => Mat x y a -> a Source #

square3 :: RingP a => Bool -> Pair a -> Pair a -> SomeTri a Source #

(|+|) :: [[a]] -> [[a]] -> [[a]] Source #

(-+-) :: [a] -> [a] -> [a] Source #

lin :: AbelianGroup a => Shape' x -> Shape' y -> Mat x y a -> [[a]] Source #

sparse :: AbelianGroup a => Shape' x -> Shape' y -> Mat x y a -> [(Int, Int, a)] Source #

shiftX :: forall {s :: Shape} {b} {c}. Shape' s -> [(Int, b, c)] -> [(Int, b, c)] Source #

shiftY :: forall {s :: Shape} {a} {c}. Shape' s -> [(a, Int, c)] -> [(a, Int, c)] Source #