q4c12-twofinger-0.0.0.1: Efficient alternating finger trees

Stabilityunstable
Safe HaskellSafe
LanguageHaskell2010

Q4C12.TwoFinger.Internal

Contents

Description

This is an internal module and not subject to the PVP. It may receive arbitrary changes at any time and between any two releases. Import from Q4C12.TwoFinger instead, unless you really need the gory details, and, in that case, you must depend on the exact version of this package. (If you do need them, please file a bug so that, hopefully, your use-case can be accomplished through the public interface.)

Synopsis

Documentation

>>> import Data.List (unfoldr)
>>> import Data.Tuple (swap)
>>> import Control.Lens (over, view)
>>> let hush = either (const Nothing) Just

(<.*>) :: Apply f => f (a -> b) -> MaybeApply f a -> f b infixl 4 Source #

(<*.>) :: Apply f => MaybeApply f (a -> b) -> f a -> f b infixl 4 Source #

traverseDefault :: (Applicative f, Traversable1 t) => (a -> f a') -> t a -> f (t a') Source #

bitraverseDefault :: (Applicative f, Bitraversable1 t) => (a -> f a') -> (b -> f b') -> t a b -> f (t a' b') Source #

Types, EqN?/ShowN?/(Bi)Functor/Foldable1?/Traversable1?

data Digit e a Source #

Constructors

One e 
Two e a e 
Three e a e a e 
Four e a e a e a e 

Instances

Bifunctor Digit Source # 

Methods

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

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

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

Bitraversable Digit Source # 

Methods

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

Bifoldable Digit Source # 

Methods

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

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

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

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

Bitraversable1 Digit Source # 

Methods

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

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

Bifoldable1 Digit Source # 

Methods

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

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

Functor (Digit e) Source # 

Methods

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

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

Foldable (Digit e) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: Digit e a -> Bool #

length :: Digit e a -> Int #

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

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

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

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

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

Traversable (Digit e) Source # 

Methods

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

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

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

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

Generic (Digit e a) Source # 

Associated Types

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

Methods

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

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

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

Methods

rnf :: Digit e a -> () #

type Rep (Digit e a) Source # 
type Rep (Digit e a) = D1 (MetaData "Digit" "Q4C12.TwoFinger.Internal" "q4c12-twofinger-0.0.0.1-8syHtPdDjE8313bgi8LFJc" False) ((:+:) ((:+:) (C1 (MetaCons "One" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e))) (C1 (MetaCons "Two" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e)))))) ((:+:) (C1 (MetaCons "Three" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e)))))) (C1 (MetaCons "Four" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e)))) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e))))))))

data Node e a Source #

Constructors

Node2 e a e 
Node3 e a e a e 

Instances

Bifunctor Node Source # 

Methods

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

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

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

Bitraversable Node Source # 

Methods

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

Bifoldable Node Source # 

Methods

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

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

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

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

Bitraversable1 Node Source # 

Methods

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

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

Bifoldable1 Node Source # 

Methods

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

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

Functor (Node e) Source # 

Methods

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

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

Foldable (Node e) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: Node e a -> Bool #

length :: Node e a -> Int #

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

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

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

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

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

Traversable (Node e) Source # 

Methods

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

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

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

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

Traversable1 (Node e) Source # 

Methods

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

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

Foldable1 (Node e) Source # 

Methods

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

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

toNonEmpty :: Node e a -> NonEmpty a #

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

Methods

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

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

Generic (Node e a) Source # 

Associated Types

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

Methods

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

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

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

Methods

rnf :: Node e a -> () #

type Rep (Node e a) Source # 

data TwoFingerOddA e a Source #

Isomorphic to a, (e, a)*

Constructors

EmptyOddA a 
SingleOddA a e a 
DeepOddA a !(Digit e a) (TwoFingerOddA (Node e a) a) !(Digit e a) 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 # 

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)

data TwoFingerOddE e a Source #

Isomorphic to e, (a, e)*

Constructors

SingleOddE e 
DeepOddE !(Digit e a) (TwoFingerOddA (Node e a) a) !(Digit e a) 

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 # 

