{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Safe #-}
#endif
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE DeriveGeneric #-}
#endif
#if __GLASGOW_HASKELL__ >= 710 && __GLASGOW_HASKELL__ < 802
{-# LANGUAGE AutoDeriveTypeable #-}
#endif
-----------------------------------------------------------------------------
-- |
-- Module      :  Data.FingerTree
-- Copyright   :  Ross Paterson and Ralf Hinze 2006,
--                Ross Paterson 2006-2022,
--                James Cranch 2021
-- License     :  BSD-style
-- Maintainer  :  R.Paterson@city.ac.uk
-- Stability   :  experimental
-- Portability :  non-portable (MPTCs and functional dependencies)
--
-- A general sequence representation with arbitrary annotations, for
-- use as a base for implementations of various collection types, as
-- described in section 4 of
--
--  * Ralf Hinze and Ross Paterson,
--    \"Finger trees: a simple general-purpose data structure\",
--    /Journal of Functional Programming/ 16:2 (2006) pp 197-217.
--    <http://staff.city.ac.uk/~ross/papers/FingerTree.html>
--
-- For a directly usable sequence type, see @Data.Sequence@, which is
-- a specialization of this structure.
--
-- An amortized running time is given for each operation, with /n/
-- referring to the length of the sequence.  These bounds hold even in
-- a persistent (shared) setting.
--
-- /Note/: Many of these operations have the same names as similar
-- operations on lists in the "Prelude".  The ambiguity may be resolved
-- using either qualification or the @hiding@ clause.
--
-----------------------------------------------------------------------------

module Data.FingerTree (
#if TESTING
    FingerTree(..), Digit(..), Node(..), deep, node2, node3,
#else
    FingerTree,
#endif
    Measured(..),
    -- * Construction
    empty, singleton,
    (<|), (|>), (><),
    fromList,
    -- * Deconstruction
    null,
    -- ** Examining the ends
    ViewL(..), viewl,
    ViewR(..), viewr,
    -- ** Search
    SearchResult(..), search,
    -- ** Splitting
    -- | These functions are special cases of 'search'.
    split, takeUntil, dropUntil,
    -- * Transformation
    reverse,
    -- ** Maps
    fmap', fmapWithPos, fmapWithContext, unsafeFmap,
    -- ** Folds
    foldlWithPos, foldrWithPos, foldlWithContext, foldrWithContext,
    -- ** Traversals
    traverse', traverseWithPos, traverseWithContext, unsafeTraverse,
    -- * Example
    -- $example
    ) where

import Prelude hiding (null, reverse)
#if MIN_VERSION_base(4,6,0)
import GHC.Generics
#endif
#if MIN_VERSION_base(4,8,0)
import qualified Prelude (null)
#else
import Control.Applicative (Applicative(pure, (<*>)), (<$>))
import Data.Monoid
import Data.Foldable (Foldable(foldMap))
#endif
#if (MIN_VERSION_base(4,9,0)) && !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
import Data.Foldable (toList)

infixr 5 ><
infixr 5 <|, :<
infixl 5 |>, :>

-- | View of the left end of a sequence.
data ViewL s a
    = EmptyL        -- ^ empty sequence
    | a :< s a      -- ^ leftmost element and the rest of the sequence
    deriving (ViewL s a -> ViewL s a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (s :: * -> *) a.
(Eq a, Eq (s a)) =>
ViewL s a -> ViewL s a -> Bool
/= :: ViewL s a -> ViewL s a -> Bool
$c/= :: forall (s :: * -> *) a.
(Eq a, Eq (s a)) =>
ViewL s a -> ViewL s a -> Bool
== :: ViewL s a -> ViewL s a -> Bool
$c== :: forall (s :: * -> *) a.
(Eq a, Eq (s a)) =>
ViewL s a -> ViewL s a -> Bool
Eq, ViewL s a -> ViewL s a -> Bool
ViewL s a -> ViewL s a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {s :: * -> *} {a}. (Ord a, Ord (s a)) => Eq (ViewL s a)
forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewL s a -> ViewL s a -> Bool
forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewL s a -> ViewL s a -> Ordering
forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewL s a -> ViewL s a -> ViewL s a
min :: ViewL s a -> ViewL s a -> ViewL s a
$cmin :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewL s a -> ViewL s a -> ViewL s a
max :: ViewL s a -> ViewL s a -> ViewL s a
$cmax :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewL s a -> ViewL s a -> ViewL s a
>= :: ViewL s a -> ViewL s a -> Bool
$c>= :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewL s a -> ViewL s a -> Bool
> :: ViewL s a -> ViewL s a -> Bool
$c> :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewL s a -> ViewL s a -> Bool
<= :: ViewL s a -> ViewL s a -> Bool
$c<= :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewL s a -> ViewL s a -> Bool
< :: ViewL s a -> ViewL s a -> Bool
$c< :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewL s a -> ViewL s a -> Bool
compare :: ViewL s a -> ViewL s a -> Ordering
$ccompare :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewL s a -> ViewL s a -> Ordering
Ord, Int -> ViewL s a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (s :: * -> *) a.
(Show a, Show (s a)) =>
Int -> ViewL s a -> ShowS
forall (s :: * -> *) a.
(Show a, Show (s a)) =>
[ViewL s a] -> ShowS
forall (s :: * -> *) a. (Show a, Show (s a)) => ViewL s a -> String
showList :: [ViewL s a] -> ShowS
$cshowList :: forall (s :: * -> *) a.
(Show a, Show (s a)) =>
[ViewL s a] -> ShowS
show :: ViewL s a -> String
$cshow :: forall (s :: * -> *) a. (Show a, Show (s a)) => ViewL s a -> String
showsPrec :: Int -> ViewL s a -> ShowS
$cshowsPrec :: forall (s :: * -> *) a.
(Show a, Show (s a)) =>
Int -> ViewL s a -> ShowS
Show, ReadPrec [ViewL s a]
ReadPrec (ViewL s a)
ReadS [ViewL s a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall (s :: * -> *) a.
(Read a, Read (s a)) =>
ReadPrec [ViewL s a]
forall (s :: * -> *) a.
(Read a, Read (s a)) =>
ReadPrec (ViewL s a)
forall (s :: * -> *) a.
(Read a, Read (s a)) =>
Int -> ReadS (ViewL s a)
forall (s :: * -> *) a. (Read a, Read (s a)) => ReadS [ViewL s a]
readListPrec :: ReadPrec [ViewL s a]
$creadListPrec :: forall (s :: * -> *) a.
(Read a, Read (s a)) =>
ReadPrec [ViewL s a]
readPrec :: ReadPrec (ViewL s a)
$creadPrec :: forall (s :: * -> *) a.
(Read a, Read (s a)) =>
ReadPrec (ViewL s a)
readList :: ReadS [ViewL s a]
$creadList :: forall (s :: * -> *) a. (Read a, Read (s a)) => ReadS [ViewL s a]
readsPrec :: Int -> ReadS (ViewL s a)
$creadsPrec :: forall (s :: * -> *) a.
(Read a, Read (s a)) =>
Int -> ReadS (ViewL s a)
Read
#if __GLASGOW_HASKELL__ >= 706
        , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: * -> *) a x. Rep (ViewL s a) x -> ViewL s a
forall (s :: * -> *) a x. ViewL s a -> Rep (ViewL s a) x
$cto :: forall (s :: * -> *) a x. Rep (ViewL s a) x -> ViewL s a
$cfrom :: forall (s :: * -> *) a x. ViewL s a -> Rep (ViewL s a) x
Generic
#endif
        )

-- | View of the right end of a sequence.
data ViewR s a
    = EmptyR        -- ^ empty sequence
    | s a :> a      -- ^ the sequence minus the rightmost element,
                    -- and the rightmost element
    deriving (ViewR s a -> ViewR s a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (s :: * -> *) a.
(Eq a, Eq (s a)) =>
ViewR s a -> ViewR s a -> Bool
/= :: ViewR s a -> ViewR s a -> Bool
$c/= :: forall (s :: * -> *) a.
(Eq a, Eq (s a)) =>
ViewR s a -> ViewR s a -> Bool
== :: ViewR s a -> ViewR s a -> Bool
$c== :: forall (s :: * -> *) a.
(Eq a, Eq (s a)) =>
ViewR s a -> ViewR s a -> Bool
Eq, ViewR s a -> ViewR s a -> Bool
ViewR s a -> ViewR s a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {s :: * -> *} {a}. (Ord a, Ord (s a)) => Eq (ViewR s a)
forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewR s a -> ViewR s a -> Bool
forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewR s a -> ViewR s a -> Ordering
forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewR s a -> ViewR s a -> ViewR s a
min :: ViewR s a -> ViewR s a -> ViewR s a
$cmin :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewR s a -> ViewR s a -> ViewR s a
max :: ViewR s a -> ViewR s a -> ViewR s a
$cmax :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewR s a -> ViewR s a -> ViewR s a
>= :: ViewR s a -> ViewR s a -> Bool
$c>= :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewR s a -> ViewR s a -> Bool
> :: ViewR s a -> ViewR s a -> Bool
$c> :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewR s a -> ViewR s a -> Bool
<= :: ViewR s a -> ViewR s a -> Bool
$c<= :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewR s a -> ViewR s a -> Bool
< :: ViewR s a -> ViewR s a -> Bool
$c< :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewR s a -> ViewR s a -> Bool
compare :: ViewR s a -> ViewR s a -> Ordering
$ccompare :: forall (s :: * -> *) a.
(Ord a, Ord (s a)) =>
ViewR s a -> ViewR s a -> Ordering
Ord, Int -> ViewR s a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (s :: * -> *) a.
(Show a, Show (s a)) =>
Int -> ViewR s a -> ShowS
forall (s :: * -> *) a.
(Show a, Show (s a)) =>
[ViewR s a] -> ShowS
forall (s :: * -> *) a. (Show a, Show (s a)) => ViewR s a -> String
showList :: [ViewR s a] -> ShowS
$cshowList :: forall (s :: * -> *) a.
(Show a, Show (s a)) =>
[ViewR s a] -> ShowS
show :: ViewR s a -> String
$cshow :: forall (s :: * -> *) a. (Show a, Show (s a)) => ViewR s a -> String
showsPrec :: Int -> ViewR s a -> ShowS
$cshowsPrec :: forall (s :: * -> *) a.
(Show a, Show (s a)) =>
Int -> ViewR s a -> ShowS
Show, ReadPrec [ViewR s a]
ReadPrec (ViewR s a)
ReadS [ViewR s a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall (s :: * -> *) a.
(Read a, Read (s a)) =>
ReadPrec [ViewR s a]
forall (s :: * -> *) a.
(Read a, Read (s a)) =>
ReadPrec (ViewR s a)
forall (s :: * -> *) a.
(Read a, Read (s a)) =>
Int -> ReadS (ViewR s a)
forall (s :: * -> *) a. (Read a, Read (s a)) => ReadS [ViewR s a]
readListPrec :: ReadPrec [ViewR s a]
$creadListPrec :: forall (s :: * -> *) a.
(Read a, Read (s a)) =>
ReadPrec [ViewR s a]
readPrec :: ReadPrec (ViewR s a)
$creadPrec :: forall (s :: * -> *) a.
(Read a, Read (s a)) =>
ReadPrec (ViewR s a)
readList :: ReadS [ViewR s a]
$creadList :: forall (s :: * -> *) a. (Read a, Read (s a)) => ReadS [ViewR s a]
readsPrec :: Int -> ReadS (ViewR s a)
$creadsPrec :: forall (s :: * -> *) a.
(Read a, Read (s a)) =>
Int -> ReadS (ViewR s a)
Read
#if __GLASGOW_HASKELL__ >= 706
        , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: * -> *) a x. Rep (ViewR s a) x -> ViewR s a
forall (s :: * -> *) a x. ViewR s a -> Rep (ViewR s a) x
$cto :: forall (s :: * -> *) a x. Rep (ViewR s a) x -> ViewR s a
$cfrom :: forall (s :: * -> *) a x. ViewR s a -> Rep (ViewR s a) x
Generic
#endif
        )

instance (Functor s) => Functor (ViewL s) where
    fmap :: forall a b. (a -> b) -> ViewL s a -> ViewL s b
fmap a -> b
_ ViewL s a
EmptyL    = forall (s :: * -> *) a. ViewL s a
EmptyL
    fmap a -> b
f (a
x :< s a
xs) = a -> b
f a
x forall (s :: * -> *) a. a -> s a -> ViewL s a
:< forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f s a
xs

instance (Functor s) => Functor (ViewR s) where
    fmap :: forall a b. (a -> b) -> ViewR s a -> ViewR s b
fmap a -> b
_ ViewR s a
EmptyR    = forall (s :: * -> *) a. ViewR s a
EmptyR
    fmap a -> b
f (s a
xs :> a
x) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f s a
xs forall (s :: * -> *) a. s a -> a -> ViewR s a
:> a -> b
f a
x

#if MIN_VERSION_base(4,9,0)
instance (Measured v a) => Semigroup (FingerTree v a) where
    <> :: FingerTree v a -> FingerTree v a -> FingerTree v a
(<>) = forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
(><)
#endif

-- | 'empty' and '><'.
instance (Measured v a) => Monoid (FingerTree v a) where
    mempty :: FingerTree v a
mempty = forall v a. Measured v a => FingerTree v a
empty
#if !(MIN_VERSION_base(4,11,0))
    mappend = (><)
#endif

-- Explicit Digit type (Exercise 1)

data Digit a
    = One a
    | Two a a
    | Three a a a
    | Four a a a a
    deriving (Int -> Digit a -> ShowS
forall a. Show a => Int -> Digit a -> ShowS
forall a. Show a => [Digit a] -> ShowS
forall a. Show a => Digit a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Digit a] -> ShowS
$cshowList :: forall a. Show a => [Digit a] -> ShowS
show :: Digit a -> String
$cshow :: forall a. Show a => Digit a -> String
showsPrec :: Int -> Digit a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Digit a -> ShowS
Show
#if __GLASGOW_HASKELL__ >= 706
        , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Digit a) x -> Digit a
forall a x. Digit a -> Rep (Digit a) x
$cto :: forall a x. Rep (Digit a) x -> Digit a
$cfrom :: forall a x. Digit a -> Rep (Digit a) x
Generic
#endif
        )

instance Foldable Digit where
    foldMap :: forall m a. Monoid m => (a -> m) -> Digit a -> m
foldMap a -> m
f (One a
a) = a -> m
f a
a
    foldMap a -> m
f (Two a
a a
b) = a -> m
f a
a forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b
    foldMap a -> m
f (Three a
a a
b a
c) = a -> m
f a
a forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
c
    foldMap a -> m
f (Four a
a a
b a
c a
d) = a -> m
f a
a forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
c forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
d

-------------------
-- 4.1 Measurements
-------------------

-- | Things that can be measured.
class (Monoid v) => Measured v a | a -> v where
    measure :: a -> v

instance (Measured v a) => Measured v (Digit a) where
    measure :: Digit a -> v
measure = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall v a. Measured v a => a -> v
measure

---------------------------
-- 4.2 Caching measurements
---------------------------

