q4c12-twofinger-0.0.0.2: Efficient alternating finger trees

Safe HaskellSafe
LanguageHaskell2010

Q4C12.TwoFinger

Contents

Description

This module provides alternating finger trees, which are similar to Data.Sequence in the containers package, or Data.FingerTree in the fingertree package, except that, between every element (of type e) in the 'normal' finger tree, there is a 'separator' of type a. TwoFingerOddA e () is isomorphic to [e], and TwoFingerOddA e a is isomorphic to ([(a, e)], a). (The type variables are in that order because that permits a Traversable1 instance for TwoFingerOddA.)

Four flavours of alternating finger trees are present, corresponding to different element patterns:

The flavours' names first describe whether they have the same number of as and es within them (the Even flavours do, the Odd ones do not), and then whether the first element is an e or an a.

(Full) conses and snocs prepend or append a pair of elements to the front or rear of an alternating finger tree, keeping the flavour the same. Half-conses and -snocs transform between these flavours, adding only half the pair. All cons-like operations have an inverse operation. Some half-conses and -snocs and their inverses are \(O(1)\) amortised, with \(O(\log n)\) worst case, while some are \(O(1)\) always. All full conses, snocs and inverses are \(O(1)\) amortised and \(O(\log n)\) worst case.

Note that the names of half-conses and -snocs take the flavour that they operate on, which means that, for example, halfconsOddA and halfunconsOddA are not inverses; the actual inverse pairs are halfconsOddA + halfunconsEvenE and halfconsEvenE + halfunconsOddA.

Appending alternating finger trees is also efficient. As well as the usual Monoid and Semigroup instances, the two Even flavours can be viewed as monoid actions of the Odd flavours. All append-like operations are \(O(\log(\min(n, m)))\) amortised and \(O(\log(\max(n, m)))\) worst case.

For more information on finger trees, see:

This package's alternating finger trees are not annotated with sizes as described in section 4 of the paper.

Synopsis

TwoFingerOddA

data TwoFingerOddA e a Source #

Isomorphic to a, (e, a)*

Instances

Eq2 TwoFingerOddA Source # 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> TwoFingerOddA a c -> TwoFingerOddA b d -> Bool #

Show2 TwoFingerOddA Source # 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> TwoFingerOddA a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [TwoFingerOddA a b] -> ShowS #

Bifunctor TwoFingerOddA Source # 

Methods

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

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

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

Bitraversable TwoFingerOddA Source # 

Methods

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

Bifoldable TwoFingerOddA Source # 

Methods

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

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

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

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

Bitraversable1 TwoFingerOddA Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> TwoFingerOddA a c -> f (TwoFingerOddA b d) #

bisequence1 :: Apply f => TwoFingerOddA (f a) (f b) -> f (TwoFingerOddA a b) #

Bifoldable1 TwoFingerOddA Source # 

Methods

bifold1 :: Semigroup m => TwoFingerOddA m m -> m #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> TwoFingerOddA a b -> m #

Monad (TwoFingerOddA e) Source # 

Methods

(>>=) :: TwoFingerOddA e a -> (a -> TwoFingerOddA e b) -> TwoFingerOddA e b #

(>>) :: TwoFingerOddA e a -> TwoFingerOddA e b -> TwoFingerOddA e b #

return :: a -> TwoFingerOddA e a #

fail :: String -> TwoFingerOddA e a #

Functor (TwoFingerOddA e) Source # 

Methods

fmap :: (a -> b) -> TwoFingerOddA e a -> TwoFingerOddA e b #

(<$) :: a -> TwoFingerOddA e b -> TwoFingerOddA e a #

Applicative (TwoFingerOddA e) Source #

A 'producty' instance:

>>> (,) <$> (consOddA 1 "one" $ consOddA 2 "two" $ singletonOddA 3) <*> (consOddA 'a' "foo" $ singletonOddA 'b')
consOddA (1,'a') "foo" (consOddA (1,'b') "one" (consOddA (2,'a') "foo" (consOddA (2,'b') "two" (consOddA (3,'a') "foo" (singletonOddA (3,'b'))))))

Methods

pure :: a -> TwoFingerOddA e a #

(<*>) :: TwoFingerOddA e (a -> b) -> TwoFingerOddA e a -> TwoFingerOddA e b #

(*>) :: TwoFingerOddA e a -> TwoFingerOddA e b -> TwoFingerOddA e b #

(<*) :: TwoFingerOddA e a -> TwoFingerOddA e b -> TwoFingerOddA e a #

Foldable (TwoFingerOddA e) Source # 

Methods

fold :: Monoid m => TwoFingerOddA e m -> m #

foldMap :: Monoid m => (a -> m) -> TwoFingerOddA e a -> m #

foldr :: (a -> b -> b) -> b -> TwoFingerOddA e a -> b #

foldr' :: (a -> b -> b) -> b -> TwoFingerOddA e a -> b #

foldl :: (b -> a -> b) -> b -> TwoFingerOddA e a -> b #

foldl' :: (b -> a -> b) -> b -> TwoFingerOddA e a -> b #

