| Copyright | (c) Erich Gut |
|---|---|
| License | BSD3 |
| Maintainer | zerich.gut@gmail.com |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
OAlg.Entity.Sequence.Definition
Contents
Description
basic definitions for sequences as mappings of an index to an entity.
Synopsis
- class (LengthN (s x), Ord i) => Sequence s i x where
- listN :: Sequence s N x => s x -> [(x, N)]
- (?) :: Sequence s i x => s x -> i -> x
- isEmpty :: Sequence s i x => p i -> s x -> Bool
- span :: Sequence s i x => p i -> s x -> Span i
- support :: Sequence s i x => p i -> s x -> Set i
- image :: (Sequence s i x, Ord x) => p i -> s x -> Set x
- class (Entity x, Entity i, Sequence s i x) => ConstructableSequence s i x where
- sqcIndexMap :: (ConstructableSequence s i x, Sequence s j x) => Set i -> (i -> j) -> s x -> s x
- data SequenceException = IndexOutOfSupport
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
terminates and will not end up in an exception.lengthN xs
Property Let s, i, x be an instance of Sequence, then holds:
For all
xsins xholds:For all
xsins xholds:- Let
xsbe ins xandiini, then holds: there exists anxinxwithxsmatches?iif and only if there exists anJustx(i',x)insuch thatgraph(Just i) xsi.==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.
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
| Sequence ProductSymbol N x Source # | |
Defined in OAlg.Entity.Product.ProductSymbol | |
| Ord i => Sequence Permutation i i Source # | |
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 # | |
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 # | |
| (Integral r, Enum r) => Sequence [] r x Source # | |
| Sequence (Dim x) N p Source # | |
| Ord i => Sequence (Col i) i x Source # | |
| Ord j => Sequence (Row j) j x Source # | |
| Sequence (Product N) N a Source # | |
| Sequence (ProductForm N) N x Source # | |
| Ord i => Sequence (Graph i) i x Source # | |
| Ord i => Sequence (PSequence i) i x Source # | |
(?) :: 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
, then holds: If Sequence s i xi is in the support of xs then
xs is the ? ii-th item of xs, else its evaluation will end up by throwing a
IndexOutOfSupport-exception.
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
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
| Entity x => ConstructableSequence ProductSymbol N x Source # | |
Defined in OAlg.Entity.Product.ProductSymbol Methods sequence :: (N -> Maybe x) -> Set N -> ProductSymbol x Source # (<&) :: ProductSymbol x -> Set N -> ProductSymbol x Source # | |
| (Integral r, Enum r, Entity x, Ord x) => ConstructableSequence Set r x Source # | |
| (Integral r, Enum r, Entity x) => ConstructableSequence [] r x Source # | |
| (Entity x, Entity i, Ord i) => ConstructableSequence (Graph i) i x Source # | |
| (Entity x, Entity i, Ord i) => ConstructableSequence (PSequence i) 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
data SequenceException Source #
sequence exceptions which are sub exceptions from SomeOAlgException.
Constructors
| IndexOutOfSupport |
Instances
| Exception SequenceException Source # | |
Defined in OAlg.Entity.Sequence.Definition Methods toException :: SequenceException -> SomeException # | |
| Show SequenceException Source # | |
Defined in OAlg.Entity.Sequence.Definition Methods showsPrec :: Int -> SequenceException -> ShowS # show :: SequenceException -> String # showList :: [SequenceException] -> ShowS # | |
| Eq SequenceException Source # | |
Defined in OAlg.Entity.Sequence.Definition Methods (==) :: SequenceException -> SequenceException -> Bool # (/=) :: SequenceException -> SequenceException -> Bool # | |