data Node v a = Node2 !v a a | Node3 !v a a a
    deriving (Int -> Node v a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall v a. (Show v, Show a) => Int -> Node v a -> ShowS
forall v a. (Show v, Show a) => [Node v a] -> ShowS
forall v a. (Show v, Show a) => Node v a -> String
showList :: [Node v a] -> ShowS
$cshowList :: forall v a. (Show v, Show a) => [Node v a] -> ShowS
show :: Node v a -> String
$cshow :: forall v a. (Show v, Show a) => Node v a -> String
showsPrec :: Int -> Node v a -> ShowS
$cshowsPrec :: forall v a. (Show v, Show a) => Int -> Node v a -> ShowS
Show
#if __GLASGOW_HASKELL__ >= 706
        , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v a x. Rep (Node v a) x -> Node v a
forall v a x. Node v a -> Rep (Node v a) x
$cto :: forall v a x. Rep (Node v a) x -> Node v a
$cfrom :: forall v a x. Node v a -> Rep (Node v a) x
Generic
#endif
        )

instance Foldable (Node v) where
    foldMap :: forall m a. Monoid m => (a -> m) -> Node v a -> m
foldMap a -> m
f (Node2 v
_ a
a a
b) = a -> m
f a
a forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b
    foldMap a -> m
f (Node3 v
_ a
a a
b a
c) = a -> m
f a
a forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
c

node2        ::  (Measured v a) => a -> a -> Node v a
node2 :: forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b    =   forall v a. v -> a -> a -> Node v a
Node2 (forall v a. Measured v a => a -> v
measure a
a forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b) a
a a
b

node3        ::  (Measured v a) => a -> a -> a -> Node v a
node3 :: forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c  =   forall v a. v -> a -> a -> a -> Node v a
Node3 (forall v a. Measured v a => a -> v
measure a
a forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c) a
a a
b a
c

instance (Monoid v) => Measured v (Node v a) where
    measure :: Node v a -> v
measure (Node2 v
v a
_ a
_)    =  v
v
    measure (Node3 v
v a
_ a
_ a
_)  =  v
v

nodeToDigit :: Node v a -> Digit a
nodeToDigit :: forall v a. Node v a -> Digit a
nodeToDigit (Node2 v
_ a
a a
b) = forall a. a -> a -> Digit a
Two a
a a
b
nodeToDigit (Node3 v
_ a
a a
b a
c) = forall a. a -> a -> a -> Digit a
Three a
a a
b a
c

-- | A representation of a sequence of values of type @a@, allowing
-- access to the ends in constant time, and append and split in time
-- logarithmic in the size of the smaller piece.
--
-- The collection is also parameterized by a measure type @v@, which
-- is used to specify a position in the sequence for the 'split' operation.
-- The types of the operations enforce the constraint @'Measured' v a@,
-- which also implies that the type @v@ is determined by @a@.
--
-- A variety of abstract data types can be implemented by using different
-- element types and measurements.
data FingerTree v a
    = Empty
    | Single a
    | Deep !v !(Digit a) (FingerTree v (Node v a)) !(Digit a)
#if TESTING
    deriving (Show
#if __GLASGOW_HASKELL__ >= 706
        , Generic
#endif
        )
#elif __GLASGOW_HASKELL__ >= 706
    deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v a x. Rep (FingerTree v a) x -> FingerTree v a
forall v a x. FingerTree v a -> Rep (FingerTree v a) x
$cto :: forall v a x. Rep (FingerTree v a) x -> FingerTree v a
$cfrom :: forall v a x. FingerTree v a -> Rep (FingerTree v a) x
Generic)
#endif

deep ::  (Measured v a) =>
     Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep :: forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr FingerTree v (Node v a)
m Digit a
sf =
    forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep ((forall v a. Measured v a => a -> v
measure Digit a
pr forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m) forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure Digit a
sf) Digit a
pr FingerTree v (Node v a)
m Digit a
sf

-- | /O(1)/. The cached measure of a tree.
instance (Measured v a) => Measured v (FingerTree v a) where
    measure :: FingerTree v a -> v
measure FingerTree v a
Empty           =  forall a. Monoid a => a
mempty
    measure (Single a
x)      =  forall v a. Measured v a => a -> v
measure a
x
    measure (Deep v
v Digit a
_ FingerTree v (Node v a)
_ Digit a
_)  =  v
v

-- | Elements from left to right.
instance Foldable (FingerTree v) where
    foldMap :: forall m a. Monoid m => (a -> m) -> FingerTree v a -> m
foldMap a -> m
_ FingerTree v a
Empty = forall a. Monoid a => a
mempty
    foldMap a -> m
f (Single a
x) = a -> m
f a
x
    foldMap a -> m
f (Deep v
_ Digit a
pr FingerTree v (Node v a)
m Digit a
sf) =
        forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f Digit a
pr forall a. Monoid a => a -> a -> a
`mappend` forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f) FingerTree v (Node v a)
m forall a. Monoid a => a -> a -> a
`mappend` forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f Digit a
sf

#if MIN_VERSION_base(4,8,0)
    null :: forall a. FingerTree v a -> Bool
null FingerTree v a
Empty = Bool
True
    null FingerTree v a
_ = Bool
False
#endif

instance (Eq a) => Eq (FingerTree v a) where
    FingerTree v a
xs == :: FingerTree v a -> FingerTree v a -> Bool
== FingerTree v a
ys = forall (t :: * -> *) a. Foldable t => t a -> [a]
toList FingerTree v a
xs forall a. Eq a => a -> a -> Bool
== forall (t :: * -> *) a. Foldable t => t a -> [a]
toList FingerTree v a
ys

-- | Lexicographical order from left to right.
instance (Ord a) => Ord (FingerTree v a) where
    compare :: FingerTree v a -> FingerTree v a -> Ordering
compare FingerTree v a
xs FingerTree v a
ys = forall a. Ord a => a -> a -> Ordering
compare (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList FingerTree v a
xs) (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList FingerTree v a
ys)

#if !TESTING
instance (Show a) => Show (FingerTree v a) where
    showsPrec :: Int -> FingerTree v a -> ShowS
showsPrec Int
p FingerTree v a
xs = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$
        String -> ShowS
showString String
"fromList " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> ShowS
shows (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList FingerTree v a
xs)
#endif

-- | Like 'fmap', but with constraints on the element types.
fmap' :: (Measured v1 a1, Measured v2 a2) =>
    (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmap' :: forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmap' = forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
mapTree

mapTree :: (Measured v2 a2) =>
    (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
mapTree :: forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
mapTree a1 -> a2
_ FingerTree v1 a1
Empty = forall v a. FingerTree v a
Empty
mapTree a1 -> a2
f (Single a1
x) = forall v a. a -> FingerTree v a
Single (a1 -> a2
f a1
x)
mapTree a1 -> a2
f (Deep v1
_ Digit a1
pr FingerTree v1 (Node v1 a1)
m Digit a1
sf) =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (forall a b. (a -> b) -> Digit a -> Digit b
mapDigit a1 -> a2
f Digit a1
pr) (forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
mapTree (forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> Node v1 a1 -> Node v2 a2
mapNode a1 -> a2
f) FingerTree v1 (Node v1 a1)
m) (forall a b. (a -> b) -> Digit a -> Digit b
mapDigit a1 -> a2
f Digit a1
sf)

mapNode :: (Measured v2 a2) =>
    (a1 -> a2) -> Node v1 a1 -> Node v2 a2
mapNode :: forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> Node v1 a1 -> Node v2 a2
mapNode a1 -> a2
f (Node2 v1
_ a1
a a1
b) = forall v a. Measured v a => a -> a -> Node v a
node2 (a1 -> a2
f a1
a) (a1 -> a2
f a1
b)
mapNode a1 -> a2
f (Node3 v1
_ a1
a a1
b a1
c) = forall v a. Measured v a => a -> a -> a -> Node v a
node3 (a1 -> a2
f a1
a) (a1 -> a2
f a1
b) (a1 -> a2
f a1
c)

mapDigit :: (a -> b) -> Digit a -> Digit b
mapDigit :: forall a b. (a -> b) -> Digit a -> Digit b
mapDigit a -> b
f (One a
a) = forall a. a -> Digit a
One (a -> b
f a
a)
mapDigit a -> b
f (Two a
a a
b) = forall a. a -> a -> Digit a
Two (a -> b
f a
a) (a -> b
f a
b)
mapDigit a -> b
f (Three a
a a
b a
c) = forall a. a -> a -> a -> Digit a
Three (a -> b
f a
a) (a -> b
f a
b) (a -> b
f a
c)
mapDigit a -> b
f (Four a
a a
b a
c a
d) = forall a. a -> a -> a -> a -> Digit a
Four (a -> b
f a
a) (a -> b
f a
b) (a -> b
f a
c) (a -> b
f a
d)

-- | Map all elements of the tree with a function that also takes the
-- measure of the prefix of the tree to the left of the element.
fmapWithPos :: (Measured v1 a1, Measured v2 a2) =>
    (v1 -> a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmapWithPos :: forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmapWithPos v1 -> a1 -> a2
f = forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> a2) -> v1 -> FingerTree v1 a1 -> FingerTree v2 a2
mapWPTree v1 -> a1 -> a2
f forall a. Monoid a => a
mempty

mapWPTree :: (Measured v1 a1, Measured v2 a2) =>
    (v1 -> a1 -> a2) -> v1 -> FingerTree v1 a1 -> FingerTree v2 a2
mapWPTree :: forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> a2) -> v1 -> FingerTree v1 a1 -> FingerTree v2 a2
mapWPTree v1 -> a1 -> a2
_ v1
_ FingerTree v1 a1
Empty = forall v a. FingerTree v a
Empty
mapWPTree v1 -> a1 -> a2
f v1
vl (Single a1
x) = forall v a. a -> FingerTree v a
Single (v1 -> a1 -> a2
f v1
vl a1
x)
mapWPTree v1 -> a1 -> a2
f v1
vl (Deep v1
_ Digit a1
pr FingerTree v1 (Node v1 a1)
m Digit a1
sf) =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (forall v a b.
Measured v a =>
(v -> a -> b) -> v -> Digit a -> Digit b
mapWPDigit v1 -> a1 -> a2
f v1
vl Digit a1
pr)
         (forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> a2) -> v1 -> FingerTree v1 a1 -> FingerTree v2 a2
mapWPTree (forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> a2) -> v1 -> Node v1 a1 -> Node v2 a2
mapWPNode v1 -> a1 -> a2
f) v1
vlp FingerTree v1 (Node v1 a1)
m)
         (forall v a b.
Measured v a =>
(v -> a -> b) -> v -> Digit a -> Digit b
mapWPDigit v1 -> a1 -> a2
f v1
vlpm Digit a1
sf)
  where
    vlp :: v1
vlp     =  v1
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure Digit a1
pr
    vlpm :: v1
vlpm    =  v1
vlp forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure FingerTree v1 (Node v1 a1)
m

mapWPNode :: (Measured v1 a1, Measured v2 a2) =>
    (v1 -> a1 -> a2) -> v1 -> Node v1 a1 -> Node v2 a2
mapWPNode :: forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> a2) -> v1 -> Node v1 a1 -> Node v2 a2
mapWPNode v1 -> a1 -> a2
f v1
vl (Node2 v1
_ a1
a a1
b) = forall v a. Measured v a => a -> a -> Node v a
node2 (v1 -> a1 -> a2
f v1
vl a1
a) (v1 -> a1 -> a2
f v1
vla a1
b)
  where
    vla :: v1
vla     =  v1
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
a
mapWPNode v1 -> a1 -> a2
f v1
vl (Node3 v1
_ a1
a a1
b a1
c) = forall v a. Measured v a => a -> a -> a -> Node v a
node3 (v1 -> a1 -> a2
f v1
vl a1
a) (v1 -> a1 -> a2
f v1
vla a1
b) (v1 -> a1 -> a2
f v1
vlab a1
c)
  where
    va :: v1
va      =  v1
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
a
    vla :: v1
vla     =  v1
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
a
    vlab :: v1
vlab    =  v1
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
b

mapWPDigit :: (Measured v a) => (v -> a -> b) -> v -> Digit a -> Digit b
mapWPDigit :: forall v a b.
Measured v a =>
(v -> a -> b) -> v -> Digit a -> Digit b
mapWPDigit v -> a -> b
f v
vl (One a
a) = forall a. a -> Digit a
One (v -> a -> b
f v
vl a
a)
mapWPDigit v -> a -> b
f v
vl (Two a
a a
b) = forall a. a -> a -> Digit a
Two (v -> a -> b
f v
vl a
a) (v -> a -> b
f v
vla a
b)
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
mapWPDigit v -> a -> b
f v
vl (Three a
a a
b a
c) = forall a. a -> a -> a -> Digit a
Three (v -> a -> b
f v
vl a
a) (v -> a -> b
f v
vla a
b) (v -> a -> b
f v
vlab a
c)
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
mapWPDigit v -> a -> b
f v
vl (Four a
a a
b a
c a
d) = forall a. a -> a -> a -> a -> Digit a
Four (v -> a -> b
f v
vl a
a) (v -> a -> b
f v
vla a
b) (v -> a -> b
f v
vlab a
c) (v -> a -> b
f v
vlabc a
d)
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vlabc :: v
vlabc   =  v
vlab forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c

-- | Map all elements of the tree with a function that also takes the
-- measure of the prefix to the left and of the suffix to the right of
-- the element.
--
-- @since 0.1.2.0
fmapWithContext :: (Measured v1 a1, Measured v2 a2) =>
    (v1 -> a1 -> v1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmapWithContext :: forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmapWithContext v1 -> a1 -> v1 -> a2
f FingerTree v1 a1
t = forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2)
-> v1 -> FingerTree v1 a1 -> v1 -> FingerTree v2 a2
mapWCTree v1 -> a1 -> v1 -> a2
f forall a. Monoid a => a
mempty FingerTree v1 a1
t forall a. Monoid a => a
mempty

mapWCTree :: (Measured v1 a1, Measured v2 a2) =>
    (v1 -> a1 -> v1 -> a2) -> v1 -> FingerTree v1 a1 -> v1 -> FingerTree v2 a2
mapWCTree :: forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2)
-> v1 -> FingerTree v1 a1 -> v1 -> FingerTree v2 a2
mapWCTree v1 -> a1 -> v1 -> a2
_ v1
_ FingerTree v1 a1
Empty v1
_ = forall v a. FingerTree v a
Empty
mapWCTree v1 -> a1 -> v1 -> a2
f v1
vl (Single a1
x) v1
vr = forall v a. a -> FingerTree v a
Single (v1 -> a1 -> v1 -> a2
f v1
vl a1
x v1
vr)
mapWCTree v1 -> a1 -> v1 -> a2
f v1
vl (Deep v1
_ Digit a1
pr FingerTree v1 (Node v1 a1)
m Digit a1
sf) v1
vr =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (forall v a b.
Measured v a =>
(v -> a -> v -> b) -> v -> Digit a -> v -> Digit b
mapWCDigit v1 -> a1 -> v1 -> a2
f v1
vl Digit a1
pr v1
vmsr)
         (forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2)
-> v1 -> FingerTree v1 a1 -> v1 -> FingerTree v2 a2
mapWCTree (forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2) -> v1 -> Node v1 a1 -> v1 -> Node v2 a2
mapWCNode v1 -> a1 -> v1 -> a2
f) v1
vlp FingerTree v1 (Node v1 a1)
m v1
vsr)
         (forall v a b.
Measured v a =>
(v -> a -> v -> b) -> v -> Digit a -> v -> Digit b
mapWCDigit v1 -> a1 -> v1 -> a2
f v1
vlpm Digit a1
sf v1
vr)
  where
    vlp :: v1
vlp     =  v1
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure Digit a1
pr
    vlpm :: v1
vlpm    =  v1
vlp forall a. Monoid a => a -> a -> a
`mappend` v1
vm
    vmsr :: v1
vmsr    =  v1
vm forall a. Monoid a => a -> a -> a
`mappend` v1
vsr
    vsr :: v1
