hgeometry-combinatorial-0.11.0.0: Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Data.List.Alternating

Synopsis

Documentation

data Alternating a b Source #

A (non-empty) alternating list of a's and b's

Constructors

Alternating a [b :+ a] 
Instances
Bifunctor Alternating Source # 
Instance details

Defined in Data.List.Alternating

Methods

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

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

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

Bitraversable Alternating Source # 
Instance details

Defined in Data.List.Alternating

Methods

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

Bifoldable Alternating Source # 
Instance details

Defined in Data.List.Alternating

Methods

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

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

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

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

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

Defined in Data.List.Alternating

Methods

(==) :: Alternating a b -> Alternating a b -> Bool #

(/=) :: Alternating a b -> Alternating a b -> Bool #

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

Defined in Data.List.Alternating

Methods

compare :: Alternating a b -> Alternating a b -> Ordering #

(<) :: Alternating a b -> Alternating a b -> Bool #

(<=) :: Alternating a b -> Alternating a b -> Bool #

(>) :: Alternating a b -> Alternating a b -> Bool #

(>=) :: Alternating a b -> Alternating a b -> Bool #

max :: Alternating a b -> Alternating a b -> Alternating a b #

min :: Alternating a b -> Alternating a b -> Alternating a b #

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

Defined in Data.List.Alternating

Methods

showsPrec :: Int -> Alternating a b -> ShowS #

show :: Alternating a b -> String #

showList :: [Alternating a b] -> ShowS #

withNeighbours :: Alternating a b -> [(a, b :+ 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 a t -> Alternating b t -> [t :+ c] Source #

Generic merging scheme that merges two Alternatings and applies the function f, with the current/new value at every event. So note that if the alternating consists of 'Alternating a0 [t1 :+ a1]' 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 a t -> Alternating a t 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 a b -> Alternating a b Source #

Reverses an alternating list.

>>> reverse $ Alternating "a" [3 :+ "c", 5 :+ "e", 7 :+ "g"]
Alternating "g" [7 :+ "e",5 :+ "c",3 :+ "a"]