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.Sequence.Definition

Description

basic definitions for sequences as mappings of an index to an entity.

Synopsis

Sequence

class (LengthN (s x), Ord i) => Sequence s i x where Source #

sequences as mappings of an index.

Definition Let s, i, x be an instance of Sequence and xs be in s x, then we call xs finite if and only if the evaluation of lengthN xs terminates and will not end up in an exception.

Property Let s, i, x be an instance of Sequence, then holds:

  1. For all xs in s x holds:

    1. graph is constant in its first parameter.
    2. If xs is finite, then lengthN xs == lengthN (graph p xs) for any p.
  2. For all xs in s x holds:

    1. list is constant in its first parameter.
    2. For all ..(x,i):(x,j).. in xs holds: i < j.
    3. If xs is finite, then lengthN xs == lengthN (list p xs) for any p.
  3. Let xs be in s x and i in i, then holds: there exists an x in x with xs ? i matches Just x if and only if there exists an (i',x) in graph (Just i) xs such that i == i'.

Note The first parameter of graph - respectively list - serves only as a proxy and as such it is only relevant on the type level.

Minimal complete definition

graph | list

Methods

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

the associated graph of a sequence

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

the associated list of its items together with there index.

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

the i-th item.

Instances

Instances details
Sequence ProductSymbol N x Source # 
Instance details

Defined in OAlg.Entity.Product.ProductSymbol

Methods

graph :: p N -> ProductSymbol x -> Graph N x Source #

list :: p N -> ProductSymbol x -> [(x, N)] Source #

(??) :: ProductSymbol x -> N -> Maybe x Source #

Ord i => Sequence Permutation i i Source # 
Instance details

Defined in OAlg.Entity.Sequence.Permutation

Methods

graph :: p i -> Permutation i -> Graph i i Source #

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

(??) :: Permutation i -> i -> Maybe i Source #

Ord i => Sequence PermutationForm i i Source # 
Instance details

Defined in OAlg.Entity.Sequence.Permutation

Methods

graph :: p i -> PermutationForm i -> Graph i i Source #

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

(??) :: PermutationForm i -> i -> Maybe i Source #

(Integral r, Enum r) => Sequence Set r x Source # 
Instance details

Defined in OAlg.Entity.Sequence.Definition

Methods

graph :: p r -> Set x -> Graph r x Source #

list :: p r -> Set x -> [(x, r)] Source #

(??) :: Set x -> r -> Maybe x Source #

(Integral r, Enum r) => Sequence [] r x Source # 
Instance details

Defined in OAlg.Entity.Sequence.Definition

Methods

graph :: p r -> [x] -> Graph r x Source #

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

(??) :: [x] -> r -> Maybe x Source #

Sequence (Dim x) N p Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

graph :: p0 N -> Dim x p -> Graph N p Source #

list :: p0 N -> Dim x p -> [(p, N)] Source #

(??) :: Dim x p -> N -> Maybe p Source #

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 #

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 #

Sequence (Product N) N a Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

graph :: p N -> Product N a -> Graph N a Source #

list :: p N -> Product N a -> [(a, N)] Source #

(??) :: Product N a -> N -> Maybe a Source #

Sequence (ProductForm N) N x Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

graph :: p N -> ProductForm N x -> Graph N x Source #

list :: p N -> ProductForm N x -> [(x, N)] Source #

(??) :: ProductForm N x -> N -> Maybe x Source #

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

Defined in OAlg.Entity.Sequence.Definition

Methods

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

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

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

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

Defined in OAlg.Entity.Sequence.PSequence

Methods

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

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

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

listN :: Sequence s N x => s x -> [(x, N)] Source #

the indexed list of the sequence.

(?) :: Sequence s i x => s x -> i -> x Source #

the i-th element of the sequence.

Property Let xs be in s x and i in i for a instance of Sequence s i x, then holds: If i is in the support of xs then xs ? i is the i-th item of xs, else its evaluation will end up by throwing a IndexOutOfSupport-exception.

isEmpty :: Sequence s i x => p i -> s x -> Bool Source #

checks for being empty.

span :: Sequence s i x => p i -> s x -> Span i Source #

the span of a sequence.

support :: Sequence s i x => p i -> s x -> Set i Source #

the support of a sequence, i.e. all the indices which are not mapped to Nothing.

image :: (Sequence s i x, Ord x) => p i -> s x -> Set x Source #

the image of a sequence, i.e. all the entities are hit by the mapping.

Constructable

class (Entity x, Entity i, Sequence s i x) => ConstructableSequence s i x where Source #

constructable sequences.

Minimal complete definition

sequence

Methods

sequence :: (i -> Maybe x) -> Set i -> s x Source #

constructs a sequence.

(<&) :: s x -> Set i -> s x infixl 7 Source #

restricts a sequence.

Instances

Instances details
Entity x => ConstructableSequence ProductSymbol N x Source # 
Instance details

Defined in OAlg.Entity.Product.ProductSymbol

(Integral r, Enum r, Entity x, Ord x) => ConstructableSequence Set r x Source # 
Instance details

Defined in OAlg.Entity.Sequence.Definition

Methods

sequence :: (r -> Maybe x) -> Set r -> Set x Source #

(<&) :: Set x -> Set r -> Set x Source #

(Integral r, Enum r, Entity x) => ConstructableSequence [] r x Source # 
Instance details

Defined in OAlg.Entity.Sequence.Definition

Methods

sequence :: (r -> Maybe x) -> Set r -> [x] Source #

(<&) :: [x] -> Set r -> [x] Source #

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

Defined in OAlg.Entity.Sequence.Definition

Methods

sequence :: (i -> Maybe x) -> Set i -> Graph i x Source #

(<&) :: Graph i x -> Set i -> Graph i x Source #

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

Defined in OAlg.Entity.Sequence.PSequence

Methods

sequence :: (i -> Maybe x) -> Set i -> PSequence i x Source #

(<&) :: PSequence i x -> Set i -> PSequence i x Source #

sqcIndexMap :: (ConstructableSequence s i x, Sequence s j x) => Set i -> (i -> j) -> s x -> s x Source #

mapping the indices according to the given set.

Exception