vsr     =  forall v a. Measured v a => a -> v
measure Digit a1
sf forall a. Monoid a => a -> a -> a
`mappend` v1
vr
    vm :: v1
vm      =  forall v a. Measured v a => a -> v
measure FingerTree v1 (Node v1 a1)
m

mapWCNode :: (Measured v1 a1, Measured v2 a2) =>
    (v1 -> a1 -> v1 -> a2) -> v1 -> Node v1 a1 -> v1 -> Node v2 a2
mapWCNode :: forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2) -> v1 -> Node v1 a1 -> v1 -> Node v2 a2
mapWCNode v1 -> a1 -> v1 -> a2
f v1
vl (Node2 v1
_ a1
a a1
b) v1
vr = forall v a. Measured v a => a -> a -> Node v a
node2 (v1 -> a1 -> v1 -> a2
f v1
vl a1
a v1
vbr) (v1 -> a1 -> v1 -> a2
f v1
vla a1
b v1
vr)
  where
    vla :: v1
vla     =  v1
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
a
    vbr :: v1
vbr     =  forall v a. Measured v a => a -> v
measure a1
b forall a. Monoid a => a -> a -> a
`mappend` v1
vr
mapWCNode v1 -> a1 -> v1 -> a2
f v1
vl (Node3 v1
_ a1
a a1
b a1
c) v1
vr =
    forall v a. Measured v a => a -> a -> a -> Node v a
node3 (v1 -> a1 -> v1 -> a2
f v1
vl a1
a v1
vbcr) (v1 -> a1 -> v1 -> a2
f v1
vla a1
b v1
vcr) (v1 -> a1 -> v1 -> a2
f v1
vlab a1
c v1
vr)
  where
    vla :: v1
vla     =  v1
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
a
    vlab :: v1
vlab    =  v1
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
b
    vcr :: v1
vcr     =  forall v a. Measured v a => a -> v
measure a1
c forall a. Monoid a => a -> a -> a
`mappend` v1
vr
    vbcr :: v1
vbcr    =  forall v a. Measured v a => a -> v
measure a1
b forall a. Monoid a => a -> a -> a
`mappend` v1
vcr

mapWCDigit ::
    (Measured v a) => (v -> a -> v -> b) -> v -> Digit a -> v -> Digit b
mapWCDigit :: forall v a b.
Measured v a =>
(v -> a -> v -> b) -> v -> Digit a -> v -> Digit b
mapWCDigit v -> a -> v -> b
f v
vl (One a
a) v
vr = forall a. a -> Digit a
One (v -> a -> v -> b
f v
vl a
a v
vr)
mapWCDigit v -> a -> v -> b
f v
vl (Two a
a a
b) v
vr = forall a. a -> a -> Digit a
Two (v -> a -> v -> b
f v
vl a
a v
vbr) (v -> a -> v -> b
f v
vla a
b v
vr)
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vbr :: v
vbr     =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vr
mapWCDigit v -> a -> v -> b
f v
vl (Three a
a a
b a
c) v
vr =
    forall a. a -> a -> a -> Digit a
Three (v -> a -> v -> b
f v
vl a
a v
vbcr) (v -> a -> v -> b
f v
vla a
b v
vcr) (v -> a -> v -> b
f v
vlab a
c v
vr)
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vcr :: v
vcr     =  forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vbcr :: v
vbcr    =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcr
mapWCDigit v -> a -> v -> b
f v
vl (Four a
a a
b a
c a
d) v
vr =
    forall a. a -> a -> a -> a -> Digit a
Four (v -> a -> v -> b
f v
vl a
a v
vbcdr) (v -> a -> v -> b
f v
vla a
b v
vcdr) (v -> a -> v -> b
f v
vlab a
c v
vdr) (v -> a -> v -> b
f v
vlabc a
d v
vr)
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vlabc :: v
vlabc   =  v
vlab forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c
    vdr :: v
vdr     =  forall v a. Measured v a => a -> v
measure a
d forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vcdr :: v
vcdr    =  forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vdr
    vbcdr :: v
vbcdr   =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcdr

-- | Like 'fmap', but safe only if the function preserves the measure.
unsafeFmap :: (a -> b) -> FingerTree v a -> FingerTree v b
unsafeFmap :: forall a b v. (a -> b) -> FingerTree v a -> FingerTree v b
unsafeFmap a -> b
_ FingerTree v a
Empty = forall v a. FingerTree v a
Empty
unsafeFmap a -> b
f (Single a
x) = forall v a. a -> FingerTree v a
Single (a -> b
f a
x)
unsafeFmap a -> b
f (Deep v
v Digit a
pr FingerTree v (Node v a)
m Digit a
sf) =
    forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep v
v (forall a b. (a -> b) -> Digit a -> Digit b
mapDigit a -> b
f Digit a
pr) (forall a b v. (a -> b) -> FingerTree v a -> FingerTree v b
unsafeFmap (forall a b v. (a -> b) -> Node v a -> Node v b
unsafeFmapNode a -> b
f) FingerTree v (Node v a)
m) (forall a b. (a -> b) -> Digit a -> Digit b
mapDigit a -> b
f Digit a
sf)

unsafeFmapNode :: (a -> b) -> Node v a -> Node v b
unsafeFmapNode :: forall a b v. (a -> b) -> Node v a -> Node v b
unsafeFmapNode a -> b
f (Node2 v
v a
a a
b) = forall v a. v -> a -> a -> Node v a
Node2 v
v (a -> b
f a
a) (a -> b
f a
b)
unsafeFmapNode a -> b
f (Node3 v
v a
a a
b a
c) = forall v a. v -> a -> a -> a -> Node v a
Node3 v
v (a -> b
f a
a) (a -> b
f a
b) (a -> b
f a
c)

-- | Fold the tree from the left with a function that also takes the
-- measure of the prefix to the left of the element.
--
-- @since 0.1.5.0
foldlWithPos :: (Measured v a) =>
    (b -> v -> a -> b) -> b -> FingerTree v a -> b
foldlWithPos :: forall v a b.
Measured v a =>
(b -> v -> a -> b) -> b -> FingerTree v a -> b
foldlWithPos b -> v -> a -> b
f b
z = forall v a b.
Measured v a =>
(b -> v -> a -> b) -> b -> v -> FingerTree v a -> b
foldlWPTree b -> v -> a -> b
f b
z forall a. Monoid a => a
mempty

foldlWPTree :: (Measured v a) =>
    (b -> v -> a -> b) -> b -> v -> FingerTree v a -> b
foldlWPTree :: forall v a b.
Measured v a =>
(b -> v -> a -> b) -> b -> v -> FingerTree v a -> b
foldlWPTree b -> v -> a -> b
_ b
z v
_ FingerTree v a
Empty = b
z
foldlWPTree b -> v -> a -> b
f b
z v
vl (Single a
x) = b -> v -> a -> b
f b
z v
vl a
x
foldlWPTree b -> v -> a -> b
f b
z v
vl (Deep v
_ Digit a
pr FingerTree v (Node v a)
m Digit a
sf) = b
zpms
  where
    vlp :: v
vlp     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure Digit a
pr
    vlpm :: v
vlpm    =  v
vlp forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m
    zp :: b
zp      =  forall v a b.
Measured v a =>
(b -> v -> a -> b) -> b -> v -> Digit a -> b
foldlWPDigit b -> v -> a -> b
f b
z v
vl Digit a
pr
    zpm :: b
zpm     =  forall v a b.
Measured v a =>
(b -> v -> a -> b) -> b -> v -> FingerTree v a -> b
foldlWPTree (forall v a b.
Measured v a =>
(b -> v -> a -> b) -> b -> v -> Node v a -> b
foldlWPNode b -> v -> a -> b
f) b
zp v
vlp FingerTree v (Node v a)
m
    zpms :: b
zpms    =  forall v a b.
Measured v a =>
(b -> v -> a -> b) -> b -> v -> Digit a -> b
foldlWPDigit b -> v -> a -> b
f b
zpm v
vlpm Digit a
sf

foldlWPNode :: (Measured v a) =>
    (b -> v -> a -> b) -> b -> v -> Node v a -> b
foldlWPNode :: forall v a b.
Measured v a =>
(b -> v -> a -> b) -> b -> v -> Node v a -> b
foldlWPNode b -> v -> a -> b
f b
z v
vl (Node2 v
_ a
a a
b) = b -> v -> a -> b
f (b -> v -> a -> b
f b
z v
vl a
a) v
vla a
b
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
foldlWPNode b -> v -> a -> b
f b
z v
vl (Node3 v
_ a
a a
b a
c) = b -> v -> a -> b
f (b -> v -> a -> b
f (b -> v -> a -> b
f b
z v
vl a
a) v
vla a
b) v
vlab a
c
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b

foldlWPDigit :: (Measured v a) =>
    (b -> v -> a -> b) -> b -> v -> Digit a -> b
foldlWPDigit :: forall v a b.
Measured v a =>
(b -> v -> a -> b) -> b -> v -> Digit a -> b
foldlWPDigit b -> v -> a -> b
f b
z v
vl (One a
a) = b -> v -> a -> b
f b
z v
vl a
a
foldlWPDigit b -> v -> a -> b
f b
z v
vl (Two a
a a
b) = b -> v -> a -> b
f (b -> v -> a -> b
f b
z v
vl a
a) v
vla a
b
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
foldlWPDigit b -> v -> a -> b
f b
z v
vl (Three a
a a
b a
c) = b -> v -> a -> b
f (b -> v -> a -> b
f (b -> v -> a -> b
f b
z v
vl a
a) v
vla a
b) v
vlab a
c
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
foldlWPDigit b -> v -> a -> b
f b
z v
vl (Four a
a a
b a
c a
d) = b -> v -> a -> b
f (b -> v -> a -> b
f (b -> v -> a -> b
f (b -> v -> a -> b
f b
z v
vl a
a) v
vla a
b) v
vlab a
c) v
vlabc a
d
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vlabc :: v
vlabc   =  v
vlab forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c

-- | Fold the tree from the right with a function that also takes the
-- measure of the prefix to the left of the element.
--
-- @since 0.1.5.0
foldrWithPos :: (Measured v a) =>
    (v -> a -> b -> b) -> b -> FingerTree v a -> b
foldrWithPos :: forall v a b.
Measured v a =>
(v -> a -> b -> b) -> b -> FingerTree v a -> b
foldrWithPos v -> a -> b -> b
f b
z = forall v a b.
Measured v a =>
(v -> a -> b -> b) -> b -> v -> FingerTree v a -> b
foldrWPTree v -> a -> b -> b
f b
z forall a. Monoid a => a
mempty

foldrWPTree :: (Measured v a) =>
    (v -> a -> b -> b) -> b -> v -> FingerTree v a -> b
foldrWPTree :: forall v a b.
Measured v a =>
(v -> a -> b -> b) -> b -> v -> FingerTree v a -> b
foldrWPTree v -> a -> b -> b
_ b
z v
_ FingerTree v a
Empty = b
z
foldrWPTree v -> a -> b -> b
f b
z v
vl (Single a
x) = v -> a -> b -> b
f v
vl a
x b
z
foldrWPTree v -> a -> b -> b
f b
z v
vl (Deep v
_ Digit a
pr FingerTree v (Node v a)
m Digit a
sf) = b
zpms
  where
    vlp :: v
vlp     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure Digit a
pr
    vlpm :: v
vlpm    =  v
vlp forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m
    zpms :: b
zpms    =  forall v a b.
Measured v a =>
(v -> a -> b -> b) -> b -> v -> Digit a -> b
foldrWPDigit v -> a -> b -> b
f b
zms v
vl Digit a
pr
    zms :: b
zms     =  forall v a b.
Measured v a =>
(v -> a -> b -> b) -> b -> v -> FingerTree v a -> b
foldrWPTree (forall v a b.
Measured v a =>
(v -> a -> b -> b) -> v -> Node v a -> b -> b
foldrWPNode v -> a -> b -> b
f) b
zs v
vlp FingerTree v (Node v a)
m
    zs :: b
zs      =  forall v a b.
Measured v a =>
(v -> a -> b -> b) -> b -> v -> Digit a -> b
foldrWPDigit v -> a -> b -> b
f b
z v
vlpm Digit a
sf

-- different argument order for convenience
foldrWPNode :: (Measured v a) =>
    (v -> a -> b -> b) -> v -> Node v a -> b -> b
foldrWPNode :: forall v a b.
Measured v a =>
(v -> a -> b -> b) -> v -> Node v a -> b -> b
foldrWPNode v -> a -> b -> b
f v
vl (Node2 v
_ a
a a
b) b
z = v -> a -> b -> b
f v
vl a
a (v -> a -> b -> b
f v
vla a
b b
z)
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
foldrWPNode v -> a -> b -> b
f v
vl (Node3 v
_ a
a a
b a
c) b
z = v -> a -> b -> b
f v
vl a
a (v -> a -> b -> b
f v
vla a
b (v -> a -> b -> b
f v
vlab a
c b
z))
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b

foldrWPDigit :: (Measured v a) =>
    (v -> a -> b -> b) -> b -> v -> Digit a -> b
foldrWPDigit :: forall v a b.
Measured v a =>
(v -> a -> b -> b) -> b -> v -> Digit a -> b
foldrWPDigit v -> a -> b -> b
f b
z v
vl (One a
a) = v -> a -> b -> b
f v
vl a
a b
z
foldrWPDigit v -> a -> b -> b
f b
z v
vl (Two a
a a
b) = v -> a -> b -> b
f v
vl a
a (v -> a -> b -> b
f v
vla a
b b
z)
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
foldrWPDigit v -> a -> b -> b
f b
z v
vl (Three a
a a
b a
c) = v -> a -> b -> b
f v
vl a
a (v -> a -> b -> b
f v
vla a
b (v -> a -> b -> b
f v
vlab a
c b
z))
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
foldrWPDigit v -> a -> b -> b
f b
z v
vl (Four a
a a
b a
c a
d) = v -> a -> b -> b
f v
vl a
a (v -> a -> b -> b
f v
vla a
b (v -> a -> b -> b
f v
vlab a
c (v -> a -> b -> b
f v
vlabc a
d b
z)))
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vlabc :: v
vlabc   =  v
vlab forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c

-- | Fold the tree from the left with a function that also takes the
-- measure of the prefix to the left of the element and the measure of
-- the suffix to the right of the element.
--
-- @since 0.1.5.0
foldlWithContext :: (Measured v a) =>
    (b -> v -> a -> v -> b) -> b -> FingerTree v a -> b
foldlWithContext :: forall v a b.
Measured v a =>
(b -> v -> a -> v -> b) -> b -> FingerTree v a -> b
foldlWithContext b -> v -> a -> v -> b
f b
z FingerTree v a
t = forall v a b.
Measured v a =>
(b -> v -> a -> v -> b) -> b -> v -> FingerTree v a -> v -> b
foldlWCTree b -> v -> a -> v -> b
f b
z forall a. Monoid a => a
mempty FingerTree v a
t forall a. Monoid a => a
mempty

foldlWCTree :: (Measured v a) =>
    (b -> v -> a -> v -> b) -> b -> v -> FingerTree v a -> v -> b
foldlWCTree :: forall v a b.
Measured v a =>
(b -> v -> a -> v -> b) -> b -> v -> FingerTree v a -> v -> b
foldlWCTree b -> v -> a -> v -> b
_ b
z v
_ FingerTree v a
Empty v
_ = b
z
foldlWCTree b -> v -> a -> v -> b
f b
z v
vl (Single a
x) v
vr = b -> v -> a -> v -> b
f b
z v
vl a
x v
vr
foldlWCTree b -> v -> a -> v -> b
f b
z v
vl (Deep v
_ Digit a
pr FingerTree v (Node v a)
m Digit a
sf) v
vr = b
zpms
  where
    vlp :: v