data TwoFingerEvenE e a Source #

Isomorphic to (e, a)*

Constructors

EmptyEvenE 
SingleEvenE e a 
DeepEvenE !(Digit e a) (TwoFingerOddA (Node e a) a) !(Digit e a) 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 # 

data TwoFingerEvenA e a Source #

Isomorphic to (a, e)*

Constructors

EmptyEvenA 
SingleEvenA a e 
DeepEvenA a !(Digit e a) (TwoFingerOddA (Node e a) a) !(Digit e a) 

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 # 

Digit operations.

digitCons :: e -> a -> Digit e a -> Either (Digit e a, a, Node e a) (Digit e a) Source #

digitSnoc :: Digit e a -> a -> e -> Either (Node e a, a, Digit e a) (Digit e a) Source #

digitUncons :: Digit e a -> (e, Maybe (a, Digit e a)) Source #

digitUnsnoc :: Digit e a -> (Maybe (Digit e a, a), e) Source #

Node operations.

nodeToDigit :: Node e a -> Digit e a Source #

Tree rotations

(Un)conses/snocs for TwoFingerOddA.

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

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

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)

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)

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

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

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

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

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

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

(Un)conses/snocs for TwoFingerOddE.

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

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

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)

(Un)conses/snocs for TwoFingerEvenE.

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)

(Un)conses/snocs for TwoFingerEvenA.

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)

Monad and Applicative instances, and related operations

Construction and deconstruction of TwoFingerOddA.

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))

Construction of TwoFingerOddE

Concatenation of TwoFingerOddA.

addDigits0 :: TwoFingerOddA (Node e a) a -> Digit e a -> a -> Digit e a -> TwoFingerOddA (Node e a) a -> TwoFingerOddA (Node e a) a Source #

addDigits1 :: TwoFingerOddA (Node e a) a -> Digit e a -> a -> e -> a -> Digit e a -> TwoFingerOddA (Node e a) a -> TwoFingerOddA (Node e a) a Source #

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

addDigits2 :: TwoFingerOddA (Node e a) a -> Digit e a -> a -> e -> a -> e -> a -> Digit e a -> TwoFingerOddA (Node e a) a -> TwoFingerOddA (Node e a) a Source #

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

addDigits3 :: TwoFingerOddA (Node e a) a -> Digit e a -> a -> e -> a -> e -> a -> e -> a -> Digit e a -> TwoFingerOddA (Node e a) a -> TwoFingerOddA (Node e a) a Source #

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

addDigits4 :: TwoFingerOddA (Node e a) a -> Digit e a -> a -> e -> a -> e -> a -> e -> a -> e -> a -> Digit e a -> TwoFingerOddA (Node e a) a -> TwoFingerOddA (Node e a) a Source #

Concatenation of TwoFingerEvenE.

Concatenation of TwoFingerEvenA.

Monoid actions

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

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

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

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

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

QuickCheck stuff.

genDigit :: Gen e -> Gen a -> Gen (Digit e a) Source #

genNode :: Gen e -> Gen a -> Gen (Node e a) Source #

genOddA :: Gen e -> Gen a -> Int -> Gen (TwoFingerOddA e a) Source #

The Int parameter is expontential size: for a value \(n\), the generated tree will have (slightly more than) \(2^n\) to \(3^n\) elements.

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'

Creating infinite sequences.

takeNodeLeft :: (Stream a -> es -> (e, Stream a, es)) -> Stream a -> es -> (Node e a, Stream a, es) Source #

takeNodeRight :: (es -> Stream a -> (e, es, Stream a)) -> es -> Stream a -> (Node e a, es, Stream a) Source #

infiniteOddA' :: (Stream a -> Stream e -> (Node e' a, Stream a, Stream e)) -> (Stream e -> Stream a -> (Node e' a, Stream e, Stream a)) -> Stream a -> Stream e -> Stream e -> Stream a -> TwoFingerOddA e' a Source #

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)

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)]

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

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)]

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)

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)]

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)

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)]