hgeometry-combinatorial
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellSafe-Inferred
LanguageGHC2021

HGeometry.Sequence.Alternating

Description

A Type representing Alternating sequences. The sequence type itself is parameterized.

Synopsis

Documentation

data Alternating f sep a Source #

A (non-empty) alternating sequence of a's and sep's.

Constructors

Alternating a (f (sep, a)) 

Instances

Instances details
Foldable f => Bifoldable (Alternating f) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

bifold :: Monoid m => Alternating f m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Alternating f a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Alternating f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Alternating f a b -> c #

Functor f => Bifunctor (Alternating f) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

bimap :: (a -> b) -> (c -> d) -> Alternating f a c -> Alternating f b d #

first :: (a -> b) -> Alternating f a c -> Alternating f b c #

second :: (b -> c) -> Alternating f a b -> Alternating f a c #

Traversable f => Bitraversable (Alternating f) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> Alternating f a b -> f0 (Alternating f c d) #

Foldable f => Foldable (Alternating f sep) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

fold :: Monoid m => Alternating f sep m -> m #

foldMap :: Monoid m => (a -> m) -> Alternating f sep a -> m #

foldMap' :: Monoid m => (a -> m) -> Alternating f sep a -> m #

foldr :: (a -> b -> b) -> b -> Alternating f sep a -> b #

foldr' :: (a -> b -> b) -> b -> Alternating f sep a -> b #

foldl :: (b -> a -> b) -> b -> Alternating f sep a -> b #

foldl' :: (b -> a -> b) -> b -> Alternating f sep a -> b #

foldr1 :: (a -> a -> a) -> Alternating f sep a -> a #

foldl1 :: (a -> a -> a) -> Alternating f sep a -> a #

toList :: Alternating f sep a -> [a] #

null :: Alternating f sep a -> Bool #

length :: Alternating f sep a -> Int #

elem :: Eq a => a -> Alternating f sep a -> Bool #

maximum :: Ord a => Alternating f sep a -> a #

minimum :: Ord a => Alternating f sep a -> a #

sum :: Num a => Alternating f sep a -> a #

product :: Num a => Alternating f sep a -> a #

Foldable f => Foldable1 (Alternating f sep) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

fold1 :: Semigroup m => Alternating f sep m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Alternating f sep a -> m #

foldMap1' :: Semigroup m => (a -> m) -> Alternating f sep a -> m #

toNonEmpty :: Alternating f sep a -> NonEmpty a #

maximum :: Ord a => Alternating f sep a -> a #

minimum :: Ord a => Alternating f sep a -> a #

head :: Alternating f sep a -> a #

last :: Alternating f sep a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Alternating f sep a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Alternating f sep a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Alternating f sep a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Alternating f sep a -> b #

Traversable f => Traversable (Alternating f sep) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Alternating f sep a -> f0 (Alternating f sep b) #

sequenceA :: Applicative f0 => Alternating f sep (f0 a) -> f0 (Alternating f sep a) #

mapM :: Monad m => (a -> m b) -> Alternating f sep a -> m (Alternating f sep b) #

sequence :: Monad m => Alternating f sep (m a) -> m (Alternating f sep a) #

Functor f => Functor (Alternating f sep) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

fmap :: (a -> b) -> Alternating f sep a -> Alternating f sep b #

(<$) :: a -> Alternating f sep b -> Alternating f sep a #

Traversable f => Traversable1 (Alternating f sep) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

traverse1 :: Apply f0 => (a -> f0 b) -> Alternating f sep a -> f0 (Alternating f sep b) Source #

sequence1 :: Apply f0 => Alternating f sep (f0 b) -> f0 (Alternating f sep b) Source #

Generic (Alternating f sep a) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Associated Types

type Rep (Alternating f sep a) :: Type -> Type #

Methods

from :: Alternating f sep a -> Rep (Alternating f sep a) x #

to :: Rep (Alternating f sep a) x -> Alternating f sep a #

(Show a, Show (f (sep, a))) => Show (Alternating f sep a) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

showsPrec :: Int -> Alternating f sep a -> ShowS #

show :: Alternating f sep a -> String #

showList :: [Alternating f sep a] -> ShowS #

(NFData a, NFData (f (sep, a))) => NFData (Alternating f sep a) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

rnf :: Alternating f sep a -> () #

(Eq a, Eq (f (sep, a))) => Eq (Alternating f sep a) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

(==) :: Alternating f sep a -> Alternating f sep a -> Bool #

(/=) :: Alternating f sep a -> Alternating f sep a -> Bool #

(Ord a, Ord (f (sep, a))) => Ord (Alternating f sep a) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

Methods

compare :: Alternating f sep a -> Alternating f sep a -> Ordering #

(<) :: Alternating f sep a -> Alternating f sep a -> Bool #

(<=) :: Alternating f sep a -> Alternating f sep a -> Bool #

(>) :: Alternating f sep a -> Alternating f sep a -> Bool #

(>=) :: Alternating f sep a -> Alternating f sep a -> Bool #

max :: Alternating f sep a -> Alternating f sep a -> Alternating f sep a #

min :: Alternating f sep a -> Alternating f sep a -> Alternating f sep a #