vlp     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure Digit a
pr
    vlpm :: v
vlpm    =  v
vlp forall a. Monoid a => a -> a -> a
`mappend` v
vm
    vmsr :: v
vmsr    =  v
vm forall a. Monoid a => a -> a -> a
`mappend` v
vsr
    vsr :: v
vsr     =  forall v a. Measured v a => a -> v
measure Digit a
sf forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vm :: v
vm      =  forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m
    zp :: b
zp      =  forall v a b.
Measured v a =>
(b -> v -> a -> v -> b) -> b -> v -> Digit a -> v -> b
foldlWCDigit b -> v -> a -> v -> b
f b
z v
vl Digit a
pr v
vmsr
    zpm :: b
zpm     =  forall v a b.
Measured v a =>
(b -> v -> a -> v -> b) -> b -> v -> FingerTree v a -> v -> b
foldlWCTree (forall v a b.
Measured v a =>
(b -> v -> a -> v -> b) -> b -> v -> Node v a -> v -> b
foldlWCNode b -> v -> a -> v -> b
f) b
zp v
vlp FingerTree v (Node v a)
m v
vsr
    zpms :: b
zpms    =  forall v a b.
Measured v a =>
(b -> v -> a -> v -> b) -> b -> v -> Digit a -> v -> b
foldlWCDigit b -> v -> a -> v -> b
f b
zpm v
vlpm Digit a
sf v
vr

foldlWCNode :: (Measured v a) =>
    (b -> v -> a -> v -> b) -> b -> v -> Node v a -> v -> b
foldlWCNode :: forall v a b.
Measured v a =>
(b -> v -> a -> v -> b) -> b -> v -> Node v a -> v -> b
foldlWCNode b -> v -> a -> v -> b
f b
z v
vl (Node2 v
_ a
a a
b) v
vr = b -> v -> a -> v -> b
f (b -> v -> a -> v -> b
f b
z v
vl a
a v
vbr) v
vla a
b v
vr
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vbr :: v
vbr     =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vr
foldlWCNode b -> v -> a -> v -> b
f b
z v
vl (Node3 v
_ a
a a
b a
c) v
vr =
    b -> v -> a -> v -> b
f (b -> v -> a -> v -> b
f (b -> v -> a -> v -> b
f b
z v
vl a
a v
vbcr) v
vla a
b v
vcr) v
vlab a
c v
vr
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vcr :: v
vcr     =  forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vbcr :: v
vbcr    =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcr

foldlWCDigit :: (Measured v a) =>
    (b -> v -> a -> v -> b) -> b -> v -> Digit a -> v -> b
foldlWCDigit :: forall v a b.
Measured v a =>
(b -> v -> a -> v -> b) -> b -> v -> Digit a -> v -> b
foldlWCDigit b -> v -> a -> v -> b
f b
z v
vl (One a
a) v
vr = b -> v -> a -> v -> b
f b
z v
vl a
a v
vr
foldlWCDigit b -> v -> a -> v -> b
f b
z v
vl (Two a
a a
b) v
vr = b -> v -> a -> v -> b
f (b -> v -> a -> v -> b
f b
z v
vl a
a v
vbr) v
vla a
b v
vr
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vbr :: v
vbr     =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vr
foldlWCDigit b -> v -> a -> v -> b
f b
z v
vl (Three a
a a
b a
c) v
vr =
    b -> v -> a -> v -> b
f (b -> v -> a -> v -> b
f (b -> v -> a -> v -> b
f b
z v
vl a
a v
vbcr) v
vla a
b v
vcr) v
vlab a
c v
vr
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vcr :: v
vcr     =  forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vbcr :: v
vbcr    =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcr
foldlWCDigit b -> v -> a -> v -> b
f b
z v
vl (Four a
a a
b a
c a
d) v
vr =
    b -> v -> a -> v -> b
f (b -> v -> a -> v -> b
f (b -> v -> a -> v -> b
f (b -> v -> a -> v -> b
f b
z v
vl a
a v
vbcdr) v
vla a
b v
vcdr) v
vlab a
c v
vdr) v
vlabc a
d v
vr
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vlabc :: v
vlabc   =  v
vlab forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c
    vdr :: v
vdr     =  forall v a. Measured v a => a -> v
measure a
d forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vcdr :: v
vcdr    =  forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vdr
    vbcdr :: v
vbcdr   =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcdr

-- | Fold the tree from the right with a function that also takes the
-- measure of the prefix to the left of the element and the measure of
-- the suffix to the right of the element.
--
-- @since 0.1.5.0
foldrWithContext :: (Measured v a) =>
    (v -> a -> v -> b -> b) -> b -> FingerTree v a -> b
foldrWithContext :: forall v a b.
Measured v a =>
(v -> a -> v -> b -> b) -> b -> FingerTree v a -> b
foldrWithContext v -> a -> v -> b -> b
f b
z FingerTree v a
t = forall v a b.
Measured v a =>
(v -> a -> v -> b -> b) -> b -> v -> FingerTree v a -> v -> b
foldrWCTree v -> a -> v -> b -> b
f b
z forall a. Monoid a => a
mempty FingerTree v a
t forall a. Monoid a => a
mempty

foldrWCTree :: (Measured v a) =>
    (v -> a -> v -> b -> b) -> b -> v -> FingerTree v a -> v -> b
foldrWCTree :: forall v a b.
Measured v a =>
(v -> a -> v -> b -> b) -> b -> v -> FingerTree v a -> v -> b
foldrWCTree v -> a -> v -> b -> b
_ b
z v
_ FingerTree v a
Empty v
_ = b
z
foldrWCTree v -> a -> v -> b -> b
f b
z v
vl (Single a
x) v
vr = v -> a -> v -> b -> b
f v
vl a
x v
vr b
z
foldrWCTree v -> a -> v -> b -> b
f b
z v
vl (Deep v
_ Digit a
pr FingerTree v (Node v a)
m Digit a
sf) v
vr = b
zpms
  where
    vlp :: v
vlp     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure Digit a
pr
    vlpm :: v
vlpm    =  v
vlp forall a. Monoid a => a -> a -> a
`mappend` v
vm
    vmsr :: v
vmsr    =  v
vm forall a. Monoid a => a -> a -> a
`mappend` v
vsr
    vsr :: v
vsr     =  forall v a. Measured v a => a -> v
measure Digit a
sf forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vm :: v
vm      =  forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m
    zpms :: b
zpms    =  forall v a b.
Measured v a =>
(v -> a -> v -> b -> b) -> b -> v -> Digit a -> v -> b
foldrWCDigit v -> a -> v -> b -> b
f b
zms v
vl Digit a
pr v
vmsr
    zms :: b
zms     =  forall v a b.
Measured v a =>
(v -> a -> v -> b -> b) -> b -> v -> FingerTree v a -> v -> b
foldrWCTree (forall v a b.
Measured v a =>
(v -> a -> v -> b -> b) -> v -> Node v a -> v -> b -> b
foldrWCNode v -> a -> v -> b -> b
f) b
zs v
vlp FingerTree v (Node v a)
m v
vsr
    zs :: b
zs      =  forall v a b.
Measured v a =>
(v -> a -> v -> b -> b) -> b -> v -> Digit a -> v -> b
foldrWCDigit v -> a -> v -> b -> b
f b
z v
vlpm Digit a
sf v
vr

-- different argument order for convenience
foldrWCNode :: (Measured v a) =>
    (v -> a -> v -> b -> b) -> v -> Node v a -> v -> b -> b
foldrWCNode :: forall v a b.
Measured v a =>
(v -> a -> v -> b -> b) -> v -> Node v a -> v -> b -> b
foldrWCNode v -> a -> v -> b -> b
f v
vl (Node2 v
_ a
a a
b) v
vr b
z = v -> a -> v -> b -> b
f v
vl a
a v
vbr (v -> a -> v -> b -> b
f v
vla a
b v
vr b
z)
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vbr :: v
vbr     =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vr
foldrWCNode v -> a -> v -> b -> b
f v
vl (Node3 v
_ a
a a
b a
c) v
vr b
z =
    v -> a -> v -> b -> b
f v
vl a
a v
vbcr (v -> a -> v -> b -> b
f v
vla a
b v
vcr (v -> a -> v -> b -> b
f v
vlab a
c v
vr b
z))
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vcr :: v
vcr     =  forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vbcr :: v
vbcr    =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcr

foldrWCDigit :: (Measured v a) =>
    (v -> a -> v -> b -> b) -> b -> v -> Digit a -> v -> b
foldrWCDigit :: forall v a b.
Measured v a =>
(v -> a -> v -> b -> b) -> b -> v -> Digit a -> v -> b
foldrWCDigit v -> a -> v -> b -> b
f b
z v
vl (One a
a) v
vr = v -> a -> v -> b -> b
f v
vl a
a v
vr b
z
foldrWCDigit v -> a -> v -> b -> b
f b
z v
vl (Two a
a a
b) v
vr = v -> a -> v -> b -> b
f v
vl a
a v
vbr (v -> a -> v -> b -> b
f v
vla a
b v
vr b
z)
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vbr :: v
vbr     =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vr
foldrWCDigit v -> a -> v -> b -> b
f b
z v
vl (Three a
a a
b a
c) v
vr =
    v -> a -> v -> b -> b
f v
vl a
a v
vbcr (v -> a -> v -> b -> b
f v
vla a
b v
vcr (v -> a -> v -> b -> b
f v
vlab a
c v
vr b
z))
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vcr :: v
vcr     =  forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vbcr :: v
vbcr    =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcr
foldrWCDigit v -> a -> v -> b -> b
f b
z v
vl (Four a
a a
b a
c a
d) v
vr =
    v -> a -> v -> b -> b
f v
vl a
a v
vbcdr (v -> a -> v -> b -> b
f v
vla a
b v
vcdr (v -> a -> v -> b -> b
f v
vlab a
c v
vdr (v -> a -> v -> b -> b
f v
vlabc a
d v
vr b
z)))
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vlabc :: v
vlabc   =  v
vlab forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c
    vdr :: v
vdr     =  forall v a. Measured v a => a -> v
measure a
d forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vcdr :: v
vcdr    =  forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vdr
    vbcdr :: v
vbcdr   =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcdr

-- | Like 'traverse', but with constraints on the element types.
traverse' :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
    (a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverse' :: forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverse' = forall v2 a2 (f :: * -> *) a1 v1.
(Measured v2 a2, Applicative f) =>
(a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseTree

traverseTree :: (Measured v2 a2, Applicative f) =>
    (a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseTree :: forall v2 a2 (f :: * -> *) a1 v1.
(Measured v2 a2, Applicative f) =>
(a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseTree a1 -> f a2
_ FingerTree v1 a1
Empty = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall v a. FingerTree v a
Empty
traverseTree a1 -> f a2
f (Single a1
x) = forall v a. a -> FingerTree v a
Single forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a1 -> f a2
f a1
x
traverseTree a1 -> f a2
f (Deep v1
_ Digit a1
pr FingerTree v1 (Node v1 a1)
m Digit a1
sf) =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Digit a -> f (Digit b)
traverseDigit a1 -> f a2
f Digit a1
pr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall v2 a2 (f :: * -> *) a1 v1.
(Measured v2 a2, Applicative f) =>
(a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseTree (forall v2 a2 (f :: * -> *) a1 v1.
(Measured v2 a2, Applicative f) =>
(a1 -> f a2) -> Node v1 a1 -> f (Node v2 a2)
traverseNode a1 -> f a2
f) FingerTree v1 (Node v1 a1)
m forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Digit a -> f (Digit b)
traverseDigit a1 -> f a2
f Digit a1
sf

traverseNode :: (Measured v2 a2, Applicative f) =>
    (a1 -> f a2) -> Node v1 a1 -> f (Node v2 a2)
traverseNode :: forall v2 a2 (f :: * -> *) a1 v1.
(Measured v2 a2, Applicative f) =>
(a1 -> f a2) -> Node v1 a1 -> f (Node v2 a2)
traverseNode a1 -> f a2
f (Node2 v1
_ a1
a a1
b) = forall v a. Measured v a => a -> a -> Node v a
node2 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a1 -> f a2
f a1
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a1 -> f a2
f a1
b
traverseNode a1 -> f a2
f (Node3 v1
_ a1
a a1
b a1
c) = forall v a. Measured v a => a -> a -> a -> Node v a
node3 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a1 -> f a2
f a1
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a1 -> f a2
f a1
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a1 -> f a2
f a1
c

traverseDigit :: (Applicative f) => (a -> f b) -> Digit a -> f (Digit b)
traverseDigit :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Digit a -> f (Digit b)
traverseDigit a -> f b
f (One a
a) = forall a. a -> Digit a
One forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a
traverseDigit a -> f b
f (Two a
a a
b) = forall a. a -> a -> Digit a
Two forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
b
traverseDigit a -> f b
f (Three a
a a
b a
c) = forall a. a -> a -> a -> Digit a
Three forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
c
traverseDigit a -> f b
f (Four a
a a
b a
c a
d) = forall a. a -> a -> a -> a -> Digit a
Four forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
c forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
d

-- | Traverse the tree from left to right with a function that also
-- takes the measure of the prefix of the tree to the left of the element.
traverseWithPos :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
    (v1 -> a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWithPos :: forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWithPos v1 -> a1 -> f a2
f = forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> f a2)
-> v1 -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWPTree v1 -> a1 -> f a2
f forall a. Monoid a => a
mempty

traverseWPTree :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
    (v1 -> a1 -> f a2) -> v1 -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWPTree :: forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> f a2)
-> v1 -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWPTree v1 -> a1 -> f a2
_ v1
_ FingerTree v1 a1
Empty = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall v a. FingerTree v a
Empty
traverseWPTree v1 -> a1 -> f a2
f v1
v (Single a1
x) = forall v a. a -> FingerTree v a
Single forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v1 -> a1 -> f a2
f v1
v a1
x
traverseWPTree v1 -> a1 -> f a2
f v1
v (Deep v1
_ Digit a1
pr FingerTree v1 (Node v1 a1)
m Digit a1
sf) =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall v a (f :: * -> *) b.
(Measured v a, Applicative f) =>
(v -> a -> f b) -> v -> Digit a -> f (Digit b)
traverseWPDigit v1 -> a1 -> f a2
f v1
v Digit a1
pr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> f a2)
-> v1 -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWPTree (forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> f a2) -> v1 -> Node v1 a1 -> f (Node v2 a2)
traverseWPNode v1 -> a1 -> f a2
f) v1
vpr FingerTree v1 (Node v1 a1)
m forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall v a (f :: * -> *) b.
(Measured v a, Applicative f) =>
(v -> a -> f b) -> v -> Digit a -> f (Digit b)
traverseWPDigit v1 -> a1 -> f a2
f v1
vm Digit a1
sf
  where
    vpr :: v1
vpr     =  v1
v    forall a. Monoid a => a -> a -> a
`mappend`  forall v a. Measured v a => a -> v
measure Digit a1
pr
    vm :: v1
vm      =  v1
vpr  forall a. Monoid a => a -> a -> a
`mappend`  forall v a. Measured v a => a -> v
measure FingerTree v1 (Node v1 a1)
m

traverseWPNode :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
    (v1 -> a1 -> f a2) -> v1 -> Node v1 a1 -> f (Node v2 a2)
traverseWPNode :: forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> f a2) -> v1 -> Node v1 a1 -> f (Node v2 a2)
traverseWPNode v1 -> a1 -> f a2
f v1
v (Node2 v1
_ a1
a a1
b) = forall v a. Measured v a => a -> a -> Node v a
node2 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v1 -> a1 -> f a2
f v1
v a1
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v1 -> a1 -> f a2
f v1
va a1
b
  where
    va :: v1
va      = v1
v forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
a
traverseWPNode v1 -> a1 -> f a2
f v1
v (Node3 v1
_ a1
a a1
b a1
c) = forall v a. Measured v a => a -> a -> a -> Node v a
node3 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v1 -> a1 -> f a2
f v1
v a1
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v1 -> a1 -> f a2
f v1
va a1
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v1 -> a1 -> f a2
f v1
vab a1
c
  where
    va :: v1
va      = v1
v forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
a
    vab :: v1
vab     = v1
va forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
b

traverseWPDigit :: (Measured v a, Applicative f) =>
    (v -> a -> f b) -> v -> Digit a -> f (Digit b)
traverseWPDigit :: forall v a (f :: * -> *) b.
(Measured v a, Applicative f) =>
(v -> a -> f b) -> v -> Digit a -> f (Digit b)
traverseWPDigit v -> a -> f b
f v
v (One a
a) = forall a. a -> Digit a
One forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> f b
f v
v a
a
traverseWPDigit v -> a -> f b
f v
v (Two a
a a
b) = forall a. a -> a -> Digit a
Two forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> f b
f v
v a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> f b
f v
va a
b
  where
    va :: v
va      = v
v forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
traverseWPDigit v -> a -> f b
f v
v (Three a
a a
b a
c) = forall a. a -> a -> a -> Digit a
Three forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> f b
f v
v a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> f b
f v
va a
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> f b
f v
vab a
c
  where
    va :: v
va      = v
v forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vab :: v
vab     = v
va forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
traverseWPDigit v -> a -> f b
f v
v (Four a
a a
b a
c a
d) = forall a. a -> a -> a -> a -> Digit a
Four forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> f b
f v
v a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> f b
f v
va a
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> f b
f v
vab a
c forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> f b
f v
vabc a
d
  where
    va :: v
va      = v
v forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vab :: v
vab     = v
va forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vabc :: v
vabc    = v
vab forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c

-- | Traverse the tree from left to right with a function that also
-- takes the measure of the prefix to the left and the measure of the
-- suffix to the right of the element.
--
-- @since 0.1.2.0
traverseWithContext :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
    (v1 -> a1 -> v1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWithContext :: forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2)
-> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWithContext v1 -> a1 -> v1 -> f a2
f FingerTree v1 a1
t = forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2)
-> v1 -> FingerTree v1 a1 -> v1 -> f (FingerTree v2 a2)
traverseWCTree v1 -> a1 -> v1 -> f a2
f forall a. Monoid a => a
mempty FingerTree v1 a1
t forall a. Monoid a => a
mempty