foldr1 :: (a -> a -> a) -> TwoFingerOddA e a -> a #

foldl1 :: (a -> a -> a) -> TwoFingerOddA e a -> a #

toList :: TwoFingerOddA e a -> [a] #

null :: TwoFingerOddA e a -> Bool #

length :: TwoFingerOddA e a -> Int #

elem :: Eq a => a -> TwoFingerOddA e a -> Bool #

maximum :: Ord a => TwoFingerOddA e a -> a #

minimum :: Ord a => TwoFingerOddA e a -> a #

sum :: Num a => TwoFingerOddA e a -> a #

product :: Num a => TwoFingerOddA e a -> a #

Traversable (TwoFingerOddA e) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TwoFingerOddA e a -> f (TwoFingerOddA e b) #

sequenceA :: Applicative f => TwoFingerOddA e (f a) -> f (TwoFingerOddA e a) #

mapM :: Monad m => (a -> m b) -> TwoFingerOddA e a -> m (TwoFingerOddA e b) #

sequence :: Monad m => TwoFingerOddA e (m a) -> m (TwoFingerOddA e a) #

Eq e => Eq1 (TwoFingerOddA e) Source # 

Methods

liftEq :: (a -> b -> Bool) -> TwoFingerOddA e a -> TwoFingerOddA e b -> Bool #

Show e => Show1 (TwoFingerOddA e) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> TwoFingerOddA e a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [TwoFingerOddA e a] -> ShowS #

Traversable1 (TwoFingerOddA e) Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> TwoFingerOddA e a -> f (TwoFingerOddA e b) #

sequence1 :: Apply f => TwoFingerOddA e (f b) -> f (TwoFingerOddA e b) #

Apply (TwoFingerOddA e) Source # 

Methods

(<.>) :: TwoFingerOddA e (a -> b) -> TwoFingerOddA e a -> TwoFingerOddA e b #

(.>) :: TwoFingerOddA e a -> TwoFingerOddA e b -> TwoFingerOddA e b #

(<.) :: TwoFingerOddA e a -> TwoFingerOddA e b -> TwoFingerOddA e a #

Bind (TwoFingerOddA e) Source # 

Methods

(>>-) :: TwoFingerOddA e a -> (a -> TwoFingerOddA e b) -> TwoFingerOddA e b #

join :: TwoFingerOddA e (TwoFingerOddA e a) -> TwoFingerOddA e a #

Foldable1 (TwoFingerOddA e) Source # 

Methods

fold1 :: Semigroup m => TwoFingerOddA e m -> m #

foldMap1 :: Semigroup m => (a -> m) -> TwoFingerOddA e a -> m #

toNonEmpty :: TwoFingerOddA e a -> NonEmpty a #

(Eq e, Eq a) => Eq (TwoFingerOddA e a) Source # 

Methods

(==) :: TwoFingerOddA e a -> TwoFingerOddA e a -> Bool #

(/=) :: TwoFingerOddA e a -> TwoFingerOddA e a -> Bool #

(Show e, Show a) => Show (TwoFingerOddA e a) Source # 
Generic (TwoFingerOddA e a) Source # 

Associated Types

type Rep (TwoFingerOddA e a) :: * -> * #

Methods

from :: TwoFingerOddA e a -> Rep (TwoFingerOddA e a) x #

to :: Rep (TwoFingerOddA e a) x -> TwoFingerOddA e a #

Semigroup a => Semigroup (TwoFingerOddA e a) Source #
\(AnyOddA a) (AnyOddA b) (AnyOddA c) -> (a <> b) <> c == a <> (b <> c)
(Monoid a, Semigroup a) => Monoid (TwoFingerOddA e a) Source #
\(AnyOddA a) -> a == mempty <> a
\(AnyOddA a) -> a == a <> mempty
(NFData e, NFData a) => NFData (TwoFingerOddA e a) Source # 

Methods

rnf :: TwoFingerOddA e a -> () #

type Rep (TwoFingerOddA e a) Source # 

Construction and analysis

unitOddA :: (Monoid a, Semigroup a) => e -> TwoFingerOddA e a Source #

Surrounds the argument with mempty.

>>> unitOddA 3 :: TwoFingerOddA Int String
consOddA "" 3 (singletonOddA "")

onlyOddA :: TwoFingerOddA e a -> Maybe a Source #

>>> onlyOddA (singletonOddA "Hello!")
Just "Hello!"
>>> onlyOddA (consOddA True 3 $ singletonOddA False)
Nothing

interleavingOddA :: e -> NonEmpty a -> TwoFingerOddA e a Source #

>>> interleavingOddA "sep" (3 :| [4, 5])
consOddA 3 "sep" (consOddA 4 "sep" (singletonOddA 5))

Full conses

consOddA :: a -> e -> TwoFingerOddA e a -> TwoFingerOddA e a Source #

snocOddA :: TwoFingerOddA e a -> e -> a -> TwoFingerOddA e a Source #

Half conses

halfconsOddA :: e -> TwoFingerOddA e a -> TwoFingerEvenE e a Source #

\(O(\log n)\) worst case. Inverse: halfunconsEvenE