type Rep (Alternating f sep a) Source # 
Instance details

Defined in HGeometry.Sequence.Alternating

type Rep (Alternating f sep a) = D1 ('MetaData "Alternating" "HGeometry.Sequence.Alternating" "hgeometry-combinatorial-1.0.0.0-inplace" 'False) (C1 ('MetaCons "Alternating" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (sep, a)))))

fromNonEmptyWith :: (HasFromFoldable g, Foldable1 f) => sep -> f a -> Alternating g sep a Source #

Given a separator, and some foldable structure, constructs an Alternating.

mapF :: (f (sep, a) -> g (sep', a)) -> Alternating f sep a -> Alternating g sep' a Source #

map some function changing the f into a g.

firstWithNeighbors :: Traversable f => (a -> sep -> a -> sep') -> Alternating f sep a -> Alternating f sep' a Source #

Map over the separators of the alterating together with the neighbours

withNeighbours :: Foldable f => Alternating f sep a -> [(a, sep, a)] Source #

Computes a b with all its neighbours

>>> withNeighbours (Alternating 0 [('a', 1), ('b', 2), ('c',3)])
[(0,'a',1),(1,'b',2),(2,'c',3)]

mergeAlternating :: Ord t => (t -> a -> b -> c) -> Alternating List t a -> Alternating List t b -> [(t, c)] Source #

Generic merging scheme that merges two Alternating Lists and applies the function 'f', with the current/new value at every event. So note that if the alternating consists of 'Alternating a0 [(t1,a2)]' then the function is applied to a1, not to a0 (i.e. every value ai is considered alive on the interval [ti,t(i+1))

>>> let odds  = Alternating "a" [(3,"c"), (5,"e"), (7,"g")]
>>> let evens = Alternating "b" [(4,"d"), (6,"f"), (8,"h")]
>>> mergeAlternating (\_ a b -> a <> b) odds evens
[(3,"cb"),(4,"cd"),(5,"ed"),(6,"ef"),(7,"gf"),(8,"gh")]
>>> mergeAlternating (\t a b -> if t `mod` 2 == 0 then a else b) odds evens
[(3,"b"),(4,"c"),(5,"d"),(6,"e"),(7,"f"),(8,"g")]
>>> mergeAlternating (\_ a b -> a <> b) odds (Alternating "b" [(0,"d"), (5,"e"), (8,"h")])
[(0,"ad"),(3,"cd"),(5,"ee"),(7,"ge"),(8,"gh")]

insertBreakPoints :: Ord t => [t] -> Alternating List t a -> Alternating List t a Source #

Adds additional t-values in the alternating, (in sorted order). I.e. if we insert a "breakpoint" at time t the current 'a' value is used at that time.

>>> insertBreakPoints [0,2,4,6,8,10] $ Alternating "a" [(3, "c"), (5, "e"), (7,"g")]
Alternating "a" [(0,"a"),(2,"a"),(3,"c"),(4,"c"),(5,"e"),(6,"e"),(7,"g"),(8,"g"),(10,"g")]

reverse :: Alternating List b a -> Alternating List b a Source #

Reverses an alternating list.

>>> reverse $ Alternating "a" [(3, "c"), (5, "e"), (7, "g")]
Alternating "g" [(7,"e"),(5,"c"),(3,"a")]

consElemWith :: Cons (f (sep, a)) (f (sep, a)) (sep, a) (sep, a) => (a -> a -> sep) -> a -> Alternating f sep a -> Alternating f sep a Source #

Given a function f that takes the new element y and the (current) first element x and computes the new separating element s, conses y and the the separator onto alternating list.

>>> consElemWith (\_ _ -> ".") 0 (fromNonEmptyWith @[] "," (NonEmpty.fromList [1..5]))
Alternating 0 [(".",1),(",",2),(",",3),(",",4),(",",5)]
>>> consElemWith (\_ _ -> ".") 0 (fromNonEmptyWith @[] "," (NonEmpty.fromList [1]))
Alternating 0 [(".",1)]

unconsAlt :: Cons (f (sep, a)) (f (sep, a)) (sep, a) (sep, a) => Alternating f sep a -> Either a ((a, sep), Alternating f sep a) Source #

Uncons the Alternating, getting either just the first element (if there was only one), or the first element, the first separator, and the remaining alternating.

snocElemWith :: Snoc (f (sep, a)) (f (sep, a)) (sep, a) (sep, a) => (a -> a -> sep) -> Alternating f sep a -> a -> Alternating f sep a Source #

Given a function f that takes the (current) last element x, and the new element y, and computes the new separating element s, snocs the separator and y onto the alternating list.

>>> snocElemWith (\_ _ -> ".") (fromNonEmptyWith @[] "," (NonEmpty.fromList [1..5])) 6
Alternating 1 [(",",2),(",",3),(",",4),(",",5),(".",6)]
>>> snocElemWith (\_ _ -> ".") (fromNonEmptyWith @[] "," (NonEmpty.fromList [1])) 6
Alternating 1 [(".",6)]

separators :: Functor f => Alternating f sep a -> f sep Source #

Get the separators out of the alternating