traverseWCTree :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
    (v1 -> a1 -> v1 -> f a2) -> v1 -> FingerTree v1 a1 -> v1 -> f (FingerTree v2 a2)
traverseWCTree :: forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2)
-> v1 -> FingerTree v1 a1 -> v1 -> f (FingerTree v2 a2)
traverseWCTree v1 -> a1 -> v1 -> f a2
_ v1
_ FingerTree v1 a1
Empty v1
_ = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall v a. FingerTree v a
Empty
traverseWCTree v1 -> a1 -> v1 -> f a2
f v1
vl (Single a1
x) v1
vr = forall v a. a -> FingerTree v a
Single forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v1 -> a1 -> v1 -> f a2
f v1
vl a1
x v1
vr
traverseWCTree v1 -> a1 -> v1 -> f a2
f v1
vl (Deep v1
_ Digit a1
pr FingerTree v1 (Node v1 a1)
m Digit a1
sf) v1
vr =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall v a (f :: * -> *) b.
(Measured v a, Applicative f) =>
(v -> a -> v -> f b) -> v -> Digit a -> v -> f (Digit b)
traverseWCDigit v1 -> a1 -> v1 -> f a2
f v1
vl Digit a1
pr v1
vmsr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2)
-> v1 -> FingerTree v1 a1 -> v1 -> f (FingerTree v2 a2)
traverseWCTree (forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2)
-> v1 -> Node v1 a1 -> v1 -> f (Node v2 a2)
traverseWCNode v1 -> a1 -> v1 -> f a2
f) v1
vlp FingerTree v1 (Node v1 a1)
m v1
vsr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall v a (f :: * -> *) b.
(Measured v a, Applicative f) =>
(v -> a -> v -> f b) -> v -> Digit a -> v -> f (Digit b)
traverseWCDigit v1 -> a1 -> v1 -> f a2
f v1
vlpm Digit a1
sf v1
vr
  where
    vlp :: v1
vlp     =  v1
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure Digit a1
pr
    vlpm :: v1
vlpm    =  v1
vlp forall a. Monoid a => a -> a -> a
`mappend` v1
vm
    vmsr :: v1
vmsr    =  v1
vm forall a. Monoid a => a -> a -> a
`mappend` v1
vsr
    vsr :: v1
vsr     =  forall v a. Measured v a => a -> v
measure Digit a1
sf forall a. Monoid a => a -> a -> a
`mappend` v1
vr
    vm :: v1
vm      =  forall v a. Measured v a => a -> v
measure FingerTree v1 (Node v1 a1)
m

traverseWCNode :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
    (v1 -> a1 -> v1 -> f a2) -> v1 -> Node v1 a1 -> v1 -> f (Node v2 a2)
traverseWCNode :: forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2)
-> v1 -> Node v1 a1 -> v1 -> f (Node v2 a2)
traverseWCNode v1 -> a1 -> v1 -> f a2
f v1
vl (Node2 v1
_ a1
a a1
b) v1
vr = forall v a. Measured v a => a -> a -> Node v a
node2 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v1 -> a1 -> v1 -> f a2
f v1
vl a1
a v1
vbr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v1 -> a1 -> v1 -> f a2
f v1
vla a1
b v1
vr
  where
    vla :: v1
vla     =  v1
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
a
    vbr :: v1
vbr     =  forall v a. Measured v a => a -> v
measure a1
b forall a. Monoid a => a -> a -> a
`mappend` v1
vr
traverseWCNode v1 -> a1 -> v1 -> f a2
f v1
vl (Node3 v1
_ a1
a a1
b a1
c) v1
vr =
    forall v a. Measured v a => a -> a -> a -> Node v a
node3 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v1 -> a1 -> v1 -> f a2
f v1
vl a1
a v1
vbcr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v1 -> a1 -> v1 -> f a2
f v1
vla a1
b v1
vcr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v1 -> a1 -> v1 -> f a2
f v1
vlab a1
c v1
vr
  where
    vla :: v1
vla     =  v1
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
a
    vlab :: v1
vlab    =  v1
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a1
b
    vcr :: v1
vcr     =  forall v a. Measured v a => a -> v
measure a1
c forall a. Monoid a => a -> a -> a
`mappend` v1
vr
    vbcr :: v1
vbcr    =  forall v a. Measured v a => a -> v
measure a1
b forall a. Monoid a => a -> a -> a
`mappend` v1
vcr

traverseWCDigit :: (Measured v a, Applicative f) =>
    (v -> a -> v -> f b) -> v -> Digit a -> v -> f (Digit b)
traverseWCDigit :: forall v a (f :: * -> *) b.
(Measured v a, Applicative f) =>
(v -> a -> v -> f b) -> v -> Digit a -> v -> f (Digit b)
traverseWCDigit v -> a -> v -> f b
f v
vl (One a
a) v
vr = forall a. a -> Digit a
One forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> v -> f b
f v
vl a
a v
vr
traverseWCDigit v -> a -> v -> f b
f v
vl (Two a
a a
b) v
vr = forall a. a -> a -> Digit a
Two forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> v -> f b
f v
vl a
a v
vbr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> v -> f b
f v
vla a
b v
vr
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vbr :: v
vbr     =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vr
traverseWCDigit v -> a -> v -> f b
f v
vl (Three a
a a
b a
c) v
vr =
    forall a. a -> a -> a -> Digit a
Three forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> v -> f b
f v
vl a
a v
vbcr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> v -> f b
f v
vla a
b v
vcr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> v -> f b
f v
vlab a
c v
vr
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vcr :: v
vcr     =  forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vbcr :: v
vbcr    =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcr
traverseWCDigit v -> a -> v -> f b
f v
vl (Four a
a a
b a
c a
d) v
vr =
    forall a. a -> a -> a -> a -> Digit a
Four forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> v -> f b
f v
vl a
a v
vbcdr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> v -> f b
f v
vla a
b v
vcdr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> v -> f b
f v
vlab a
c v
vdr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> v -> f b
f v
vlabc a
d v
vr
  where
    vla :: v
vla     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vlab :: v
vlab    =  v
vla forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vlabc :: v
vlabc   =  v
vlab forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c
    vdr :: v
vdr     =  forall v a. Measured v a => a -> v
measure a
d forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vcdr :: v
vcdr    =  forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vdr
    vbcdr :: v
vbcdr   =  forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcdr

-- | Like 'traverse', but safe only if the function preserves the measure.
unsafeTraverse :: (Applicative f) =>
    (a -> f b) -> FingerTree v a -> f (FingerTree v b)
unsafeTraverse :: forall (f :: * -> *) a b v.
Applicative f =>
(a -> f b) -> FingerTree v a -> f (FingerTree v b)
unsafeTraverse a -> f b
_ FingerTree v a
Empty = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall v a. FingerTree v a
Empty
unsafeTraverse a -> f b
f (Single a
x) = forall v a. a -> FingerTree v a
Single forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x
unsafeTraverse a -> f b
f (Deep v
v Digit a
pr FingerTree v (Node v a)
m Digit a
sf) =
    forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep v
v forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Digit a -> f (Digit b)
traverseDigit a -> f b
f Digit a
pr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b v.
Applicative f =>
(a -> f b) -> FingerTree v a -> f (FingerTree v b)
unsafeTraverse (forall (f :: * -> *) a b v.
Applicative f =>
(a -> f b) -> Node v a -> f (Node v b)
unsafeTraverseNode a -> f b
f) FingerTree v (Node v a)
m forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Digit a -> f (Digit b)
traverseDigit a -> f b
f Digit a
sf

unsafeTraverseNode :: (Applicative f) =>
    (a -> f b) -> Node v a -> f (Node v b)
unsafeTraverseNode :: forall (f :: * -> *) a b v.
Applicative f =>
(a -> f b) -> Node v a -> f (Node v b)
unsafeTraverseNode a -> f b
f (Node2 v
v a
a a
b) = forall v a. v -> a -> a -> Node v a
Node2 v
v forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
b
unsafeTraverseNode a -> f b
f (Node3 v
v a
a a
b a
c) = forall v a. v -> a -> a -> a -> Node v a
Node3 v
v forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
c

-----------------------------------------------------
-- 4.3 Construction, deconstruction and concatenation
-----------------------------------------------------

-- | /O(1)/. The empty sequence.
empty :: Measured v a => FingerTree v a
empty :: forall v a. Measured v a => FingerTree v a
empty = forall v a. FingerTree v a
Empty

-- | /O(1)/. A singleton sequence.
singleton :: Measured v a => a -> FingerTree v a
singleton :: forall v a. Measured v a => a -> FingerTree v a
singleton = forall v a. a -> FingerTree v a
Single

-- | /O(n)/. Create a sequence from a finite list of elements.
-- The opposite operation 'toList' is supplied by the 'Foldable' instance.
fromList :: (Measured v a) => [a] -> FingerTree v a
fromList :: forall v a. Measured v a => [a] -> FingerTree v a
fromList = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
(<|) forall v a. FingerTree v a
Empty

-- | /O(1)/. Add an element to the left end of a sequence.
-- Mnemonic: a triangle with the single element at the pointy end.
(<|) :: (Measured v a) => a -> FingerTree v a -> FingerTree v a
a
a <| :: forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
Empty              =  forall v a. a -> FingerTree v a
Single a
a
a
a <| Single a
b           =  forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (forall a. a -> Digit a
One a
a) forall v a. FingerTree v a
Empty (forall a. a -> Digit a
One a
b)
a
a <| Deep v
v (Four a
b a
c a
d a
e) FingerTree v (Node v a)
m Digit a
sf = FingerTree v (Node v a)
m seq :: forall a b. a -> b -> b
`seq`
    forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (forall v a. Measured v a => a -> v
measure a
a forall a. Monoid a => a -> a -> a
`mappend` v
v) (forall a. a -> a -> Digit a
Two a
a a
b) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
c a
d a
e forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v (Node v a)
m) Digit a
sf
a
a <| Deep v
v Digit a
pr FingerTree v (Node v a)
m Digit a
sf     =
    forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (forall v a. Measured v a => a -> v
measure a
a forall a. Monoid a => a -> a -> a
`mappend` v
v) (forall a. a -> Digit a -> Digit a
consDigit a
a Digit a
pr) FingerTree v (Node v a)
m Digit a
sf

consDigit :: a -> Digit a -> Digit a
consDigit :: forall a. a -> Digit a -> Digit a
consDigit a
a (One a
b) = forall a. a -> a -> Digit a
Two a
a a
b
consDigit a
a (Two a
b a
c) = forall a. a -> a -> a -> Digit a
Three a
a a
b a
c
consDigit a
a (Three a
b a
c a
d) = forall a. a -> a -> a -> a -> Digit a
Four a
a a
b a
c a
d
consDigit a
_ (Four a
_ a
_ a
_ a
_) = forall a. String -> a
illegal_argument String
"consDigit"

-- | /O(1)/. Add an element to the right end of a sequence.
-- Mnemonic: a triangle with the single element at the pointy end.
(|>) :: (Measured v a) => FingerTree v a -> a -> FingerTree v a
FingerTree v a
Empty |> :: forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a              =  forall v a. a -> FingerTree v a
Single a
a
Single a
a |> a
b           =  forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (forall a. a -> Digit a
One a
a) forall v a. FingerTree v a
Empty (forall a. a -> Digit a
One a
b)
Deep v
v Digit a
pr FingerTree v (Node v a)
m (Four a
a a
b a
c a
d) |> a
e = FingerTree v (Node v a)
m seq :: forall a b. a -> b -> b
`seq`
    forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (v
v forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
e) Digit a
pr (FingerTree v (Node v a)
m forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall a. a -> a -> Digit a
Two a
d a
e)
Deep v
v Digit a
pr FingerTree v (Node v a)
m Digit a
sf |> a
x     =
    forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (v
v forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
x) Digit a
pr FingerTree v (Node v a)
m (forall a. Digit a -> a -> Digit a
snocDigit Digit a
sf a
x)

snocDigit :: Digit a -> a -> Digit a
snocDigit :: forall a. Digit a -> a -> Digit a
snocDigit (One a
a) a
b = forall a. a -> a -> Digit a
Two a
a a
b
snocDigit (Two a
a a
b) a
c = forall a. a -> a -> a -> Digit a
Three a
a a
b a
c
snocDigit (Three a
a a
b a
c) a
d = forall a. a -> a -> a -> a -> Digit a
Four a
a a
b a
c a
d
snocDigit (Four a
_ a
_ a
_ a
_) a
_ = forall a. String -> a
illegal_argument String
"snocDigit"

-- | /O(1)/. Is this the empty sequence?
null :: FingerTree v a -> Bool
null :: forall v a. FingerTree v a -> Bool
null FingerTree v a
Empty = Bool
True
null FingerTree v a
_ = Bool
False