\e (AnyOddA as) -> halfunconsEvenE (halfconsOddA e as) == Just (e, as)

halfunconsOddA :: TwoFingerOddA e a -> (a, TwoFingerEvenE e a) Source #

\(O(1)\) worst case. Inverse: halfconsEvenE

\(AnyOddA as) -> as == uncurry halfconsEvenE (halfunconsOddA as)

halfsnocOddA :: TwoFingerOddA e a -> e -> TwoFingerEvenA e a Source #

\(O(\log n)\) worst case. Inverse: halfunsnocEvenA

\(AnyOddA as) e -> halfunsnocEvenA (halfsnocOddA as e) == Just (as, e)

halfunsnocOddA :: TwoFingerOddA e a -> (TwoFingerEvenA e a, a) Source #

\(O(1)\) worst case. Inverse: halfsnocOddA

\(AnyOddA as) -> as == uncurry halfsnocEvenA (halfunsnocOddA as)

Lenses

firstOddA :: Functor f => (a -> f a) -> TwoFingerOddA e a -> f (TwoFingerOddA e a) Source #

Access the first a of a TwoFingerOddA e a. \(O(1)\). This type is Lens' (TwoFingerOddA e a) a in disguise.

>>> view firstOddA (consOddA 3 True $ singletonOddA 15)
3

lastOddA :: Functor f => (a -> f a) -> TwoFingerOddA e a -> f (TwoFingerOddA e a) Source #

Access the last a of a TwoFingerOddA e a. \(O(1)\). This type is Lens' (TwoFingerOddA e a) a in disguise.

>>> over lastOddA (+ 5) (consOddA 3 True $ singletonOddA 15)
consOddA 3 True (singletonOddA 20)

TwoFingerOddE

data TwoFingerOddE e a Source #

Isomorphic to e, (a, e)*

Instances

Eq2 TwoFingerOddE Source # 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> TwoFingerOddE a c -> TwoFingerOddE b d -> Bool #

Show2 TwoFingerOddE Source # 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> TwoFingerOddE a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [TwoFingerOddE a b] -> ShowS #

Bifunctor TwoFingerOddE Source # 

Methods

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

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

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

Bitraversable TwoFingerOddE Source # 

Methods

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

Bifoldable TwoFingerOddE Source # 

Methods

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

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

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

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

Functor (TwoFingerOddE e) Source # 

Methods

fmap :: (a -> b) -> TwoFingerOddE e a -> TwoFingerOddE e b #

(<$) :: a -> TwoFingerOddE e b -> TwoFingerOddE e a #

Foldable (TwoFingerOddE e) Source # 

Methods

fold :: Monoid m => TwoFingerOddE e m -> m #

foldMap :: Monoid m => (a -> m) -> TwoFingerOddE e a -> m #

foldr :: (a -> b -> b) -> b -> TwoFingerOddE e a -> b #

foldr' :: (a -> b -> b) -> b -> TwoFingerOddE e a -> b #

foldl :: (b -> a -> b) -> b -> TwoFingerOddE e a -> b #

foldl' :: (b -> a -> b) -> b -> TwoFingerOddE e a -> b #

foldr1 :: (a -> a -> a) -> TwoFingerOddE e a -> a #

foldl1 :: (a -> a -> a) -> TwoFingerOddE e a -> a #

toList :: TwoFingerOddE e a -> [a] #

null :: TwoFingerOddE e a -> Bool #

length :: TwoFingerOddE e a -> Int #

elem :: Eq a => a -> TwoFingerOddE e a -> Bool #

maximum :: Ord a => TwoFingerOddE e a -> a #

minimum :: Ord a => TwoFingerOddE e a -> a #

sum :: Num a => TwoFingerOddE e a -> a #

product :: Num a => TwoFingerOddE e a -> a #

Traversable (TwoFingerOddE e) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TwoFingerOddE e a -> f (TwoFingerOddE e b) #

sequenceA :: Applicative f => TwoFingerOddE e (f a) -> f (TwoFingerOddE e a) #

mapM :: Monad m => (a -> m b) -> TwoFingerOddE e a -> m (TwoFingerOddE e b) #

sequence :: Monad m => TwoFingerOddE e (m a) -> m (TwoFingerOddE e a) #

Eq e => Eq1 (TwoFingerOddE e) Source # 

Methods

liftEq :: (a -> b -> Bool) -> TwoFingerOddE e a -> TwoFingerOddE e b -> Bool #

Show e => Show1 (TwoFingerOddE e) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> TwoFingerOddE e a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [TwoFingerOddE e a] -> ShowS #

(Eq e, Eq a) => Eq (TwoFingerOddE e a) Source # 

Methods

(==) :: TwoFingerOddE e a -> TwoFingerOddE e a -> Bool #

(/=) :: TwoFingerOddE e a -> TwoFingerOddE e a -> Bool #

(Show e, Show a) => Show (TwoFingerOddE e a) Source # 
Generic (TwoFingerOddE e a) Source # 

Associated Types

type Rep (TwoFingerOddE e a) :: * -> * #

Methods

