oalg-base-1.1.4.0: Algebraic structures on oriented entities and limits as a tool kit to solve algebraic problems.
Copyright(c) Erich Gut
LicenseBSD3
Maintainerzerich.gut@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

OAlg.Entity.Matrix.Entries

Description

entries of matrices and viewing them as a column of rows respectively as a row of columns.

Synopsis

Entries

newtype Entries i j x Source #

two dimensional partial sequence.

Constructors

Entries (PSequence (i, j) x) 

Instances

Instances details
Functor (Entries i j) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

fmap :: (a -> b) -> Entries i j a -> Entries i j b #

(<$) :: a -> Entries i j b -> Entries i j a #

(Show x, Show i, Show j) => Show (Entries i j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

showsPrec :: Int -> Entries i j x -> ShowS #

show :: Entries i j x -> String #

showList :: [Entries i j x] -> ShowS #

(Eq x, Eq i, Eq j) => Eq (Entries i j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

(==) :: Entries i j x -> Entries i j x -> Bool #

(/=) :: Entries i j x -> Entries i j x -> Bool #

(Ord x, Ord i, Ord j) => Ord (Entries i j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

compare :: Entries i j x -> Entries i j x -> Ordering #

(<) :: Entries i j x -> Entries i j x -> Bool #

(<=) :: Entries i j x -> Entries i j x -> Bool #

(>) :: Entries i j x -> Entries i j x -> Bool #

(>=) :: Entries i j x -> Entries i j x -> Bool #

max :: Entries i j x -> Entries i j x -> Entries i j x #

min :: Entries i j x -> Entries i j x -> Entries i j x #

(Transposable x, Ord n) => Transposable (Entries n n x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

transpose :: Entries n n x -> Entries n n x Source #

LengthN (Entries i j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

lengthN :: Entries i j x -> N Source #

(Entity x, Entity i, Entity j, Ord i, Ord j) => Validable (Entries i j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

valid :: Entries i j x -> Statement Source #

(Entity x, Entity i, Entity j, Ord i, Ord j) => Entity (Entries i j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

type Dual (Entries i j x :: TYPE LiftedRep) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

type Dual (Entries i j x :: TYPE LiftedRep) = Entries j i (Op x)

etsxs :: Entries i j x -> [(x, i, j)] Source #

underlying list of indexed entries.

etsEmpty :: Entries i j x Source #

the empty sequence of entries.

etsAdd :: (Additive x, Ord i, Ord j) => Entries i j x -> Entries i j x -> Entries i j x Source #

adding two entries.

Property Let zs = etsAdd xs ys, then holds:

Pre
For all (i,j) in (i,j) where there exists an (x,i,j) in xs and a (y,i,j) in ys holds: root x == root y.
Post
  1. zs is valid.
  2. For all (i,j) in (i,j) holds:

    1. If exists a (x,i,j) in xs but not exists a (y,i,j) in ys then there exists a (z,i,j) in zs with z == x.
    2. If exists a (y,i,j) in ys but not exists a (x,i,j) in xs then there exists a (z,i,j) in zs with z == y.
    3. If exists a (x,i,j) in xs and (y,i,j) in ys then there exists a (z,i,j) in zs with z == x + y.

etsMlt :: (Distributive x, Ord k) => Col i (Row k x) -> Row j (Col k x) -> Col i (Row j x) Source #

multiplication.

etsJoin :: (i ~ N, j ~ N) => ProductSymbol i -> ProductSymbol j -> Entries i j (Entries i j x) -> Entries i j x Source #

joining entries of entries.

Property Let xs' = etsJoin r c xs

Pre
For all (xij,i,j) in xs holds:
  1. i < lengthN r and j < lengthN c
  2. For all (_,i',j') in xij holds: i' < ri and j' < cj where ..ri.. = r, ..cj.. = c.
Post
xs' is valid.

etscr :: Eq i => Entries i j x -> Col i (Row j x) Source #

the underlying column of rows.

etsrc :: (Ord i, Ord j) => Entries i j x -> Row j (Col i x) Source #

the underlying row of columns.

crets :: Col i (Row j x) -> Entries i j x Source #

the entries given by a column of rows.

rcets :: (Ord i, Ord j) => Row j (Col i x) -> Entries i j x Source #

the entries given by a row of columns.

etsElimZeros :: Additive x => Entries i j x -> Entries i j x Source #

elimination of zeros.

Row

newtype Row j x Source #

viewing a partial sequence as a row.

Constructors

Row (PSequence j x) 

Instances

Instances details
Functor (Row j) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

fmap :: (a -> b) -> Row j a -> Row j b #

(<$) :: a -> Row j b -> Row j a #

Ord j => Sequence (Row j) j x Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

graph :: p j -> Row j x -> Graph j x Source #

list :: p j -> Row j x -> [(x, j)] Source #

(??) :: Row j x -> j -> Maybe x Source #

(Entity x, Entity j, Ord j) => PermutableSequence (Row j) j x Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

permuteBy :: p j -> (w -> w -> Ordering) -> (x -> w) -> Row j x -> (Row j x, Permutation j) Source #

Ord j => Opr (Permutation j) (Row j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

(<*) :: Row j x -> Permutation j -> Row j x Source #

(Entity x, Entity j, Ord j) => TotalOpr (Permutation j) (Row j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

(Show x, Show j) => Show (Row j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

showsPrec :: Int -> Row j x -> ShowS #

show :: Row j x -> String #

showList :: [Row j x] -> ShowS #

(Eq x, Eq j) => Eq (Row j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

(==) :: Row j x -> Row j x -> Bool #

(/=) :: Row j x -> Row j x -> Bool #

LengthN (Row j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

lengthN :: Row j x -> N Source #

(Entity x, Entity j, Ord j) => Validable (Row j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

valid :: Row j x -> Statement Source #

(Entity x, Entity j, Ord j) => Entity (Row j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

type Dual (Row j (Col i x) :: TYPE LiftedRep) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

type Dual (Row j (Col i x) :: TYPE LiftedRep) = Col j (Row i (Op x))

rowxs :: Row j x -> [(x, j)] Source #

underlying list of indexed entries.

rowEmpty :: Row j x Source #

the empty row.

rowIsEmpty :: Row j x -> Bool Source #

check for being empty.

rowHead :: Row j x -> (x, j) Source #

head.

rowTail :: Row j x -> Row j x Source #

tail.

rowFilter :: (x -> Bool) -> Row j x -> Row j x Source #

filtering a row by the given predicate.

rowMapShift :: Number j => j -> ((x, j) -> y) -> Row j x -> Row j y Source #

mapping and shifting of a row.

rowAppend :: Row j x -> Row j x -> Row j x Source #

appending a row.

Property Let zs = rowAppend xs ys where ..(x,l) = xs and (y,f).. = ys then holds:

If
l < f
Then
zs is valid.

rowInterlace :: Ord j => (x -> y -> z) -> (x -> z) -> (y -> z) -> Row j x -> Row j y -> Row j z Source #

interlacing two rows.

rowElimZeros :: Additive a => Row i a -> Row i a Source #

elimination of zeros.

rowSwap :: Ord j => j -> j -> Row j x -> Row j x Source #

swapping two entries of a row.

Pre k < l.

rowAdd :: (Additive a, Ord j) => Row j a -> Row j a -> Row j a Source #

adding two rows.

rowMltl :: Distributive a => a -> Row j a -> Row j a Source #

multiplies each element of the row by the given factor from the left.

rowShear :: Ord j => (Maybe x -> s -> Maybe x) -> (Maybe x -> Maybe x -> Maybe x) -> j -> j -> s -> s -> s -> s -> Row j x -> Row j x Source #

shears two entries of a row.

Property Let r' = rowShear (<*) (+) k l s t u v r, then holds:

Pre
k < l.

Note rowShear is like multiplying the given row from the right with the matrix given by k l s t u v.

rowScale :: Ord j => (x -> s -> Maybe x) -> j -> s -> Row j x -> Row j x Source #

scales the entry at the given position by the given factor.

Col

newtype Col i x Source #

viewing a partial sequence as a column.

Constructors

Col (PSequence i x) 

Instances

Instances details
Functor (Col i) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

fmap :: (a -> b) -> Col i a -> Col i b #

(<$) :: a -> Col i b -> Col i a #

Ord i => Sequence (Col i) i x Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

graph :: p i -> Col i x -> Graph i x Source #

list :: p i -> Col i x -> [(x, i)] Source #

(??) :: Col i x -> i -> Maybe x Source #

(Entity x, Entity i, Ord i) => PermutableSequence (Col i) i x Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

permuteBy :: p i -> (w -> w -> Ordering) -> (x -> w) -> Col i x -> (Col i x, Permutation i) Source #

Ord i => Opr (Permutation i) (Col i x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

(<*) :: Col i x -> Permutation i -> Col i x Source #

(Entity x, Entity i, Ord i) => TotalOpr (Permutation i) (Col i x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

(Show x, Show i) => Show (Col i x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

showsPrec :: Int -> Col i x -> ShowS #

show :: Col i x -> String #

showList :: [Col i x] -> ShowS #

(Eq x, Eq i) => Eq (Col i x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

(==) :: Col i x -> Col i x -> Bool #

(/=) :: Col i x -> Col i x -> Bool #

LengthN (Col i x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

lengthN :: Col i x -> N Source #

(Entity x, Entity i, Ord i) => Validable (Col i x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

Methods

valid :: Col i x -> Statement Source #

(Entity x, Entity i, Ord i) => Entity (Col i x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

type Dual (Row j (Col i x) :: TYPE LiftedRep) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

type Dual (Row j (Col i x) :: TYPE LiftedRep) = Col j (Row i (Op x))

colxs :: Col i x -> [(x, i)] Source #

underlying list of indexed entries.

colEmpty :: Col i x Source #

the empty column.

colIsEmpty :: Col i x -> Bool Source #

check for being empty.

colHead :: Col i x -> (x, i) Source #

head.

colTail :: Col i x -> Col i x Source #

tail.

colFilter :: (x -> Bool) -> Col i x -> Col i x Source #

filtering a column by the given predicate.

colMapShift :: Number i => i -> ((x, i) -> y) -> Col i x -> Col i y Source #

mapping and shifting of a column.

colAppend :: Col i x -> Col i x -> Col i x Source #

appending a column..

Property Let zs = colAppend xs ys where ..(x,l) = xs and (y,f).. = ys then holds:

If
l < f
Then
zs is valid.

colInterlace :: Ord i => (x -> y -> z) -> (x -> z) -> (y -> z) -> Col i x -> Col i y -> Col i z Source #

interlacing two columns.

colElimZeros :: Additive a => Col i a -> Col i a Source #

elimination of zeros.

colSwap :: Ord i => i -> i -> Col i x -> Col i x Source #

swapping two entries of a column.

Pre k < l.

colAdd :: (Additive a, Ord i) => Col i a -> Col i a -> Col i a Source #

adding two columns.

colMltr :: Distributive a => Col i a -> a -> Col i a Source #

multiplies each element of the column by the given factor from the right.

colShear :: Ord i => (s -> Maybe x -> Maybe x) -> (Maybe x -> Maybe x -> Maybe x) -> i -> i -> s -> s -> s -> s -> Col i x -> Col i x Source #

shears two entries of a column.

Property Let c' = colShear (<*) (+) k l s t u v c, then holds:

Pre
k < l.

Note colShear is like multiplying the given column from the left with the matrix given by k l s t u v.

colScale :: Ord i => (s -> x -> Maybe x) -> i -> s -> Col i x -> Col i x Source #

scales the entry at the given position by the given factor.

Col Row

crHeadColAt :: Eq j => j -> Col i (Row j a) -> Col i a Source #

get the head column at j.

Pre for all j' in rws holds: j <= j'.

crHeadRowAt :: Eq i => i -> Col i (Row j a) -> Row j a Source #

get the head row at i.

Pre for all i' in rws holdst: i <= i'.

Duality

coEntries :: (Ord i, Ord j) => Entries i j x -> Dual (Entries i j x) Source #

to the dual of Entries, with inverse coEntriesInv.

coEntriesInv :: (Ord i, Ord j) => Dual (Entries i j x) -> Entries i j x Source #

from the dual of Entries, with inverse coEntries.