-- | /O(1)/. Analyse the left end of a sequence.
viewl :: (Measured v a) => FingerTree v a -> ViewL (FingerTree v) a
viewl :: forall v a.
Measured v a =>
FingerTree v a -> ViewL (FingerTree v) a
viewl FingerTree v a
Empty                     =  forall (s :: * -> *) a. ViewL s a
EmptyL
viewl (Single a
x)                =  a
x forall (s :: * -> *) a. a -> s a -> ViewL s a
:< forall v a. FingerTree v a
Empty
viewl (Deep v
_ (One a
x) FingerTree v (Node v a)
m Digit a
sf)     =  a
x forall (s :: * -> *) a. a -> s a -> ViewL s a
:< forall v a.
Measured v a =>
FingerTree v (Node v a) -> Digit a -> FingerTree v a
rotL FingerTree v (Node v a)
m Digit a
sf
viewl (Deep v
_ Digit a
pr FingerTree v (Node v a)
m Digit a
sf)          =  forall a. Digit a -> a
lheadDigit Digit a
pr forall (s :: * -> *) a. a -> s a -> ViewL s a
:< forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (forall a. Digit a -> Digit a
ltailDigit Digit a
pr) FingerTree v (Node v a)
m Digit a
sf

rotL :: (Measured v a) => FingerTree v (Node v a) -> Digit a -> FingerTree v a
rotL :: forall v a.
Measured v a =>
FingerTree v (Node v a) -> Digit a -> FingerTree v a
rotL FingerTree v (Node v a)
m Digit a
sf      =   case forall v a.
Measured v a =>
FingerTree v a -> ViewL (FingerTree v) a
viewl FingerTree v (Node v a)
m of
    ViewL (FingerTree v) (Node v a)
EmptyL  ->  forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree Digit a
sf
    Node v a
a :< FingerTree v (Node v a)
m' ->  forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure Digit a
sf) (forall v a. Node v a -> Digit a
nodeToDigit Node v a
a) FingerTree v (Node v a)
m' Digit a
sf

lheadDigit :: Digit a -> a
lheadDigit :: forall a. Digit a -> a
lheadDigit (One a
a) = a
a
lheadDigit (Two a
a a
_) = a
a
lheadDigit (Three a
a a
_ a
_) = a
a
lheadDigit (Four a
a a
_ a
_ a
_) = a
a

ltailDigit :: Digit a -> Digit a
ltailDigit :: forall a. Digit a -> Digit a
ltailDigit (One a
_) = forall a. String -> a
illegal_argument String
"ltailDigit"
ltailDigit (Two a
_ a
b) = forall a. a -> Digit a
One a
b
ltailDigit (Three a
_ a
b a
c) = forall a. a -> a -> Digit a
Two a
b a
c
ltailDigit (Four a
_ a
b a
c a
d) = forall a. a -> a -> a -> Digit a
Three a
b a
c a
d

-- | /O(1)/. Analyse the right end of a sequence.
viewr :: (Measured v a) => FingerTree v a -> ViewR (FingerTree v) a
viewr :: forall v a.
Measured v a =>
FingerTree v a -> ViewR (FingerTree v) a
viewr FingerTree v a
Empty                     =  forall (s :: * -> *) a. ViewR s a
EmptyR
viewr (Single a
x)                =  forall v a. FingerTree v a
Empty forall (s :: * -> *) a. s a -> a -> ViewR s a
:> a
x
viewr (Deep v
_ Digit a
pr FingerTree v (Node v a)
m (One a
x))     =  forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> FingerTree v a
rotR Digit a
pr FingerTree v (Node v a)
m forall (s :: * -> *) a. s a -> a -> ViewR s a
:> a
x
viewr (Deep v
_ Digit a
pr FingerTree v (Node v a)
m Digit a
sf)          =  forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr FingerTree v (Node v a)
m (forall a. Digit a -> Digit a
rtailDigit Digit a
sf) forall (s :: * -> *) a. s a -> a -> ViewR s a
:> forall a. Digit a -> a
rheadDigit Digit a
sf

rotR :: (Measured v a) => Digit a -> FingerTree v (Node v a) -> FingerTree v a
rotR :: forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> FingerTree v a
rotR Digit a
pr FingerTree v (Node v a)
m = case forall v a.
Measured v a =>
FingerTree v a -> ViewR (FingerTree v) a
viewr FingerTree v (Node v a)
m of
    ViewR (FingerTree v) (Node v a)
EmptyR  ->  forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree Digit a
pr
    FingerTree v (Node v a)
m' :> Node v a
a ->  forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (forall v a. Measured v a => a -> v
measure Digit a
pr forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m) Digit a
pr FingerTree v (Node v a)
m' (forall v a. Node v a -> Digit a
nodeToDigit Node v a
a)

rheadDigit :: Digit a -> a
rheadDigit :: forall a. Digit a -> a
rheadDigit (One a
a) = a
a
rheadDigit (Two a
_ a
b) = a
b
rheadDigit (Three a
_ a
_ a
c) = a
c
rheadDigit (Four a
_ a
_ a
_ a
d) = a
d

rtailDigit :: Digit a -> Digit a
rtailDigit :: forall a. Digit a -> Digit a
rtailDigit (One a
_) = forall a. String -> a
illegal_argument String
"rtailDigit"
rtailDigit (Two a
a a
_) = forall a. a -> Digit a
One a
a
rtailDigit (Three a
a a
b a
_) = forall a. a -> a -> Digit a
Two a
a a
b
rtailDigit (Four a
a a
b a
c a
_) = forall a. a -> a -> a -> Digit a
Three a
a a
b a
c

digitToTree :: (Measured v a) => Digit a -> FingerTree v a
digitToTree :: forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree (One a
a) = forall v a. a -> FingerTree v a
Single a
a
digitToTree (Two a
a a
b) = forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (forall a. a -> Digit a
One a
a) forall v a. FingerTree v a
Empty (forall a. a -> Digit a
One a
b)
digitToTree (Three a
a a
b a
c) = forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (forall a. a -> a -> Digit a
Two a
a a
b) forall v a. FingerTree v a
Empty (forall a. a -> Digit a
One a
c)
digitToTree (Four a
a a
b a
c a
d) = forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (forall a. a -> a -> Digit a
Two a
a a
b) forall v a. FingerTree v a
Empty (forall a. a -> a -> Digit a
Two a
c a
d)

----------------
-- Concatenation
----------------

-- | /O(log(min(n1,n2)))/. Concatenate two sequences.
(><) :: (Measured v a) => FingerTree v a -> FingerTree v a -> FingerTree v a
>< :: forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
(><) =  forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
appendTree0

appendTree0 :: (Measured v a) => FingerTree v a -> FingerTree v a -> FingerTree v a
appendTree0 :: forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
appendTree0 FingerTree v a
Empty FingerTree v a
xs =
    FingerTree v a
xs
appendTree0 FingerTree v a
xs FingerTree v a
Empty =
    FingerTree v a
xs
appendTree0 (Single a
x) FingerTree v a
xs =
    a
x forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree0 FingerTree v a
xs (Single a
x) =
    FingerTree v a
xs forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
x
appendTree0 (Deep v
_ Digit a
pr1 FingerTree v (Node v a)
m1 Digit a
sf1) (Deep v
_ Digit a
pr2 FingerTree v (Node v a)
m2 Digit a
sf2) =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr1 (forall v a.
Measured v a =>
FingerTree v (Node v a)
-> Digit a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
addDigits0 FingerTree v (Node v a)
m1 Digit a
sf1 Digit a
pr2 FingerTree v (Node v a)
m2) Digit a
sf2