from :: TwoFingerOddE e a -> Rep (TwoFingerOddE e a) x #

to :: Rep (TwoFingerOddE e a) x -> TwoFingerOddE e a #

(NFData e, NFData a) => NFData (TwoFingerOddE e a) Source # 

Methods

rnf :: TwoFingerOddE e a -> () #

type Rep (TwoFingerOddE e a) Source # 

Construction

Full conses

consOddE :: e -> a -> TwoFingerOddE e a -> TwoFingerOddE e a Source #

snocOddE :: TwoFingerOddE e a -> a -> e -> TwoFingerOddE e a Source #

Half conses

halfconsOddE :: a -> TwoFingerOddE e a -> TwoFingerEvenA e a Source #

\(O(1)\) worst case. Inverse: halfunconsEvenA

\a (AnyOddE as) -> halfunconsEvenA (halfconsOddE a as) == Just (a, as)

halfsnocOddE :: TwoFingerOddE e a -> a -> TwoFingerEvenE e a Source #

\(O(1)\) worst case. Inverse: halfunsnocEvenE

\(AnyOddE as) a -> halfunsnocEvenE (halfsnocOddE as a) == Just (as, a)

halfunconsOddE :: TwoFingerOddE e a -> (e, TwoFingerEvenA e a) Source #

\(O(\log n)\) worst case. Inverse: halfconsEvenA

\(AnyOddE as) -> as == uncurry halfconsEvenA (halfunconsOddE as)

halfunsnocOddE :: TwoFingerOddE e a -> (TwoFingerEvenE e a, e) Source #

\(O(\log n)\) worst case. Inverse: halfsnocEvenE

\(AnyOddE as) -> as == uncurry halfsnocEvenE (halfunsnocOddE as)

TwoFingerEvenA

data TwoFingerEvenA e a Source #

Isomorphic to (a, e)*

Instances

Eq2 TwoFingerEvenA Source # 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> TwoFingerEvenA a c -> TwoFingerEvenA b d -> Bool #

Show2 TwoFingerEvenA Source # 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> TwoFingerEvenA a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [TwoFingerEvenA a b] -> ShowS #

Bifunctor TwoFingerEvenA Source # 

Methods

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

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

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

Bitraversable TwoFingerEvenA Source # 

Methods

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

Bifoldable TwoFingerEvenA Source # 

Methods

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

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

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

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

Functor (TwoFingerEvenA e) Source # 

Methods

fmap :: (a -> b) -> TwoFingerEvenA e a -> TwoFingerEvenA e b #

(<$) :: a -> TwoFingerEvenA e b -> TwoFingerEvenA e a #

Foldable (TwoFingerEvenA e) Source # 

Methods

fold :: Monoid m => TwoFingerEvenA e m -> m #

foldMap :: Monoid m => (a -> m) -> TwoFingerEvenA e a -> m #

foldr :: (a -> b -> b) -> b -> TwoFingerEvenA e a -> b #

foldr' :: (a -> b -> b) -> b -> TwoFingerEvenA e a -> b #

foldl :: (b -> a -> b) -> b -> TwoFingerEvenA e a -> b #

foldl' :: (b -> a -> b) -> b -> TwoFingerEvenA e a -> b #

foldr1 :: (a -> a -> a) -> TwoFingerEvenA e a -> a #

foldl1 :: (a -> a -> a) -> TwoFingerEvenA e a -> a #

toList :: TwoFingerEvenA e a -> [a] #

null :: TwoFingerEvenA e a -> Bool #

length :: TwoFingerEvenA e a -> Int #

elem :: Eq a => a -> TwoFingerEvenA e a -> Bool #

maximum :: Ord a => TwoFingerEvenA e a -> a #

minimum :: Ord a => TwoFingerEvenA e a -> a #

sum :: Num a => TwoFingerEvenA e a -> a #

product :: Num a => TwoFingerEvenA e a -> a #

Traversable (TwoFingerEvenA e) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TwoFingerEvenA e a -> f (TwoFingerEvenA e b) #

sequenceA :: Applicative f => TwoFingerEvenA e (f a) -> f (TwoFingerEvenA e a) #

mapM :: Monad m => (a -> m b) -> TwoFingerEvenA e a -> m (TwoFingerEvenA e b) #

sequence :: Monad m => TwoFingerEvenA e (m a) -> m (TwoFingerEvenA e a) #

Eq e => Eq1 (TwoFingerEvenA e) Source # 

Methods

liftEq :: (a -> b -> Bool) -> TwoFingerEvenA e a -> TwoFingerEvenA e b -> Bool #

Show e => Show1 (TwoFingerEvenA e) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> TwoFingerEvenA e a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [TwoFingerEvenA e a] -> ShowS #

Plus (TwoFingerEvenA e) Source # 

Methods

zero :: TwoFingerEvenA e a #

Alt (TwoFingerEvenA e) Source # 
(Eq e, Eq a) => Eq (TwoFingerEvenA e a) Source # 
(Show e, Show a) => Show (TwoFingerEvenA e a) Source # 
Generic (TwoFingerEvenA e a) Source # 

Associated Types

