q4c12-twofinger-0.2: Efficient alternating finger trees

Safe HaskellSafe
LanguageHaskell2010

Q4C12.TwoFinger

Contents

Description

This module provides alternating finger trees, based on Seq from the containers package. 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:

Many of the functions in this package follow laws, which are not documented inline. tests/Properties.hs is an automatically-tested QuickCheck suite of properties.

Synopsis

TwoFingerOddA

data TwoFingerOddA e a Source #

Isomorphic to a, (e, a)*

Instances

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 #

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 #

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 #

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 #

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

(*>) :: 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) #

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 #

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 #

(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 # 
(Monoid a, Semigroup a) => Monoid (TwoFingerOddA e a) Source # 
(NFData e, NFData a) => NFData (TwoFingerOddA e a) Source # 

Methods

rnf :: TwoFingerOddA e a -> () #

type Rep (TwoFingerOddA e a) Source # 
type Rep (TwoFingerOddA e a) = D1 * (MetaData "TwoFingerOddA" "Q4C12.TwoFinger.Internal" "q4c12-twofinger-0.2-9cBnWEqDzTnESyfCCTtQBn" False) (C1 * (MetaCons "TwoFingerOddA" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Seq (a, e)))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

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(1)\) worst case. Inverse: halfunconsEvenE

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

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

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

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

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

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

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

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 #

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 #

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 #

Bitraversable1 TwoFingerOddE Source # 

Methods

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

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

Bifoldable1 TwoFingerOddE Source # 

Methods

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

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

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 # 
type Rep (TwoFingerOddE e a) = D1 * (MetaData "TwoFingerOddE" "Q4C12.TwoFinger.Internal" "q4c12-twofinger-0.2-9cBnWEqDzTnESyfCCTtQBn" False) (C1 * (MetaCons "TwoFingerOddE" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * e)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Seq (a, e))))))

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(\log n)\) worst case. Inverse: halfunconsEvenA

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

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

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

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

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

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

TwoFingerEvenA

data TwoFingerEvenA e a Source #

Isomorphic to (a, e)*

Instances

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 #

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 #

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 #

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 # 
Monoid (TwoFingerEvenA e a) Source # 
(NFData e, NFData a) => NFData (TwoFingerEvenA e a) Source # 

Methods

rnf :: TwoFingerEvenA e a -> () #

type Rep (TwoFingerEvenA e a) Source # 
type Rep (TwoFingerEvenA e a) = D1 * (MetaData "TwoFingerEvenA" "Q4C12.TwoFinger.Internal" "q4c12-twofinger-0.2-9cBnWEqDzTnESyfCCTtQBn" False) (C1 * (MetaCons "TwoFingerEvenA" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Seq (a, e)))))

Full conses

Half conses

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

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

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

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

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

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

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

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

TwoFingerEvenE

data TwoFingerEvenE e a Source #

Isomorphic to (e, a)*

Instances

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 #

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 #

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 #

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 # 
Monoid (TwoFingerEvenE e a) Source # 
(NFData e, NFData a) => NFData (TwoFingerEvenE e a) Source # 

Methods

rnf :: TwoFingerEvenE e a -> () #

type Rep (TwoFingerEvenE e a) Source # 
type Rep (TwoFingerEvenE e a) = D1 * (MetaData "TwoFingerEvenE" "Q4C12.TwoFinger.Internal" "q4c12-twofinger-0.2-9cBnWEqDzTnESyfCCTtQBn" False) ((:+:) * (C1 * (MetaCons "EmptyEvenE" PrefixI False) (U1 *)) (C1 * (MetaCons "TwoFingerEvenE" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * e)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Seq (a, e)))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))))

Full conses

Half conses

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

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

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

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

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

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

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

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

Appending different flavours

Monoid actions

Two odds make an even