addDigits0 :: (Measured v a) => FingerTree v (Node v a) -> Digit a -> Digit a -> FingerTree v (Node v a) -> FingerTree v (Node v a)
addDigits0 :: forall v a.
Measured v a =>
FingerTree v (Node v a)
-> Digit a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
addDigits0 FingerTree v (Node v a)
m1 (One a
a) (One a
b) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (One a
a) (Two a
b a
c) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (One a
a) (Three a
b a
c a
d) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b) (forall v a. Measured v a => a -> a -> Node v a
node2 a
c a
d) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (One a
a) (Four a
b a
c a
d a
e) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Two a
a a
b) (One a
c) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Two a
a a
b) (Two a
c a
d) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b) (forall v a. Measured v a => a -> a -> Node v a
node2 a
c a
d) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Two a
a a
b) (Three a
c a
d a
e) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Two a
a a
b) (Four a
c a
d a
e a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) (One a
d) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b) (forall v a. Measured v a => a -> a -> Node v a
node2 a
c a
d) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) (Two a
d a
e) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) (Three a
d a
e a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) (Four a
d a
e a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) (One a
e) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) (Two a
e a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) (Three a
e a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits0 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) (Four a
e a
f a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2

appendTree1 :: (Measured v a) => FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 :: forall v a.
Measured v a =>
FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 FingerTree v a
Empty a
a FingerTree v a
xs =
    a
a forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree1 FingerTree v a
xs a
a FingerTree v a
Empty =
    FingerTree v a
xs forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a
appendTree1 (Single a
x) a
a FingerTree v a
xs =
    a
x forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
a forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree1 FingerTree v a
xs a
a (Single a
x) =
    FingerTree v a
xs forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
x
appendTree1 (Deep v
_ Digit a
pr1 FingerTree v (Node v a)
m1 Digit a
sf1) a
a (Deep v
_ Digit a
pr2 FingerTree v (Node v a)
m2 Digit a
sf2) =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr1 (forall v a.
Measured v a =>
FingerTree v (Node v a)
-> Digit a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
addDigits1 FingerTree v (Node v a)
m1 Digit a
sf1 a
a Digit a
pr2 FingerTree v (Node v a)
m2) Digit a
sf2

addDigits1 :: (Measured v a) => FingerTree v (Node v a) -> Digit a -> a -> Digit a -> FingerTree v (Node v a) -> FingerTree v (Node v a)
addDigits1 :: forall v a.
Measured v a =>
FingerTree v (Node v a)
-> Digit a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
addDigits1 FingerTree v (Node v a)
m1 (One a
a) a
b (One a
c) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (One a
a) a
b (Two a
c a
d) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b) (forall v a. Measured v a => a -> a -> Node v a
node2 a
c a
d) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (One a
a) a
b (Three a
c a
d a
e) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (One a
a) a
b (Four a
c a
d a
e a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c (One a
d) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b) (forall v a. Measured v a => a -> a -> Node v a
node2 a
c a
d) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c (Two a
d a
e) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c (Three a
d a
e a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c (Four a
d a
e a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d (One a
e) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d (Two a
e a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d (Three a
e a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d (Four a
e a
f a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e (One a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e (Two a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e (Three a
f a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits1 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e (Four a
f a
g a
h a
i) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) FingerTree v (Node v a)
m2

appendTree2 :: (Measured v a) => FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 :: forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v a
Empty a
a a
b FingerTree v a
xs =
    a
a forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree2 FingerTree v a
xs a
a a
b FingerTree v a
Empty =
    FingerTree v a
xs forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b
appendTree2 (Single a
x) a
a a
b FingerTree v a
xs =
    a
x forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
a forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree2 FingerTree v a
xs a
a a
b (Single a
x) =
    FingerTree v a
xs forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
x
appendTree2 (Deep v
_ Digit a
pr1 FingerTree v (Node v a)
m1 Digit a
sf1) a
a a
b (Deep v
_ Digit a
pr2 FingerTree v (Node v a)
m2 Digit a
sf2) =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr1 (forall v a.
Measured v a =>
FingerTree v (Node v a)
-> Digit a
-> a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
addDigits2 FingerTree v (Node v a)
m1 Digit a
sf1 a
a a
b Digit a
pr2 FingerTree v (Node v a)
m2) Digit a
sf2

addDigits2 :: (Measured v a) => FingerTree v (Node v a) -> Digit a -> a -> a -> Digit a -> FingerTree v (Node v a) -> FingerTree v (Node v a)
addDigits2 :: forall v a.
Measured v a =>
FingerTree v (Node v a)
-> Digit a
-> a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
addDigits2 FingerTree v (Node v a)
m1 (One a
a) a
b a
c (One a
d) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b) (forall v a. Measured v a => a -> a -> Node v a
node2 a
c a
d) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (One a
a) a
b a
c (Two a
d a
e) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (One a
a) a
b a
c (Three a
d a
e a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (One a
a) a
b a
c (Four a
d a
e a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d (One a
e) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d (Two a
e a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d (Three a
e a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d (Four a
e a
f a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e (One a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e (Two a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e (Three a
f a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e (Four a
f a
g a
h a
i) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f (One a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f (Two a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f (Three a
g a
h a
i) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) FingerTree v (Node v a)
m2
addDigits2 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f (Four a
g a
h a
i a
j) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) (forall v a. Measured v a => a -> a -> Node v a
node2 a
i a
j) FingerTree v (Node v a)
m2

appendTree3 :: (Measured v a) => FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 :: forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v a
Empty a
a a
b a
c FingerTree v a
xs =
    a
a forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
c forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree3 FingerTree v a
xs a
a a
b a
c FingerTree v a
Empty =
    FingerTree v a
xs forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
c
appendTree3 (Single a
x) a
a a
b a
c FingerTree v a
xs =
    a
x forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
a forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
c forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree3 FingerTree v a
xs a
a a
b a
c (Single a
x) =
    FingerTree v a
xs forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
c forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
x
appendTree3 (Deep v
_ Digit a
pr1 FingerTree v (Node v a)
m1 Digit a
sf1) a
a a
b a
c (Deep v
_ Digit a
pr2 FingerTree v (Node v a)
m2 Digit a
sf2) =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr1 (forall v a.
Measured v a =>
FingerTree v (Node v a)
-> Digit a
-> a
-> a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
addDigits3 FingerTree v (Node v a)
m1 Digit a
sf1 a
a a
b a
c Digit a
pr2 FingerTree v (Node v a)
m2) Digit a
sf2

addDigits3 :: (Measured v a) => FingerTree v (Node v a) -> Digit a -> a -> a -> a -> Digit a -> FingerTree v (Node v a) -> FingerTree v (Node v a)
addDigits3 :: forall v a.
Measured v a =>
FingerTree v (Node v a)
-> Digit a
-> a
-> a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
addDigits3 FingerTree v (Node v a)
m1 (One a
a) a
b a
c a
d (One a
e) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (One a
a) a
b a
c a
d (Two a
e a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (One a
a) a
b a
c a
d (Three a
e a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (One a
a) a
b a
c a
d (Four a
e a
f a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d a
e (One a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d a
e (Two a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d a
e (Three a
f a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d a
e (Four a
f a
g a
h a
i) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e a
f (One a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e a
f (Two a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e a
f (Three a
g a
h a
i) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e a
f (Four a
g a
h a
i a
j) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) (forall v a. Measured v a => a -> a -> Node v a
node2 a
i a
j) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g (One a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g (Two a
h a
i) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g (Three a
h a
i a
j) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) (forall v a. Measured v a => a -> a -> Node v a
node2 a
i a
j) FingerTree v (Node v a)
m2
addDigits3 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g (Four a
h a
i a
j a
k) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) (forall v a. Measured v a => a -> a -> Node v a
node2 a
j a
k) FingerTree v (Node v a)
m2

appendTree4 :: (Measured v a) => FingerTree v a -> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 :: forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v a
Empty a
a a
b a
c a
d FingerTree v a
xs =
    a
a forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
c forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
d forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree4 FingerTree v a
xs a
a a
b a
c a
d FingerTree v a
Empty =
    FingerTree v a
xs forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
c forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
d
appendTree4 (Single a
x) a
a a
b a
c a
d FingerTree v a
xs =
    a
x forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
a forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
c forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
d forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree4 FingerTree v a
xs a
a a
b a
c a
d (Single a
x) =
    FingerTree v a
xs forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
c forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
d forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
x
appendTree4 (Deep v
_ Digit a
pr1 FingerTree v (Node v a)
m1 Digit a
sf1) a
a a
b a
c a
d (Deep v
_ Digit a
pr2 FingerTree v (Node v a)
m2 Digit a
sf2) =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr1 (forall v a.
Measured v a =>
FingerTree v (Node v a)
-> Digit a
-> a
-> a
-> a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
addDigits4 FingerTree v (Node v a)
m1 Digit a
sf1 a
a a
b a
c a
d Digit a
pr2 FingerTree v (Node v a)
m2) Digit a
sf2

addDigits4 :: (Measured v a) => FingerTree v (Node v a) -> Digit a -> a -> a -> a -> a -> Digit a -> FingerTree v (Node v a) -> FingerTree v (Node v a)
addDigits4 :: forall v a.
Measured v a =>
FingerTree v (Node v a)
-> Digit a
-> a
-> a
-> a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
addDigits4 FingerTree v (Node v a)
m1 (One a
a) a
b a
c a
d a
e (One a
f) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (One a
a) a
b a
c a
d a
e (Two a
f a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (One a
a) a
b a
c a
d a
e (Three a
f a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (One a
a) a
b a
c a
d a
e (Four a
f a
g a
h a
i) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d a
e a
f (One a
g) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e) (forall v a. Measured v a => a -> a -> Node v a
node2 a
f a
g) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d a
e a
f (Two a
g a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d a
e a
f (Three a
g a
h a
i) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Two a
a a
b) a
c a
d a
e a
f (Four a
g a
h a
i a
j) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) (forall v a. Measured v a => a -> a -> Node v a
node2 a
i a
j) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e a
f a
g (One a
h) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e a
f a
g (Two a
h a
i) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e a
f a
g (Three a
h a
i a
j) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) (forall v a. Measured v a => a -> a -> Node v a
node2 a
i a
j) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Three a
a a
b a
c) a
d a
e a
f a
g (Four a
h a
i a
j a
k) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) (forall v a. Measured v a => a -> a -> Node v a
node2 a
j a
k) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g a
h (One a
i) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree3 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g a
h (Two a
i a
j) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h) (forall v a. Measured v a => a -> a -> Node v a
node2 a
i a
j) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g a
h (Three a
i a
j a
k) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) (forall v a. Measured v a => a -> a -> Node v a
node2 a
j a
k) FingerTree v (Node v a)
m2
addDigits4 FingerTree v (Node v a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g a
h (Four a
i a
j a
k a
l) FingerTree v (Node v a)
m2 =
    forall v a.
Measured v a =>
FingerTree v a
-> a -> a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree4 FingerTree v (Node v a)
m1 (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) (forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
j a
k a
l) FingerTree v (Node v a)
m2

----------------
-- 4.4 Splitting
----------------

-- | A result of 'search', attempting to find a point where a predicate
-- on splits of the sequence changes from 'False' to 'True'.
--
-- @since 0.1.2.0
data SearchResult v a
    = Position !(FingerTree v a) a !(FingerTree v a)
        -- ^ A tree opened at a particular element: the prefix to the
        -- left, the element, and the suffix to the right.
    | OnLeft
        -- ^ A position to the left of the sequence, indicating that the
        -- predicate is 'True' at both ends.
    | OnRight
        -- ^ A position to the right of the sequence, indicating that the
        -- predicate is 'False' at both ends.
    | Nowhere
        -- ^ No position in the tree, returned if the predicate is 'True'
        -- at the left end and 'False' at the right end.  This will not
        -- occur if the predicate in monotonic on the tree.
    deriving (SearchResult v a -> SearchResult v a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall v a. Eq a => SearchResult v a -> SearchResult v a -> Bool
/= :: SearchResult v a -> SearchResult v a -> Bool
$c/= :: forall v a. Eq a => SearchResult v a -> SearchResult v a -> Bool
== :: SearchResult v a -> SearchResult v a -> Bool
$c== :: forall v a. Eq a => SearchResult v a -> SearchResult v a -> Bool
Eq, SearchResult v a -> SearchResult v a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {v} {a}. Ord a => Eq (SearchResult v a)
forall v a. Ord a => SearchResult v a -> SearchResult v a -> Bool
forall v a.
Ord a =>
SearchResult v a -> SearchResult v a -> Ordering
forall v a.
Ord a =>
SearchResult v a -> SearchResult v a -> SearchResult v a
min :: SearchResult v a -> SearchResult v a -> SearchResult v a
$cmin :: forall v a.
Ord a =>
SearchResult v a -> SearchResult v a -> SearchResult v a
max :: SearchResult v a -> SearchResult v a -> SearchResult v a
$cmax :: forall v a.
Ord a =>
SearchResult v a -> SearchResult v a -> SearchResult v a
>= :: SearchResult v a -> SearchResult v a -> Bool
$c>= :: forall v a. Ord a => SearchResult v a -> SearchResult v a -> Bool
> :: SearchResult v a -> SearchResult v a -> Bool
$c> :: forall v a. Ord a => SearchResult v a -> SearchResult v a -> Bool
<= :: SearchResult v a -> SearchResult v a -> Bool
$c<= :: forall v a. Ord a => SearchResult v a -> SearchResult v a -> Bool
< :: SearchResult v a -> SearchResult v a -> Bool
$c< :: forall v a. Ord a => SearchResult v a -> SearchResult v a -> Bool
compare :: SearchResult v a -> SearchResult v a -> Ordering
$ccompare :: forall v a.
Ord a =>
SearchResult v a -> SearchResult v a -> Ordering
Ord, Int -> SearchResult v a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall v a. Show a => Int -> SearchResult v a -> ShowS
forall v a. Show a => [SearchResult v a] -> ShowS
forall v a. Show a => SearchResult v a -> String
showList :: [SearchResult v a] -> ShowS
$cshowList :: forall v a. Show a => [SearchResult v a] -> ShowS
show :: SearchResult v a -> String
$cshow :: forall v a. Show a => SearchResult v a -> String
showsPrec :: Int -> SearchResult v a -> ShowS
$cshowsPrec :: forall v a. Show a => Int -> SearchResult v a -> ShowS
Show
#if __GLASGOW_HASKELL__ >= 706
        , forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v a x. Rep (SearchResult v a) x -> SearchResult v a
forall v a x. SearchResult v a -> Rep (SearchResult v a) x
$cto :: forall v a x. Rep (SearchResult v a) x -> SearchResult v a
$cfrom :: forall v a x. SearchResult v a -> Rep (SearchResult v a) x
Generic
#endif
        )

-- | /O(log(min(i,n-i)))/. Search a sequence for a point where a predicate
-- on splits of the sequence changes from 'False' to 'True'.
--
-- The argument @p@ is a relation between the measures of the two
-- sequences that could be appended together to form the sequence @t@.
-- If the relation is 'False' at the leftmost split and 'True' at the
-- rightmost split, i.e.
--
-- @not (p 'mempty' ('measure' t)) && p ('measure' t) 'mempty'@
--
-- then there must exist an element @x@ in the sequence such that @p@
-- is 'False' for the split immediately before @x@ and 'True' for the
-- split just after it:
--
-- <<images/search.svg>>
--
-- In this situation, @'search' p t@ returns such an element @x@ and the
-- pieces @l@ and @r@ of the sequence to its left and right respectively.
-- That is, it returns @'Position' l x r@ such that
--
-- * @l >< (x <| r) = t@
--
-- * @not (p (measure l) (measure (x <| r))@
--
-- * @p (measure (l |> x)) (measure r)@
--
-- For predictable results, one should ensure that there is only one such
-- point, i.e. that the predicate is /monotonic/ on @t@.
--
-- @since 0.1.2.0
search :: (Measured v a) =>
    (v -> v -> Bool) -> FingerTree v a -> SearchResult v a
search :: forall v a.
Measured v a =>
(v -> v -> Bool) -> FingerTree v a -> SearchResult v a
search v -> v -> Bool
p FingerTree v a
t
  | Bool
p_left Bool -> Bool -> Bool
&& Bool
p_right = forall v a. SearchResult v a
OnLeft
  | Bool -> Bool
not Bool
p_left Bool -> Bool -> Bool
&& Bool
p_right = case forall v a.
Measured v a =>
(v -> v -> Bool)
-> v -> FingerTree v a -> v -> Split (FingerTree v a) a
searchTree v -> v -> Bool
p forall a. Monoid a => a
mempty FingerTree v a
t forall a. Monoid a => a
mempty of
        Split FingerTree v a
l a
x FingerTree v a
r -> forall v a.
FingerTree v a -> a -> FingerTree v a -> SearchResult v a
Position FingerTree v a
l a
x FingerTree v a
r
  | Bool -> Bool
not Bool
p_left Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
p_right = forall v a. SearchResult v a
OnRight
  | Bool
otherwise = forall v a. SearchResult v a
Nowhere
  where
    p_left :: Bool
p_left = v -> v -> Bool
p forall a. Monoid a => a
mempty v
vt
    p_right :: Bool
p_right = v -> v -> Bool
p v
vt forall a. Monoid a => a
mempty
    vt :: v
vt = forall v a. Measured v a => a -> v
measure FingerTree v a
t

-- isSplit :: (Measured v a) => (v -> v -> Bool) -> v -> a -> v -> Bool
-- isSplit p vl x vr = not (p vl (v `mappend` vr)) && p (vl `mappend` v) vr
--   where v = measure x
--
-- property:
-- isSplit p vl t vr =>
--    let Split l x r = search t in
--    isSplit p (vl `mappend` measure l) x (measure r `mappend` vr)

searchTree :: (Measured v a) =>
    (v -> v -> Bool) -> v -> FingerTree v a -> v -> Split (FingerTree v a) a
searchTree :: forall v a.
Measured v a =>
(v -> v -> Bool)
-> v -> FingerTree v a -> v -> Split (FingerTree v a) a
searchTree v -> v -> Bool
_ v
_ FingerTree v a
Empty v
_ = forall a. String -> a
illegal_argument String
"searchTree"
searchTree v -> v -> Bool
_ v
_ (Single a
x) v
_ = forall t a. t -> a -> t -> Split t a
Split forall v a. FingerTree v a
Empty a
x forall v a. FingerTree v a
Empty
searchTree v -> v -> Bool
p v
vl (Deep v
_ Digit a
pr FingerTree v (Node v a)
m Digit a
sf) v
vr
  | v -> v -> Bool
p v
vlp v
vmsr = case forall v a.
Measured v a =>
(v -> v -> Bool) -> v -> Digit a -> v -> Split (Maybe (Digit a)) a
searchDigit v -> v -> Bool
p v
vl Digit a
pr v
vmsr of
    Split Maybe (Digit a)
l a
x Maybe (Digit a)
r -> forall t a. t -> a -> t -> Split t a
Split (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall v a. FingerTree v a
Empty forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree Maybe (Digit a)
l) a
x (forall v a.
Measured v a =>
Maybe (Digit a)
-> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deepL Maybe (Digit a)
r FingerTree v (Node v a)
m Digit a
sf)
  | v -> v -> Bool
p v
vlpm v
vsr = case forall v a.
Measured v a =>
(v -> v -> Bool)
-> v -> FingerTree v a -> v -> Split (FingerTree v a) a
searchTree v -> v -> Bool
p v
vlp FingerTree v (Node v a)
m v
vsr of
    Split FingerTree v (Node v a)
ml Node v a
xs FingerTree v (Node v a)
mr -> case forall v a.
Measured v a =>
(v -> v -> Bool) -> v -> Node v a -> v -> Split (Maybe (Digit a)) a
searchNode v -> v -> Bool
p (v
vlp forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
ml) Node v a
xs (forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
mr forall a. Monoid a => a -> a -> a
`mappend` v
vsr) of
        Split Maybe (Digit a)
l a
x Maybe (Digit a)
r -> forall t a. t -> a -> t -> Split t a
Split (forall v a.
Measured v a =>
Digit a
-> FingerTree v (Node v a) -> Maybe (Digit a) -> FingerTree v a
deepR Digit a
pr FingerTree v (Node v a)
ml Maybe (Digit a)
l) a
x (forall v a.
Measured v a =>
Maybe (Digit a)
-> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deepL Maybe (Digit a)
r FingerTree v (Node v a)
mr Digit a
sf)
  | Bool
otherwise = case forall v a.
Measured v a =>
(v -> v -> Bool) -> v -> Digit a -> v -> Split (Maybe (Digit a)) a
searchDigit v -> v -> Bool
p v
vlpm Digit a
sf v
vr of
    Split Maybe (Digit a)
l a
x Maybe (Digit a)
r -> forall t a. t -> a -> t -> Split t a
Split (forall v a.
Measured v a =>
Digit a
-> FingerTree v (Node v a) -> Maybe (Digit a) -> FingerTree v a
deepR Digit a
pr FingerTree v (Node v a)
m Maybe (Digit a)
l) a
x (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall v a. FingerTree v a
Empty forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree Maybe (Digit a)
r)
  where
    vlp :: v
vlp     =  v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure Digit a
pr
    vlpm :: v
vlpm    =  v
vlp forall a. Monoid a => a -> a -> a
`mappend` v
vm
    vmsr :: v
vmsr    =  v
vm forall a. Monoid a => a -> a -> a
`mappend` v
vsr
    vsr :: v
vsr     =  forall v a. Measured v a => a -> v
measure Digit a
sf forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vm :: v
vm      =  forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m

searchNode :: (Measured v a) =>
    (v -> v -> Bool) -> v -> Node v a -> v -> Split (Maybe (Digit a)) a
searchNode :: forall v a.
Measured v a =>
(v -> v -> Bool) -> v -> Node v a -> v -> Split (Maybe (Digit a)) a
searchNode v -> v -> Bool
p v
vl (Node2 v
_ a
a a
b) v
vr
  | v -> v -> Bool
p v
va v
vb     = forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
b))
  | Bool
otherwise   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
a)) a
b forall a. Maybe a
Nothing
  where
    va :: v
va      = v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vb :: v
vb      = forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vr
searchNode v -> v -> Bool
p v
vl (Node3 v
_ a
a a
b a
c) v
vr
  | v -> v -> Bool
p v
va v
vbc    = forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
b a
c))
  | v -> v -> Bool
p v
vab v
vc    = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
a)) a
b (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
c))
  | Bool
otherwise   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
a a
b)) a
c forall a. Maybe a
Nothing
  where
    va :: v
va      = v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vab :: v
vab     = v
va forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vc :: v
vc      = forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vr
    vbc :: v
vbc     = forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vc

searchDigit :: (Measured v a) =>
    (v -> v -> Bool) -> v -> Digit a -> v -> Split (Maybe (Digit a)) a
searchDigit :: forall v a.
Measured v a =>
(v -> v -> Bool) -> v -> Digit a -> v -> Split (Maybe (Digit a)) a
searchDigit v -> v -> Bool
_ v
vl (One a
a) v
vr = v
vl seq :: forall a b. a -> b -> b
`seq` v
vr seq :: forall a b. a -> b -> b
`seq` forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a forall a. Maybe a
Nothing
searchDigit v -> v -> Bool
p v
vl (Two a
a a
b) v
vr
  | v -> v -> Bool
p v
va v
vb     = forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
b))
  | Bool
otherwise   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
a)) a
b forall a. Maybe a
Nothing
  where
    va :: v
va      = v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vb :: v
vb      = forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vr
searchDigit v -> v -> Bool
p v
vl (Three a
a a
b a
c) v
vr
  | v -> v -> Bool
p v
va v
vbc    = forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
b a
c))
  | v -> v -> Bool
p v
vab v
vc    = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
a)) a
b (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
c))
  | Bool