type Rep (TwoFingerEvenA e a) :: * -> * #

Methods

from :: TwoFingerEvenA e a -> Rep (TwoFingerEvenA e a) x #

to :: Rep (TwoFingerEvenA e a) x -> TwoFingerEvenA e a #

Semigroup (TwoFingerEvenA e a) Source #
\(AnyEvenA a) (AnyEvenA b) (AnyEvenA c) -> (a <> b) <> c == a <> (b <> c)
Monoid (TwoFingerEvenA e a) Source #
\(AnyEvenA a) -> a == a <> mempty
\(AnyEvenA a) -> a == mempty <> a
(NFData e, NFData a) => NFData (TwoFingerEvenA e a) Source # 

Methods

rnf :: TwoFingerEvenA e a -> () #

type Rep (TwoFingerEvenA e a) Source # 

Full conses

Half conses

halfconsEvenA :: e -> TwoFingerEvenA e a -> TwoFingerOddE e a Source #

\(O(\log n)\) worst case. Inverse: halfunconsOddE.

\e (AnyEvenA as) -> halfunconsOddE (halfconsEvenA e as) == (e, as)

halfsnocEvenA :: TwoFingerEvenA e a -> a -> TwoFingerOddA e a Source #

\(O(1)\) worst case. Inverse: halfunsnocOddA.

\(AnyEvenA as) a -> halfunsnocOddA (halfsnocEvenA as a) == (as, a)

halfunconsEvenA :: TwoFingerEvenA e a -> Maybe (a, TwoFingerOddE e a) Source #

\(O(1)\) worst case. Inverse: halfconsOddE.

\(AnyEvenA as) -> as == maybe mempty (uncurry halfconsOddE) (halfunconsEvenA as)

halfunsnocEvenA :: TwoFingerEvenA e a -> Maybe (TwoFingerOddA e a, e) Source #

\(O(\log n)\) worst case. Inverse: halfsnocOddA.

\(AnyEvenA as) -> as == maybe mempty (uncurry halfsnocOddA) (halfunsnocEvenA as)

TwoFingerEvenE

data TwoFingerEvenE e a Source #

Isomorphic to (e, a)*

Instances

Eq2 TwoFingerEvenE Source # 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> TwoFingerEvenE a c -> TwoFingerEvenE b d -> Bool #

Show2 TwoFingerEvenE Source # 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> TwoFingerEvenE a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [TwoFingerEvenE a b] -> ShowS #

Bifunctor TwoFingerEvenE Source # 

Methods

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

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

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

Bitraversable TwoFingerEvenE Source # 

Methods

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

Bifoldable TwoFingerEvenE Source # 

Methods

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

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

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

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

Functor (TwoFingerEvenE e) Source # 

Methods

fmap :: (a -> b) -> TwoFingerEvenE e a -> TwoFingerEvenE e b #

(<$) :: a -> TwoFingerEvenE e b -> TwoFingerEvenE e a #

Foldable (TwoFingerEvenE e) Source # 

Methods

fold :: Monoid m => TwoFingerEvenE e m -> m #

foldMap :: Monoid m => (a -> m) -> TwoFingerEvenE e a -> m #

foldr :: (a -> b -> b) -> b -> TwoFingerEvenE e a -> b #

foldr' :: (a -> b -> b) -> b -> TwoFingerEvenE e a -> b #

foldl :: (b -> a -> b) -> b -> TwoFingerEvenE e a -> b #

foldl' :: (b -> a -> b) -> b -> TwoFingerEvenE e a -> b #

foldr1 :: (a -> a -> a) -> TwoFingerEvenE e a -> a #

foldl1 :: (a -> a -> a) -> TwoFingerEvenE e a -> a #

toList :: TwoFingerEvenE e a -> [a] #

null :: TwoFingerEvenE e a -> Bool #

length :: TwoFingerEvenE e a -> Int #

elem :: Eq a => a -> TwoFingerEvenE e a -> Bool #

maximum :: Ord a => TwoFingerEvenE e a -> a #

minimum :: Ord a => TwoFingerEvenE e a -> a #

sum :: Num a => TwoFingerEvenE e a -> a #

product :: Num a => TwoFingerEvenE e a -> a #

Traversable (TwoFingerEvenE e) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TwoFingerEvenE e a -> f (TwoFingerEvenE e b) #

sequenceA :: Applicative f => TwoFingerEvenE e (f a) -> f (TwoFingerEvenE e a) #

mapM :: Monad m => (a -> m b) -> TwoFingerEvenE e a -> m (TwoFingerEvenE e b) #

sequence :: Monad m => TwoFingerEvenE e (m a) -> m (TwoFingerEvenE e a) #

Eq e => Eq1 (TwoFingerEvenE e) Source # 

Methods

liftEq :: (a -> b -> Bool) -> TwoFingerEvenE e a -> TwoFingerEvenE e b -> Bool #

Show e => Show1 (TwoFingerEvenE e) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> TwoFingerEvenE e a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [TwoFingerEvenE e a] -> ShowS #

Plus (TwoFingerEvenE e) Source # 

Methods

