Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
partially defined sequences of items in x
with a totally ordered index type i
.
Synopsis
- newtype PSequence i x = PSequence [(x, i)]
- iProxy :: s i x -> Proxy i
- psqSpan :: Ord i => PSequence i x -> Span i
- psqEmpty :: PSequence i x
- psqIsEmpty :: PSequence i x -> Bool
- psqxs :: PSequence i x -> [(x, i)]
- psequence :: Ord i => (x -> x -> x) -> [(x, i)] -> PSequence i x
- psqHead :: PSequence i x -> (x, i)
- psqTail :: PSequence i x -> PSequence i x
- psqMap :: (x -> y) -> PSequence i x -> PSequence i y
- psqMapShift :: Number i => i -> ((x, i) -> y) -> PSequence i x -> PSequence i y
- psqFilter :: (x -> Bool) -> PSequence i x -> PSequence i x
- psqSplitWhile :: ((x, i) -> Bool) -> PSequence i x -> (PSequence i x, PSequence i x)
- psqInterlace :: Ord i => (x -> y -> z) -> (x -> z) -> (y -> z) -> PSequence i x -> PSequence i y -> PSequence i z
- psqCompose :: (Ord i, Ord j) => PSequence i x -> PSequence j i -> PSequence j x
- psqAppend :: PSequence i x -> PSequence i x -> PSequence i x
- psqShear :: Ord i => (Maybe a -> Maybe a -> Maybe a, i) -> (Maybe a -> Maybe a -> Maybe a, i) -> PSequence i a -> PSequence i a
- psqSwap :: Ord i => i -> i -> PSequence i a -> PSequence i a
- xPSequence :: Ord i => N -> N -> X x -> X i -> X (PSequence i x)
Sequence
newtype PSequence i x Source #
partially defined sequences (x0,i0),(x1,i1)..
of index items in x
with a
totally ordered index type i
.
Property Let
be in PSequence
xis
then holds:
PSequence
i xi
for all <
j..(_,i)
in :
(_,j)..xis
.
Examples
>>>
PSequence [('a',3),('b',7),('c',12)] :: PSequence N Char
PSequence [('a',3),('b',7),('c',12)]
and
>>>
validate (valid (PSequence [('a',3),('b',7),('c',12)] :: PSequence N Char))
Valid
but
>>>
validate (valid (PSequence [('a',3),('b',15),('c',12)] :: PSequence N Char))
Invalid
as Char
is a totally ordered type it can serve as index type
>>>
validate (valid (PSequence [(12,'c'),(3,'e'),(8,'x')] :: PSequence Char Z))
Valid
and they admit a total right operation <*
of
Permutation
i
>>>
(PSequence [(12,'c'),(3,'e'),(8,'x')] :: PSequence Char Z) <* pmtSwap 'e' 'x'
PSequence [(12,'c'),(8,'e'),(3,'x')]
Note As we keep the constructor public, it is crucial for there further use to
ensure that they are valid
!
PSequence [(x, i)] |
Instances
psqIsEmpty :: PSequence i x -> Bool Source #
checks of being empty.
psequence :: Ord i => (x -> x -> x) -> [(x, i)] -> PSequence i x Source #
the partial sequenc given by a aggregation function an a list of value index pairs, which will be sorted and accordingly aggregated by thegiven aggregation function.
psqMap :: (x -> y) -> PSequence i x -> PSequence i y Source #
maps the entries, where the indices are preserved.
psqMapShift :: Number i => i -> ((x, i) -> y) -> PSequence i x -> PSequence i y Source #
maps and shifts a partial sequence.
psqFilter :: (x -> Bool) -> PSequence i x -> PSequence i x Source #
filters the partially defiend sequence accordingly the given predicate.
psqSplitWhile :: ((x, i) -> Bool) -> PSequence i x -> (PSequence i x, PSequence i x) Source #
splits the sequence as long as the given predicate holds.
psqInterlace :: Ord i => (x -> y -> z) -> (x -> z) -> (y -> z) -> PSequence i x -> PSequence i y -> PSequence i z Source #
interlaces the tow partially defined sequences according to the given mappings.
psqShear :: Ord i => (Maybe a -> Maybe a -> Maybe a, i) -> (Maybe a -> Maybe a -> Maybe a, i) -> PSequence i a -> PSequence i a Source #