otherwise   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
a a
b)) a
c forall a. Maybe a
Nothing
  where
    va :: v
va      = v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vab :: v
vab     = v
va forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vbc :: v
vbc     = forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vc
    vc :: v
vc      = forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vr
searchDigit v -> v -> Bool
p v
vl (Four a
a a
b a
c a
d) v
vr
  | v -> v -> Bool
p v
va v
vbcd   = forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a (forall a. a -> Maybe a
Just (forall a. a -> a -> a -> Digit a
Three a
b a
c a
d))
  | v -> v -> Bool
p v
vab v
vcd   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
a)) a
b (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
c a
d))
  | v -> v -> Bool
p v
vabc v
vd   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
a a
b)) a
c (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
d))
  | Bool
otherwise   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> a -> a -> Digit a
Three a
a a
b a
c)) a
d forall a. Maybe a
Nothing
  where
    va :: v
va      = v
vl forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vab :: v
vab     = v
va forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vabc :: v
vabc    = v
vab forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c
    vbcd :: v
vbcd    = forall v a. Measured v a => a -> v
measure a
b forall a. Monoid a => a -> a -> a
`mappend` v
vcd
    vcd :: v
vcd     = forall v a. Measured v a => a -> v
measure a
c forall a. Monoid a => a -> a -> a
`mappend` v
vd
    vd :: v
vd      = forall v a. Measured v a => a -> v
measure a
d forall a. Monoid a => a -> a -> a
`mappend` v
vr

-- | /O(log(min(i,n-i)))/. Split a sequence at a point where the predicate
-- on the accumulated measure of the prefix changes from 'False' to 'True'.
--
-- For predictable results, one should ensure that there is only one such
-- point, i.e. that the predicate is /monotonic/.
split ::  (Measured v a) =>
      (v -> Bool) -> FingerTree v a -> (FingerTree v a, FingerTree v a)
split :: forall v a.
Measured v a =>
(v -> Bool) -> FingerTree v a -> (FingerTree v a, FingerTree v a)
split v -> Bool
_ FingerTree v a
Empty  =  (forall v a. FingerTree v a
Empty, forall v a. FingerTree v a
Empty)
split v -> Bool
p FingerTree v a
xs
  | v -> Bool
p (forall v a. Measured v a => a -> v
measure FingerTree v a
xs) =  (FingerTree v a
l, a
x forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
r)
  | Bool
otherwise   =  (FingerTree v a
xs, forall v a. FingerTree v a
Empty)
  where
    Split FingerTree v a
l a
x FingerTree v a
r = forall v a.
Measured v a =>
(v -> Bool) -> v -> FingerTree v a -> Split (FingerTree v a) a
splitTree v -> Bool
p forall a. Monoid a => a
mempty FingerTree v a
xs

-- | /O(log(min(i,n-i)))/.
-- Given a monotonic predicate @p@, @'takeUntil' p t@ is the largest
-- prefix of @t@ whose measure does not satisfy @p@.
--
-- *  @'takeUntil' p t = 'fst' ('split' p t)@
takeUntil :: (Measured v a) => (v -> Bool) -> FingerTree v a -> FingerTree v a
takeUntil :: forall v a.
Measured v a =>
(v -> Bool) -> FingerTree v a -> FingerTree v a
takeUntil v -> Bool
p  =  forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v a.
Measured v a =>
(v -> Bool) -> FingerTree v a -> (FingerTree v a, FingerTree v a)
split v -> Bool
p

-- | /O(log(min(i,n-i)))/.
-- Given a monotonic predicate @p@, @'dropUntil' p t@ is the rest of @t@
-- after removing the largest prefix whose measure does not satisfy @p@.
--
-- * @'dropUntil' p t = 'snd' ('split' p t)@
dropUntil :: (Measured v a) => (v -> Bool) -> FingerTree v a -> FingerTree v a
dropUntil :: forall v a.
Measured v a =>
(v -> Bool) -> FingerTree v a -> FingerTree v a
dropUntil v -> Bool
p  =  forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v a.
Measured v a =>
(v -> Bool) -> FingerTree v a -> (FingerTree v a, FingerTree v a)
split v -> Bool
p

data Split t a = Split !t a !t

splitTree :: (Measured v a) =>
    (v -> Bool) -> v -> FingerTree v a -> Split (FingerTree v a) a
splitTree :: forall v a.
Measured v a =>
(v -> Bool) -> v -> FingerTree v a -> Split (FingerTree v a) a
splitTree v -> Bool
_ v
_ FingerTree v a
Empty = forall a. String -> a
illegal_argument String
"splitTree"
splitTree v -> Bool
_ v
_ (Single a
x) = forall t a. t -> a -> t -> Split t a
Split forall v a. FingerTree v a
Empty a
x forall v a. FingerTree v a
Empty
splitTree v -> Bool
p v
i (Deep v
_ Digit a
pr FingerTree v (Node v a)
m Digit a
sf)
  | v -> Bool
p v
vpr = case forall v a.
Measured v a =>
(v -> Bool) -> v -> Digit a -> Split (Maybe (Digit a)) a
splitDigit v -> Bool
p v
i Digit a
pr of
    Split Maybe (Digit a)
l a
x Maybe (Digit a)
r -> forall t a. t -> a -> t -> Split t a
Split (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall v a. FingerTree v a
Empty forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree Maybe (Digit a)
l) a
x (forall v a.
Measured v a =>
Maybe (Digit a)
-> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deepL Maybe (Digit a)
r FingerTree v (Node v a)
m Digit a
sf)
  | v -> Bool
p v
vm = case forall v a.
Measured v a =>
(v -> Bool) -> v -> FingerTree v a -> Split (FingerTree v a) a
splitTree v -> Bool
p v
vpr FingerTree v (Node v a)
m of
    Split FingerTree v (Node v a)
ml Node v a
xs FingerTree v (Node v a)
mr -> case forall v a.
Measured v a =>
(v -> Bool) -> v -> Node v a -> Split (Maybe (Digit a)) a
splitNode v -> Bool
p (v
vpr forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
ml) Node v a
xs of
        Split Maybe (Digit a)
l a
x Maybe (Digit a)
r -> forall t a. t -> a -> t -> Split t a
Split (forall v a.
Measured v a =>
Digit a
-> FingerTree v (Node v a) -> Maybe (Digit a) -> FingerTree v a
deepR Digit a
pr  FingerTree v (Node v a)
ml Maybe (Digit a)
l) a
x (forall v a.
Measured v a =>
Maybe (Digit a)
-> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deepL Maybe (Digit a)
r FingerTree v (Node v a)
mr Digit a
sf)
  | Bool
otherwise = case forall v a.
Measured v a =>
(v -> Bool) -> v -> Digit a -> Split (Maybe (Digit a)) a
splitDigit v -> Bool
p v
vm Digit a
sf of
    Split Maybe (Digit a)
l a
x Maybe (Digit a)
r -> forall t a. t -> a -> t -> Split t a
Split (forall v a.
Measured v a =>
Digit a
-> FingerTree v (Node v a) -> Maybe (Digit a) -> FingerTree v a
deepR Digit a
pr  FingerTree v (Node v a)
m  Maybe (Digit a)
l) a
x (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall v a. FingerTree v a
Empty forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree Maybe (Digit a)
r)
  where
    vpr :: v
vpr     =  v
i    forall a. Monoid a => a -> a -> a
`mappend`  forall v a. Measured v a => a -> v
measure Digit a
pr
    vm :: v
vm      =  v
vpr  forall a. Monoid a => a -> a -> a
`mappend`  forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m

deepL :: (Measured v a) =>
    Maybe (Digit a) -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deepL :: forall v a.
Measured v a =>
Maybe (Digit a)
-> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deepL Maybe (Digit a)
Nothing FingerTree v (Node v a)
m Digit a
sf      =   forall v a.
Measured v a =>
FingerTree v (Node v a) -> Digit a -> FingerTree v a
rotL FingerTree v (Node v a)
m Digit a
sf
deepL (Just Digit a
pr) FingerTree v (Node v a)
m Digit a
sf    =   forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr FingerTree v (Node v a)
m Digit a
sf

deepR :: (Measured v a) =>
    Digit a -> FingerTree v (Node v a) -> Maybe (Digit a) -> FingerTree v a
deepR :: forall v a.
Measured v a =>
Digit a
-> FingerTree v (Node v a) -> Maybe (Digit a) -> FingerTree v a
deepR Digit a
pr FingerTree v (Node v a)
m Maybe (Digit a)
Nothing      =   forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> FingerTree v a
rotR Digit a
pr FingerTree v (Node v a)
m
deepR Digit a
pr FingerTree v (Node v a)
m (Just Digit a
sf)    =   forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr FingerTree v (Node v a)
m Digit a
sf

splitNode :: (Measured v a) =>
    (v -> Bool) -> v -> Node v a -> Split (Maybe (Digit a)) a
splitNode :: forall v a.
Measured v a =>
(v -> Bool) -> v -> Node v a -> Split (Maybe (Digit a)) a
splitNode v -> Bool
p v
i (Node2 v
_ a
a a
b)
  | v -> Bool
p v
va        = forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
b))
  | Bool
otherwise   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
a)) a
b forall a. Maybe a
Nothing
  where
    va :: v
va      = v
i forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
splitNode v -> Bool
p v
i (Node3 v
_ a
a a
b a
c)
  | v -> Bool
p v
va        = forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
b a
c))
  | v -> Bool
p v
vab       = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
a)) a
b (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
c))
  | Bool
otherwise   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
a a
b)) a
c forall a. Maybe a
Nothing
  where
    va :: v
va      = v
i forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vab :: v
vab     = v
va forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b

splitDigit :: (Measured v a) =>
    (v -> Bool) -> v -> Digit a -> Split (Maybe (Digit a)) a
splitDigit :: forall v a.
Measured v a =>
(v -> Bool) -> v -> Digit a -> Split (Maybe (Digit a)) a
splitDigit v -> Bool
_ v
i (One a
a) = v
i seq :: forall a b. a -> b -> b
`seq` forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a forall a. Maybe a
Nothing
splitDigit v -> Bool
p v
i (Two a
a a
b)
  | v -> Bool
p v
va        = forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
b))
  | Bool
otherwise   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
a)) a
b forall a. Maybe a
Nothing
  where
    va :: v
va      = v
i forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
splitDigit v -> Bool
p v
i (Three a
a a
b a
c)
  | v -> Bool
p v
va        = forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
b a
c))
  | v -> Bool
p v
vab       = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
a)) a
b (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
c))
  | Bool
otherwise   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
a a
b)) a
c forall a. Maybe a
Nothing
  where
    va :: v
va      = v
i forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vab :: v
vab     = v
va forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
splitDigit v -> Bool
p v
i (Four a
a a
b a
c a
d)
  | v -> Bool
p v
va        = forall t a. t -> a -> t -> Split t a
Split forall a. Maybe a
Nothing a
a (forall a. a -> Maybe a
Just (forall a. a -> a -> a -> Digit a
Three a
b a
c a
d))
  | v -> Bool
p v
vab       = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
a)) a
b (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
c a
d))
  | v -> Bool
p v
vabc      = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> a -> Digit a
Two a
a a
b)) a
c (forall a. a -> Maybe a
Just (forall a. a -> Digit a
One a
d))
  | Bool
otherwise   = forall t a. t -> a -> t -> Split t a
Split (forall a. a -> Maybe a
Just (forall a. a -> a -> a -> Digit a
Three a
a a
b a
c)) a
d forall a. Maybe a
Nothing
  where
    va :: v
va      = v
i forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
a
    vab :: v
vab     = v
va forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
b
    vabc :: v
vabc    = v
vab forall a. Monoid a => a -> a -> a
`mappend` forall v a. Measured v a => a -> v
measure a
c

------------------
-- Transformations
------------------

-- | /O(n)/. The reverse of a sequence.
reverse :: (Measured v a) => FingerTree v a -> FingerTree v a
reverse :: forall v a. Measured v a => FingerTree v a -> FingerTree v a
reverse = forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
reverseTree forall a. a -> a
id

reverseTree :: (Measured v2 a2) => (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
reverseTree :: forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
reverseTree a1 -> a2
_ FingerTree v1 a1
Empty = forall v a. FingerTree v a
Empty
reverseTree a1 -> a2
f (Single a1
x) = forall v a. a -> FingerTree v a
Single (a1 -> a2
f a1
x)
reverseTree a1 -> a2
f (Deep v1
_ Digit a1
pr FingerTree v1 (Node v1 a1)
m Digit a1
sf) =
    forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (forall a b. (a -> b) -> Digit a -> Digit b
reverseDigit a1 -> a2
f Digit a1
sf) (forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
reverseTree (forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> Node v1 a1 -> Node v2 a2
reverseNode a1 -> a2
f) FingerTree v1 (Node v1 a1)
m) (forall a b. (a -> b) -> Digit a -> Digit b
reverseDigit a1 -> a2
f Digit a1
pr)

reverseNode :: (Measured v2 a2) => (a1 -> a2) -> Node v1 a1 -> Node v2 a2
reverseNode :: forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> Node v1 a1 -> Node v2 a2
reverseNode a1 -> a2
f (Node2 v1
_ a1
a a1
b) = forall v a. Measured v a => a -> a -> Node v a
node2 (a1 -> a2
f a1
b) (a1 -> a2
f a1
a)
reverseNode a1 -> a2
f (Node3 v1
_ a1
a a1
b a1
c) = forall v a. Measured v a => a -> a -> a -> Node v a
node3 (a1 -> a2
f a1
c) (a1 -> a2
f a1
b) (a1 -> a2
f a1
a)

reverseDigit :: (a -> b) -> Digit a -> Digit b
reverseDigit :: forall a b. (a -> b) -> Digit a -> Digit b
reverseDigit a -> b
f (One a
a) = forall a. a -> Digit a
One (a -> b
f a
a)
reverseDigit a -> b
f (Two a
a a
b) = forall a. a -> a -> Digit a
Two (a -> b
f a
b) (a -> b
f a
a)
reverseDigit a -> b
f (Three a
a a
b a
c) = forall a. a -> a -> a -> Digit a
Three (a -> b
f a
c) (a -> b
f a
b) (a -> b
f a
a)
reverseDigit a -> b
f (Four a
a a
b a
c a
d) = forall a. a -> a -> a -> a -> Digit a
Four (a -> b
f a
d) (a -> b
f a
c) (a -> b
f a
b) (a -> b
f a
a)

illegal_argument :: String -> a
illegal_argument :: forall a. String -> a
illegal_argument String
name =
    forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Logic error: " forall a. [a] -> [a] -> [a]
++ String
name forall a. [a] -> [a] -> [a]
++ String
" called with illegal argument"

{- $example

Particular abstract data types may be implemented by defining
element types with suitable 'Measured' instances.

(from section 4.5 of the paper)
Simple sequences can be implemented using a 'Data.Monoid.Sum' monoid
as a measure:

> newtype Elem a = Elem { getElem :: a }
>
> instance Measured (Sum Int) (Elem a) where
>     measure (Elem _) = Sum 1
>
> newtype Seq a = Seq (FingerTree (Sum Int) (Elem a))

Then the measure of a subsequence is simply its length.
This representation supports log-time extraction of subsequences:

> take :: Int -> Seq a -> Seq a
> take k (Seq xs) = Seq (takeUntil (> Sum k) xs)
>
> drop :: Int -> Seq a -> Seq a
> drop k (Seq xs) = Seq (dropUntil (> Sum k) xs)

The module @Data.Sequence@ is an optimized instantiation of this type.

For further examples, see "Data.IntervalMap.FingerTree" and
"Data.PriorityQueue.FingerTree".

-}