zero :: TwoFingerEvenE e a #

Alt (TwoFingerEvenE e) Source # 
(Eq e, Eq a) => Eq (TwoFingerEvenE e a) Source # 
(Show e, Show a) => Show (TwoFingerEvenE e a) Source # 
Generic (TwoFingerEvenE e a) Source # 

Associated Types

type Rep (TwoFingerEvenE e a) :: * -> * #

Methods

from :: TwoFingerEvenE e a -> Rep (TwoFingerEvenE e a) x #

to :: Rep (TwoFingerEvenE e a) x -> TwoFingerEvenE e a #

Semigroup (TwoFingerEvenE e a) Source #
\(AnyEvenE a) (AnyEvenE b) (AnyEvenE c) -> (a <> b) <> c == a <> (b <> c)
Monoid (TwoFingerEvenE e a) Source #
\(AnyEvenE a) -> a == a <> mempty
\(AnyEvenE a) -> a == mempty <> a
(NFData e, NFData a) => NFData (TwoFingerEvenE e a) Source # 

Methods

rnf :: TwoFingerEvenE e a -> () #

type Rep (TwoFingerEvenE e a) Source # 

Full conses

Half conses

halfconsEvenE :: a -> TwoFingerEvenE e a -> TwoFingerOddA e a Source #

\(O(1)\) worst case. Inverse: halfunconsOddA

\a (AnyEvenE as) -> halfunconsOddA (halfconsEvenE a as) == (a, as)

halfsnocEvenE :: TwoFingerEvenE e a -> e -> TwoFingerOddE e a Source #

\(O(\log n)\) worst case. Inverse: halfunsnocOddE.

\(AnyEvenE as) e -> halfunsnocOddE (halfsnocEvenE as e) == (as, e)

halfunconsEvenE :: TwoFingerEvenE e a -> Maybe (e, TwoFingerOddA e a) Source #

\(O(\log n)\) worst case. Inverse: halfconsOddA.

\(AnyEvenE as) -> as == maybe mempty (uncurry halfconsOddA) (halfunconsEvenE as)

halfunsnocEvenE :: TwoFingerEvenE e a -> Maybe (TwoFingerOddE e a, a) Source #

\(O(1)\) worst case. Inverse: halfsnocOddE.

\(AnyEvenE as) -> as == maybe mempty (uncurry halfsnocOddE) (halfunsnocEvenE as)

Appending different flavours

\(AnyOddA a) (AnyOddA b) (AnyEvenE c) -> appendOddAEvenE (a <> b) c == a <> appendOddAEvenE b c
\(AnyOddA a) (AnyOddE b) (AnyOddA c) -> appendEvenAOddA (appendOddAOddE a b) c == appendOddAEvenE a (appendOddEOddA b c)
\(AnyOddA a) (AnyOddE b) (AnyEvenA c) -> appendOddAOddE a (appendOddEEvenA b c) == appendOddAOddE a b <> c
\(AnyOddA a) (AnyEvenE b) (AnyOddE c) -> appendOddAOddE a (appendEvenEOddE b c) == appendOddAOddE (appendOddAEvenE a b) c
\(AnyOddA a) (AnyEvenE b) (AnyEvenE c) -> appendOddAEvenE a (b <> c) == appendOddAEvenE (appendOddAEvenE a b) c
\(AnyOddE a) (AnyOddA b) (AnyOddE c) -> appendOddEEvenA a (appendOddAOddE b c) == appendEvenEOddE (appendOddEOddA a b) c
\(AnyOddE a) (AnyOddA b) (AnyEvenE c) -> appendOddEOddA a (appendOddAEvenE b c) == appendOddEOddA a b <> c
\(AnyOddE a) (AnyEvenA b) (AnyOddA c) -> appendOddEOddA a (appendEvenAOddA b c) == appendOddEOddA (appendOddEEvenA a b) c
\(AnyOddE a) (AnyEvenA b) (AnyEvenA c) -> appendOddEEvenA a (b <> c) == appendOddEEvenA (appendOddEEvenA a b) c
\(AnyEvenA a) (AnyOddA b) (AnyOddA c) -> appendEvenAOddA a (b <> c) == appendEvenAOddA a b <> c
\(AnyEvenA a) (AnyOddA b) (AnyOddE c) -> appendOddAOddE (appendEvenAOddA a b) c == a <> appendOddAOddE b c
\(AnyEvenA a) (AnyOddA b) (AnyEvenE c) -> appendOddAEvenE (appendEvenAOddA a b) c == appendEvenAOddA a (appendOddAEvenE b c)
\(AnyEvenA a) (AnyEvenA b) (AnyOddA c) -> appendEvenAOddA (a <> b) c == appendEvenAOddA a (appendEvenAOddA b c)
\(AnyEvenE a) (AnyOddE b) (AnyOddA c) -> appendOddEOddA (appendEvenEOddE a b) c == a <> appendOddEOddA b c
\(AnyEvenE a) (AnyOddE b) (AnyEvenA c) -> appendOddEEvenA (appendEvenEOddE a b) c == appendEvenEOddE a (appendOddEEvenA b c)
\(AnyEvenE a) (AnyEvenE b) (AnyOddE c) -> appendEvenEOddE (a <> b) c == appendEvenEOddE a (appendEvenEOddE b c)

appendEvenAOddA :: TwoFingerEvenA e a -> TwoFingerOddA e a -> TwoFingerOddA e a Source #

\(AnyOddA a) -> a == appendEvenAOddA mempty a

appendOddEEvenA :: TwoFingerOddE e a -> TwoFingerEvenA e a -> TwoFingerOddE e a Source #

\(AnyOddE a) -> a == appendOddEEvenA a mempty

appendOddAEvenE :: TwoFingerOddA e a -> TwoFingerEvenE e a -> TwoFingerOddA e a Source #

\(AnyOddA a) -> a == appendOddAEvenE a mempty

appendEvenEOddE :: TwoFingerEvenE e a -> TwoFingerOddE e a -> TwoFingerOddE e a Source #

\(AnyOddE a) -> a == appendEvenEOddE mempty a

Two odds make an even

Aligning (zipping)

alignLeftOddAOddA :: TwoFingerOddA e a -> TwoFingerOddA e' a' -> (TwoFingerOddA (e, e') (a, a'), Either (TwoFingerEvenE e a) (TwoFingerEvenE e' a')) Source #

Align two TwoFingerOddA sequences elementwise, and return the excess remainder.

>>> alignLeftOddAOddA (consOddA 'a' 1 $ consOddA 'b' 2 $ singletonOddA 'c') (consOddA "foo" 10 $ singletonOddA "bar")
(consOddA ('a',"foo") (1,10) (singletonOddA ('b',"bar")),Left (consEvenE 2 'c' mempty))
>>> alignLeftOddAOddA (consOddA 'a' 1 $ singletonOddA 'b') (consOddA "foo" 10 $ consOddA "bar" 20 $ singletonOddA "baz")
(consOddA ('a',"foo") (1,10) (singletonOddA ('b',"bar")),Right (consEvenE 20 "baz" mempty))
\(AnyOddA as) (AnyOddA bs) -> let { (aligned, rest) = alignLeftOddAOddA as bs ; as' = appendOddAEvenE (bimap fst fst aligned) (either id (const mempty) rest) ; bs' = appendOddAEvenE (bimap snd snd aligned) (either (const mempty) id rest) } in as == as' && bs == bs'

alignLeftOddAEvenA :: TwoFingerOddA e a -> TwoFingerEvenA e' a' -> Either (TwoFingerEvenA (e, e') (a, a'), TwoFingerOddA e a) (TwoFingerOddA (e, e') (a, a'), TwoFingerOddE e' a') Source #

>>> alignLeftOddAEvenA (consOddA 'a' 1 $ consOddA 'b' 2 $ singletonOddA 'c') (consEvenA "foo" 10 mempty)
Left (consEvenA ('a',"foo") (1,10) mempty,consOddA 'b' 2 (singletonOddA 'c'))
>>> alignLeftOddAEvenA (consOddA 'a' 1 $ singletonOddA 'b') (consEvenA "foo" 10 $ consEvenA "bar" 20 $ consEvenA "baz" 30 mempty)
Right (consOddA ('a',"foo") (1,10) (singletonOddA ('b',"bar")),consOddE 20 "baz" (singletonOddE 30))
\(AnyOddA as) (AnyEvenA bs) -> let { (as', bs') = case alignLeftOddAEvenA as bs of { Left (aligned, rest) -> (appendEvenAOddA (bimap fst fst aligned) rest, bimap snd snd aligned) ; Right (aligned, rest) -> (bimap fst fst aligned, appendOddAOddE (bimap snd snd aligned) rest) } } in as == as' && bs == bs'

alignLeftOddEOddE :: TwoFingerOddE e a -> TwoFingerOddE e' a' -> (TwoFingerOddE (e, e') (a, a'), Either (TwoFingerEvenA e a) (TwoFingerEvenA e' a')) Source #

>>> alignLeftOddEOddE (consOddE 'a' 1 $ consOddE 'b' 2 $ singletonOddE 'c') (consOddE "foo" 10 $ singletonOddE "bar")
(consOddE ('a',"foo") (1,10) (singletonOddE ('b',"bar")),Left (consEvenA 2 'c' mempty))
>>> alignLeftOddEOddE (consOddE 'a' 1 $ singletonOddE 'b') (consOddE "foo" 10 $ consOddE "bar" 20 $ singletonOddE "baz")
(consOddE ('a',"foo") (1,10) (singletonOddE ('b',"bar")),Right (consEvenA 20 "baz" mempty))
\(AnyOddE as) (AnyOddE bs) -> let { (aligned, rest) = alignLeftOddEOddE as bs ; as' = appendOddEEvenA (bimap fst fst aligned) (either id (const mempty) rest) ; bs' = appendOddEEvenA (bimap snd snd aligned) (either (const mempty) id rest) } in as == as' && bs == bs'

alignLeftOddEEvenE :: TwoFingerOddE e a -> TwoFingerEvenE e' a' -> Either (TwoFingerEvenE (e, e') (a, a'), TwoFingerOddE e a) (TwoFingerOddE (e, e') (a, a'), TwoFingerOddA e' a') Source #

\(AnyOddE as) (AnyEvenE bs) -> let { (as', bs') = case alignLeftOddEEvenE as bs of { Left (aligned, rest) -> (appendEvenEOddE (bimap fst fst aligned) rest, bimap snd snd aligned) ; Right (aligned, rest) -> (bimap fst fst aligned, appendOddEOddA (bimap snd snd aligned) rest) } } in as == as' && bs == bs'

Infinite trees

repeatOddA :: a -> e -> TwoFingerOddA e a Source #

Infinitely repeat the given a and e.

\(AnyOddA as) -> as == bimap (uncurry ($)) (uncurry ($)) (fst $ alignLeftOddAOddA (repeatOddA id id) as)
\(AnyEvenA as) -> either ((as ==) . bimap (uncurry ($)) (uncurry ($)) . fst) (const False) (alignLeftOddAEvenA (repeatOddA id id) as)

repeatOddE :: e -> a -> TwoFingerOddE e a Source #

Infinitely repeat the given a and e.

\(AnyOddE as) -> as == bimap (uncurry ($)) (uncurry ($)) (fst $ alignLeftOddEOddE (repeatOddE id id) as)
\(AnyEvenE as) -> either ((==) as . bimap (uncurry ($)) (uncurry ($)) . fst) (const False) $ alignLeftOddEEvenE (repeatOddE id id) as

repeatEvenA :: a -> e -> TwoFingerEvenA e a Source #

Infinitely repeat the given a and e.

\(AnyEvenA as) -> as == bimap (uncurry ($)) (uncurry ($)) (fst $ alignLeftEvenAEvenA (repeatEvenA id id) as)
\(AnyOddA as) -> either (const False) ((==) as . bimap (uncurry $ flip ($)) (uncurry $ flip ($)) . fst) $ alignLeftOddAEvenA as (repeatEvenA id id)

repeatEvenE :: e -> a -> TwoFingerEvenE e a Source #

\(AnyEvenE as) -> as == bimap (uncurry ($)) (uncurry ($)) (fst $ alignLeftEvenEEvenE (repeatEvenE id id) as)
\(AnyOddE as) -> either (const False) ((==) as . bimap (uncurry $ flip ($)) (uncurry $ flip ($)) . fst) $ alignLeftOddEEvenE as (repeatEvenE id id)

infiniteOddA :: Stream a -> Stream e -> Stream e -> Stream a -> TwoFingerOddA e a Source #

From streams of leftward a, leftward e, rightward e and rightward a, build an infinite TwoFingerOddA.

>>> let infinite = infiniteOddA (Stream.iterate (+ 1) 0) (Stream.iterate (+ 1) 10) (Stream.iterate (+ 1) 20) (Stream.iterate (+ 1) 30)
>>> take 5 $ unfoldr (hush . unconsOddA) infinite
[(0,10),(1,11),(2,12),(3,13),(4,14)]
>>> take 5 $ unfoldr (fmap swap . hush . unsnocOddA) infinite
[(20,30),(21,31),(22,32),(23,33),(24,34)]

infiniteOddE :: Stream e -> Stream a -> Stream a -> Stream e -> TwoFingerOddE e a Source #

>>> let infinite = infiniteOddE (Stream.iterate (+ 1) 0) (Stream.iterate (+ 1) 10) (Stream.iterate (+ 1) 20) (Stream.iterate (+ 1) 30)
>>> take 5 $ unfoldr (hush . unconsOddE) infinite
[(0,10),(1,11),(2,12),(3,13),(4,14)]
>>> take 5 $ unfoldr (fmap swap . hush . unsnocOddE) infinite
[(20,30),(21,31),(22,32),(23,33),(24,34)]

infiniteEvenA :: Stream a -> Stream e -> Stream a -> Stream e -> TwoFingerEvenA e a Source #

>>> let infinite = infiniteEvenA (Stream.iterate (+ 1) 0) (Stream.iterate (+ 1) 10) (Stream.iterate (+ 1) 20) (Stream.iterate (+ 1) 30)
>>> take 5 $ unfoldr unconsEvenA infinite
[(0,10),(1,11),(2,12),(3,13),(4,14)]
>>> take 5 $ unfoldr (fmap swap . unsnocEvenA) infinite
[(20,30),(21,31),(22,32),(23,33),(24,34)]

infiniteEvenE :: Stream e -> Stream a -> Stream e -> Stream a -> TwoFingerEvenE e a Source #

>>> let infinite = infiniteEvenE (Stream.iterate (+ 1) 0) (Stream.iterate (+ 1) 10) (Stream.iterate (+ 1) 20) (Stream.iterate (+ 1) 30)
>>> take 5 $ unfoldr unconsEvenE infinite
[(0,10),(1,11),(2,12),(3,13),(4,14)]
>>> take 5 $ unfoldr (fmap swap . unsnocEvenE) infinite
[(20,30),(21,31),(22,32),(23,33),(24,34)]