{-# LANGUAGE CPP                    #-}
{-# LANGUAGE DeriveAnyClass         #-}
{-# LANGUAGE DeriveFunctor          #-}
{-# LANGUAGE DeriveGeneric          #-}
{-# LANGUAGE FlexibleInstances      #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances   #-}
{-# LANGUAGE TypeFamilies           #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.FingerTree
-- Copyright   :  (c) Ross Paterson, Ralf Hinze 2006
-- 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 HaskellWorks.Data.FingerTree
  ( FingerTree(..)
  , Digit(..)
  , Node(..)
  , deep
  , node2
  , node3
  , Measured(..)
  -- * Construction
  , empty
  , singleton
  , append
  , fromList
  -- * Deconstruction
  , null
  , ViewL(..)
  , ViewR(..)
  , viewl
  , viewr
  , split
  , takeUntil
  , dropUntil
  -- * Transformation
  , reverse
  , fmap'
  , fmapWithPos
  , unsafeFmap
  , traverse'
  , traverseWithPos
  , unsafeTraverse
  -- * Example
  -- $example
  , (><)
  , (<|)
  , (|>)
  ) where

import Control.DeepSeq
import Data.Foldable                (toList)
import GHC.Generics                 (Generic)
import HaskellWorks.Data.Container
import HaskellWorks.Data.Cons
import HaskellWorks.Data.Snoc
import HaskellWorks.Data.Ops
import Prelude                      hiding (null, reverse)

import qualified Data.Semigroup as S

#if !MIN_VERSION_base(4,13,0)
import Control.Applicative          (Applicative (pure, (<*>)), (<$>))
#endif

infixr 5 :<
infixl 5 :>

{- HLINT ignore "Reduce duplication"  -}
{- HLINT ignore "Use record patterns" -}

-- | 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
(ViewL s a -> ViewL s a -> Bool)
-> (ViewL s a -> ViewL s a -> Bool) -> Eq (ViewL s a)
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, Eq (ViewL s a)
Eq (ViewL s a)
-> (ViewL s a -> ViewL s a -> Ordering)
-> (ViewL s a -> ViewL s a -> Bool)
-> (ViewL s a -> ViewL s a -> Bool)
-> (ViewL s a -> ViewL s a -> Bool)
-> (ViewL s a -> ViewL s a -> Bool)
-> (ViewL s a -> ViewL s a -> ViewL s a)
-> (ViewL s a -> ViewL s a -> ViewL s a)
-> Ord (ViewL s a)
ViewL s a -> ViewL s a -> Bool
ViewL s a -> ViewL s a -> Ordering
ViewL s a -> ViewL s a -> ViewL s a
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
$cp1Ord :: forall (s :: * -> *) a. (Ord a, Ord (s a)) => Eq (ViewL s a)
Ord, Int -> ViewL s a -> ShowS
[ViewL s a] -> ShowS
ViewL s a -> String
(Int -> ViewL s a -> ShowS)
-> (ViewL s a -> String)
-> ([ViewL s a] -> ShowS)
-> Show (ViewL s a)
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)
Int -> ReadS (ViewL s a)
ReadS [ViewL s a]
(Int -> ReadS (ViewL s a))
-> ReadS [ViewL s a]
-> ReadPrec (ViewL s a)
-> ReadPrec [ViewL s a]
-> Read (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, (forall x. ViewL s a -> Rep (ViewL s a) x)
-> (forall x. Rep (ViewL s a) x -> ViewL s a)
-> Generic (ViewL s a)
forall x. Rep (ViewL s a) x -> ViewL s a
forall x. ViewL s a -> Rep (ViewL s a) x
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, ViewL s a -> ()
(ViewL s a -> ()) -> NFData (ViewL s a)
forall a. (a -> ()) -> NFData a
forall (s :: * -> *) a. (NFData a, NFData (s a)) => ViewL s a -> ()
rnf :: ViewL s a -> ()
$crnf :: forall (s :: * -> *) a. (NFData a, NFData (s a)) => ViewL s a -> ()
NFData)

-- | 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
(ViewR s a -> ViewR s a -> Bool)
-> (ViewR s a -> ViewR s a -> Bool) -> Eq (ViewR s a)
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, Eq (ViewR s a)
Eq (ViewR s a)
-> (ViewR s a -> ViewR s a -> Ordering)
-> (ViewR s a -> ViewR s a -> Bool)
-> (ViewR s a -> ViewR s a -> Bool)
-> (ViewR s a -> ViewR s a -> Bool)
-> (ViewR s a -> ViewR s a -> Bool)
-> (ViewR s a -> ViewR s a -> ViewR s a)
-> (ViewR s a -> ViewR s a -> ViewR s a)
-> Ord (ViewR s a)
ViewR s a -> ViewR s a -> Bool
ViewR s a -> ViewR s a -> Ordering
ViewR s a -> ViewR s a -> ViewR s a
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
$cp1Ord :: forall (s :: * -> *) a. (Ord a, Ord (s a)) => Eq (ViewR s a)
Ord, Int -> ViewR s a -> ShowS
[ViewR s a] -> ShowS
ViewR s a -> String
(Int -> ViewR s a -> ShowS)
-> (ViewR s a -> String)
-> ([ViewR s a] -> ShowS)
-> Show (ViewR s a)
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)
Int -> ReadS (ViewR s a)
ReadS [ViewR s a]
(Int -> ReadS (ViewR s a))
-> ReadS [ViewR s a]
-> ReadPrec (ViewR s a)
-> ReadPrec [ViewR s a]
-> Read (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, (forall x. ViewR s a -> Rep (ViewR s a) x)
-> (forall x. Rep (ViewR s a) x -> ViewR s a)
-> Generic (ViewR s a)
forall x. Rep (ViewR s a) x -> ViewR s a
forall x. ViewR s a -> Rep (ViewR s a) x
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, ViewR s a -> ()
(ViewR s a -> ()) -> NFData (ViewR s a)
forall a. (a -> ()) -> NFData a
forall (s :: * -> *) a. (NFData a, NFData (s a)) => ViewR s a -> ()
rnf :: ViewR s a -> ()
$crnf :: forall (s :: * -> *) a. (NFData a, NFData (s a)) => ViewR s a -> ()
NFData)

instance Functor s => Functor (ViewL s) where
  fmap :: (a -> b) -> ViewL s a -> ViewL s b
fmap a -> b
_ ViewL s a
EmptyL    = ViewL s b
forall (s :: * -> *) a. ViewL s a
EmptyL
  fmap a -> b
f (a
x :< s a
xs) = a -> b
f a
x b -> s b -> ViewL s b
forall (s :: * -> *) a. a -> s a -> ViewL s a
:< (a -> b) -> s a -> s b
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 :: (a -> b) -> ViewR s a -> ViewR s b
fmap a -> b
_ ViewR s a
EmptyR    = ViewR s b
forall (s :: * -> *) a. ViewR s a
EmptyR
  fmap a -> b
f (s a
xs :> a
x) = (a -> b) -> s a -> s b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f s a
xs s b -> b -> ViewR s b
forall (s :: * -> *) a. s a -> a -> ViewR s a
:> a -> b
f a
x

instance Measured v a => S.Semigroup (FingerTree v a) where
  <> :: FingerTree v a -> FingerTree v a -> FingerTree 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
append
  {-# INLINE (<>) #-}

-- | 'empty' and '><'.
instance Measured v a => Monoid (FingerTree v a) where
  mempty :: FingerTree v a
mempty = FingerTree v a
forall v a. Measured v a => FingerTree v a
empty
  {-# INLINE mempty #-}

instance Container (FingerTree v a) where
  type Elem (FingerTree v a) = a

data Digit a
  = One a
  | Two a a
  | Three a a a
  | Four a a a a
  deriving (Int -> Digit a -> ShowS
[Digit a] -> ShowS
Digit a -> String
(Int -> Digit a -> ShowS)
-> (Digit a -> String) -> ([Digit a] -> ShowS) -> Show (Digit a)
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, (forall x. Digit a -> Rep (Digit a) x)
-> (forall x. Rep (Digit a) x -> Digit a) -> Generic (Digit a)
forall x. Rep (Digit a) x -> Digit a
forall x. Digit a -> Rep (Digit a) x
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, Digit a -> ()
(Digit a -> ()) -> NFData (Digit a)
forall a. NFData a => Digit a -> ()
forall a. (a -> ()) -> NFData a
rnf :: Digit a -> ()
$crnf :: forall a. NFData a => Digit a -> ()
NFData, a -> Digit b -> Digit a
(a -> b) -> Digit a -> Digit b
(forall a b. (a -> b) -> Digit a -> Digit b)
-> (forall a b. a -> Digit b -> Digit a) -> Functor Digit
forall a b. a -> Digit b -> Digit a
forall a b. (a -> b) -> Digit a -> Digit b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Digit b -> Digit a
$c<$ :: forall a b. a -> Digit b -> Digit a
fmap :: (a -> b) -> Digit a -> Digit b
$cfmap :: forall a b. (a -> b) -> Digit a -> Digit b
Functor)

instance Foldable Digit where
  foldMap :: (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 m -> m -> m
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 m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b m -> m -> m
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 m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
c m -> m -> m
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 = (a -> v) -> Digit a -> v
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> v
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
[Node v a] -> ShowS
Node v a -> String
(Int -> Node v a -> ShowS)
-> (Node v a -> String) -> ([Node v a] -> ShowS) -> Show (Node v a)
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, (forall x. Node v a -> Rep (Node v a) x)
-> (forall x. Rep (Node v a) x -> Node v a) -> Generic (Node v a)
forall x. Rep (Node v a) x -> Node v a
forall x. Node v a -> Rep (Node v a) x
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, Node v a -> ()
(Node v a -> ()) -> NFData (Node v a)
forall a. (a -> ()) -> NFData a
forall v a. (NFData v, NFData a) => Node v a -> ()
rnf :: Node v a -> ()
$crnf :: forall v a. (NFData v, NFData a) => Node v a -> ()
NFData)

instance Foldable (Node v) where
  foldMap :: (a -> m) -> Node v a -> m
foldMap a -> m
f (Node2 v
_ a
a a
b)   = a -> m
f a
a m -> m -> m
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 m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
c

node2        ::  (Measured v a) => a -> a -> Node v a
node2 :: a -> a -> Node v a
node2 a
a a
b    =   v -> a -> a -> Node v a
forall v a. v -> a -> a -> Node v a
Node2 (a -> v
forall v a. Measured v a => a -> v
measure a
a v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
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 :: a -> a -> a -> Node v a
node3 a
a a
b a
c  =   v -> a -> a -> a -> Node v a
forall v a. v -> a -> a -> a -> Node v a
Node3 (a -> v
forall v a. Measured v a => a -> v
measure a
a v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
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 :: Node v a -> Digit a
nodeToDigit (Node2 v
_ a
a a
b)   = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
nodeToDigit (Node3 v
_ a
a a
b a
c) = a -> a -> a -> Digit a
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)
  deriving ((forall x. FingerTree v a -> Rep (FingerTree v a) x)
-> (forall x. Rep (FingerTree v a) x -> FingerTree v a)
-> Generic (FingerTree v a)
forall x. Rep (FingerTree v a) x -> FingerTree v a
forall x. FingerTree v a -> Rep (FingerTree v a) x
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, FingerTree v a -> ()
(FingerTree v a -> ()) -> NFData (FingerTree v a)
forall a. (a -> ()) -> NFData a
forall v a. (NFData a, NFData v) => FingerTree v a -> ()
rnf :: FingerTree v a -> ()
$crnf :: forall v a. (NFData a, NFData v) => FingerTree v a -> ()
NFData)

deep :: (Measured v a) => Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep :: 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 = v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep ((Digit a -> v
forall v a. Measured v a => a -> v
measure Digit a
pr v -> FingerTree v (Node v a) -> v
forall v a. Measured v a => v -> FingerTree v a -> v
`mappendVal` FingerTree v (Node v a)
m) v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` Digit a -> v
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          =  v
forall a. Monoid a => a
mempty
  measure (Single a
x)     =  a -> v
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

instance Foldable (FingerTree v) where
  foldMap :: (a -> m) -> FingerTree v a -> m
foldMap a -> m
_ FingerTree v a
Empty            = m
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) = (a -> m) -> Digit a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f Digit a
pr m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` (Node v a -> m) -> FingerTree v (Node v a) -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((a -> m) -> Node v a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f) FingerTree v (Node v a)
m m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` (a -> m) -> Digit a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f Digit a
sf

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

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 = [a] -> [a] -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (FingerTree v a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList FingerTree v a
xs) (FingerTree v a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList FingerTree v a
ys)

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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"fromList " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> ShowS
forall a. Show a => a -> ShowS
shows (FingerTree v a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList FingerTree v a
xs)

-- | Like 'fmap', but with a more constrained type.
fmap' :: (Measured v1 a1, Measured v2 a2) => (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmap' :: (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmap' = (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
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 :: (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
mapTree a1 -> a2
_ FingerTree v1 a1
Empty            = FingerTree v2 a2
forall v a. FingerTree v a
Empty
mapTree a1 -> a2
f (Single a1
x)       = a2 -> FingerTree v2 a2
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) = Digit a2
-> FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep ((a1 -> a2) -> Digit a1 -> Digit a2
forall a b. (a -> b) -> Digit a -> Digit b
mapDigit a1 -> a2
f Digit a1
pr) ((Node v1 a1 -> Node v2 a2)
-> FingerTree v1 (Node v1 a1) -> FingerTree v2 (Node v2 a2)
forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
mapTree ((a1 -> a2) -> Node v1 a1 -> Node v2 a2
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) ((a1 -> a2) -> Digit a1 -> Digit a2
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 :: (a1 -> a2) -> Node v1 a1 -> Node v2 a2
mapNode a1 -> a2
f (Node2 v1
_ a1
a a1
b)   = a2 -> a2 -> Node v2 a2
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) = a2 -> a2 -> a2 -> Node v2 a2
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 :: (a -> b) -> Digit a -> Digit b
mapDigit a -> b
f (One a
a)        = b -> Digit b
forall a. a -> Digit a
One (a -> b
f a
a)
mapDigit a -> b
f (Two a
a a
b)      = b -> b -> Digit 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)  = b -> b -> b -> Digit b
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) = b -> b -> b -> b -> Digit b
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 :: (v1 -> a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmapWithPos v1 -> a1 -> a2
f = (v1 -> a1 -> a2) -> v1 -> FingerTree v1 a1 -> FingerTree v2 a2
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 v1
forall a. Monoid a => a
mempty

mapWPTree :: (Measured v1 a1, Measured v2 a2) => (v1 -> a1 -> a2) -> v1 -> FingerTree v1 a1 -> FingerTree v2 a2
mapWPTree :: (v1 -> a1 -> a2) -> v1 -> FingerTree v1 a1 -> FingerTree v2 a2
mapWPTree v1 -> a1 -> a2
_ v1
_ FingerTree v1 a1
Empty = FingerTree v2 a2
forall v a. FingerTree v a
Empty
mapWPTree v1 -> a1 -> a2
f v1
v (Single a1
x) = a2 -> FingerTree v2 a2
forall v a. a -> FingerTree v a
Single (v1 -> a1 -> a2
f v1
v a1
x)
mapWPTree v1 -> a1 -> a2
f v1
v (Deep v1
_ Digit a1
pr FingerTree v1 (Node v1 a1)
m Digit a1
sf) = Digit a2
-> FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep
  ((v1 -> a1 -> a2) -> v1 -> Digit a1 -> Digit a2
forall v a b.
Measured v a =>
(v -> a -> b) -> v -> Digit a -> Digit b
mapWPDigit v1 -> a1 -> a2
f v1
v Digit a1
pr)
  ((v1 -> Node v1 a1 -> Node v2 a2)
-> v1 -> FingerTree v1 (Node v1 a1) -> FingerTree v2 (Node v2 a2)
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 -> Node v1 a1 -> Node v2 a2
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
vpr FingerTree v1 (Node v1 a1)
m)
  ((v1 -> a1 -> a2) -> v1 -> Digit a1 -> Digit a2
forall v a b.
Measured v a =>
(v -> a -> b) -> v -> Digit a -> Digit b
mapWPDigit v1 -> a1 -> a2
f v1
vm Digit a1
sf)
  where vpr :: v1
vpr = v1
v    v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend`  Digit a1 -> v1
forall v a. Measured v a => a -> v
measure Digit a1
pr
        vm :: v1
vm  = v1
vpr  v1 -> FingerTree v1 (Node v1 a1) -> v1
forall v a. Measured v a => v -> FingerTree v a -> v
`mappendVal` FingerTree v1 (Node v1 a1)
m

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

mapWPDigit :: (Measured v a) => (v -> a -> b) -> v -> Digit a -> Digit b
mapWPDigit :: (v -> a -> b) -> v -> Digit a -> Digit b
mapWPDigit v -> a -> b
f v
v (One a
a  ) = b -> Digit b
forall a. a -> Digit a
One (v -> a -> b
f v
v a
a)
mapWPDigit v -> a -> b
f v
v (Two a
a a
b) = b -> b -> Digit b
forall a. a -> a -> Digit a
Two (v -> a -> b
f v
v a
a) (v -> a -> b
f v
va a
b)
  where va :: v
va = v
v v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
mapWPDigit v -> a -> b
f v
v (Three a
a a
b a
c) = b -> b -> b -> Digit b
forall a. a -> a -> a -> Digit a
Three (v -> a -> b
f v
v a
a) (v -> a -> b
f v
va a
b) (v -> a -> b
f v
vab a
c)
  where va :: v
va  = v
v  v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
        vab :: v
vab = v
va v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
b
mapWPDigit v -> a -> b
f v
v (Four a
a a
b a
c a
d) = b -> b -> b -> b -> Digit b
forall a. a -> a -> a -> a -> Digit a
Four (v -> a -> b
f v
v a
a) (v -> a -> b
f v
va a
b) (v -> a -> b
f v
vab a
c) (v -> a -> b
f v
vabc a
d)
  where va :: v
va    = v
v   v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
        vab :: v
vab   = v
va  v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
b
        vabc :: v
vabc  = v
vab v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
c

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

-- | Like 'traverse', but with a more constrained type.
traverse' :: (Measured v1 a1, Measured v2 a2, Applicative f) => (a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverse' :: (a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverse' = (a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
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 :: (a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseTree a1 -> f a2
_ FingerTree v1 a1
Empty = FingerTree v2 a2 -> f (FingerTree v2 a2)
forall (f :: * -> *) a. Applicative f => a -> f a
pure FingerTree v2 a2
forall v a. FingerTree v a
Empty
traverseTree a1 -> f a2
f (Single a1
x) = a2 -> FingerTree v2 a2
forall v a. a -> FingerTree v a
Single (a2 -> FingerTree v2 a2) -> f a2 -> f (FingerTree v2 a2)
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) = Digit a2
-> FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep
  (Digit a2
 -> FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2)
-> f (Digit a2)
-> f (FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a1 -> f a2) -> Digit a1 -> f (Digit a2)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Digit a -> f (Digit b)
traverseDigit a1 -> f a2
f Digit a1
pr
  f (FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2)
-> f (FingerTree v2 (Node v2 a2))
-> f (Digit a2 -> FingerTree v2 a2)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Node v1 a1 -> f (Node v2 a2))
-> FingerTree v1 (Node v1 a1) -> f (FingerTree v2 (Node v2 a2))
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) -> Node v1 a1 -> f (Node v2 a2)
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
  f (Digit a2 -> FingerTree v2 a2)
-> f (Digit a2) -> f (FingerTree v2 a2)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (a1 -> f a2) -> Digit a1 -> f (Digit a2)
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 :: (a1 -> f a2) -> Node v1 a1 -> f (Node v2 a2)
traverseNode a1 -> f a2
f (Node2 v1
_ a1
a a1
b)   = a2 -> a2 -> Node v2 a2
forall v a. Measured v a => a -> a -> Node v a
node2 (a2 -> a2 -> Node v2 a2) -> f a2 -> f (a2 -> Node v2 a2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a1 -> f a2
f a1
a f (a2 -> Node v2 a2) -> f a2 -> f (Node v2 a2)
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) = a2 -> a2 -> a2 -> Node v2 a2
forall v a. Measured v a => a -> a -> a -> Node v a
node3 (a2 -> a2 -> a2 -> Node v2 a2)
-> f a2 -> f (a2 -> a2 -> Node v2 a2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a1 -> f a2
f a1
a f (a2 -> a2 -> Node v2 a2) -> f a2 -> f (a2 -> Node v2 a2)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a1 -> f a2
f a1
b f (a2 -> Node v2 a2) -> f a2 -> f (Node v2 a2)
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 :: (a -> f b) -> Digit a -> f (Digit b)
traverseDigit a -> f b
f (One a
a)        = b -> Digit b
forall a. a -> Digit a
One   (b -> Digit b) -> f b -> f (Digit b)
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)      = b -> b -> Digit b
forall a. a -> a -> Digit a
Two   (b -> b -> Digit b) -> f b -> f (b -> Digit b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> Digit b) -> f b -> f (Digit b)
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)  = b -> b -> b -> Digit b
forall a. a -> a -> a -> Digit a
Three (b -> b -> b -> Digit b) -> f b -> f (b -> b -> Digit b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> b -> Digit b) -> f b -> f (b -> Digit b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
b f (b -> Digit b) -> f b -> f (Digit 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) = b -> b -> b -> b -> Digit b
forall a. a -> a -> a -> a -> Digit a
Four  (b -> b -> b -> b -> Digit b) -> f b -> f (b -> b -> b -> Digit b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> b -> b -> Digit b) -> f b -> f (b -> b -> Digit b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
b f (b -> b -> Digit b) -> f b -> f (b -> Digit b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
c f (b -> Digit b) -> f b -> f (Digit b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
d

-- | Traverse the tree 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 :: (v1 -> a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWithPos v1 -> a1 -> f a2
f = (v1 -> a1 -> f a2)
-> v1 -> FingerTree v1 a1 -> f (FingerTree v2 a2)
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 v1
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 :: (v1 -> a1 -> f a2)
-> v1 -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWPTree v1 -> a1 -> f a2
_ v1
_ FingerTree v1 a1
Empty = FingerTree v2 a2 -> f (FingerTree v2 a2)
forall (f :: * -> *) a. Applicative f => a -> f a
pure FingerTree v2 a2
forall v a. FingerTree v a
Empty
traverseWPTree v1 -> a1 -> f a2
f v1
v (Single a1
x) = a2 -> FingerTree v2 a2
forall v a. a -> FingerTree v a
Single (a2 -> FingerTree v2 a2) -> f a2 -> f (FingerTree v2 a2)
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) = Digit a2
-> FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep
  (Digit a2
 -> FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2)
-> f (Digit a2)
-> f (FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (v1 -> a1 -> f a2) -> v1 -> Digit a1 -> f (Digit a2)
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
  f (FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2)
-> f (FingerTree v2 (Node v2 a2))
-> f (Digit a2 -> FingerTree v2 a2)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (v1 -> Node v1 a1 -> f (Node v2 a2))
-> v1
-> FingerTree v1 (Node v1 a1)
-> f (FingerTree v2 (Node v2 a2))
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 -> Node v1 a1 -> f (Node v2 a2)
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
  f (Digit a2 -> FingerTree v2 a2)
-> f (Digit a2) -> f (FingerTree v2 a2)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (v1 -> a1 -> f a2) -> v1 -> Digit a1 -> f (Digit a2)
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   v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend`  Digit a1 -> v1
forall v a. Measured v a => a -> v
measure Digit a1
pr
        vm :: v1
vm  = v1
vpr v1 -> FingerTree v1 (Node v1 a1) -> v1
forall v a. Measured v a => v -> FingerTree v a -> v
`mappendVal` 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 :: (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) = a2 -> a2 -> Node v2 a2
forall v a. Measured v a => a -> a -> Node v a
node2 (a2 -> a2 -> Node v2 a2) -> f a2 -> f (a2 -> Node v2 a2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v1 -> a1 -> f a2
f v1
v a1
a f (a2 -> Node v2 a2) -> f a2 -> f (Node v2 a2)
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 v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` a1 -> v1
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) = a2 -> a2 -> a2 -> Node v2 a2
forall v a. Measured v a => a -> a -> a -> Node v a
node3 (a2 -> a2 -> a2 -> Node v2 a2)
-> f a2 -> f (a2 -> a2 -> Node v2 a2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v1 -> a1 -> f a2
f v1
v a1
a f (a2 -> a2 -> Node v2 a2) -> f a2 -> f (a2 -> Node v2 a2)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v1 -> a1 -> f a2
f v1
va a1
b f (a2 -> Node v2 a2) -> f a2 -> f (Node v2 a2)
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  v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` a1 -> v1
forall v a. Measured v a => a -> v
measure a1
a
        vab :: v1
vab = v1
va v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` a1 -> v1
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 :: (v -> a -> f b) -> v -> Digit a -> f (Digit b)
traverseWPDigit v -> a -> f b
f v
v (One a
a) = b -> Digit b
forall a. a -> Digit a
One (b -> Digit b) -> f b -> f (Digit b)
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) = b -> b -> Digit b
forall a. a -> a -> Digit a
Two (b -> b -> Digit b) -> f b -> f (b -> Digit b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> f b
f v
v a
a f (b -> Digit b) -> f b -> f (Digit b)
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 v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
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) = b -> b -> b -> Digit b
forall a. a -> a -> a -> Digit a
Three (b -> b -> b -> Digit b) -> f b -> f (b -> b -> Digit b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> f b
f v
v a
a f (b -> b -> Digit b) -> f b -> f (b -> Digit b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> f b
f v
va a
b f (b -> Digit b) -> f b -> f (Digit 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  v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
        vab :: v
vab = v
va v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
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) = b -> b -> b -> b -> Digit b
forall a. a -> a -> a -> a -> Digit a
Four (b -> b -> b -> b -> Digit b) -> f b -> f (b -> b -> b -> Digit b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> a -> f b
f v
v a
a f (b -> b -> b -> Digit b) -> f b -> f (b -> b -> Digit b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> f b
f v
va a
b f (b -> b -> Digit b) -> f b -> f (b -> Digit b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> f b
f v
vab a
c f (b -> Digit b) -> f b -> f (Digit b)
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   v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
        vab :: v
vab  = v
va  v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
b
        vabc :: v
vabc = v
vab v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
c

-- | 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 :: (a -> f b) -> FingerTree v a -> f (FingerTree v b)
unsafeTraverse a -> f b
_ FingerTree v a
Empty = FingerTree v b -> f (FingerTree v b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure FingerTree v b
forall v a. FingerTree v a
Empty
unsafeTraverse a -> f b
f (Single a
x) = b -> FingerTree v b
forall v a. a -> FingerTree v a
Single (b -> FingerTree v b) -> f b -> f (FingerTree v b)
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) = v
-> Digit b -> FingerTree v (Node v b) -> Digit b -> FingerTree v b
forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep v
v
  (Digit b -> FingerTree v (Node v b) -> Digit b -> FingerTree v b)
-> f (Digit b)
-> f (FingerTree v (Node v b) -> Digit b -> FingerTree v b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> Digit a -> f (Digit b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Digit a -> f (Digit b)
traverseDigit a -> f b
f Digit a
pr
  f (FingerTree v (Node v b) -> Digit b -> FingerTree v b)
-> f (FingerTree v (Node v b)) -> f (Digit b -> FingerTree v b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Node v a -> f (Node v b))
-> FingerTree v (Node v a) -> f (FingerTree v (Node v b))
forall (f :: * -> *) a b v.
Applicative f =>
(a -> f b) -> FingerTree v a -> f (FingerTree v b)
unsafeTraverse ((a -> f b) -> Node v a -> f (Node v b)
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
  f (Digit b -> FingerTree v b) -> f (Digit b) -> f (FingerTree v b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (a -> f b) -> Digit a -> f (Digit 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 :: (a -> f b) -> Node v a -> f (Node v b)
unsafeTraverseNode a -> f b
f (Node2 v
v a
a a
b)   = v -> b -> b -> Node v b
forall v a. v -> a -> a -> Node v a
Node2 v
v (b -> b -> Node v b) -> f b -> f (b -> Node v b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> Node v b) -> f b -> f (Node v b)
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) = v -> b -> b -> b -> Node v b
forall v a. v -> a -> a -> a -> Node v a
Node3 v
v (b -> b -> b -> Node v b) -> f b -> f (b -> b -> Node v b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> b -> Node v b) -> f b -> f (b -> Node v b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
b f (b -> Node v b) -> f b -> f (Node v 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 :: FingerTree v a
empty = FingerTree v a
forall v a. FingerTree v a
Empty

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

-- | /O(n)/. Create a sequence from a finite list of elements.
fromList :: (Measured v a) => [a] -> FingerTree v a
fromList :: [a] -> FingerTree v a
fromList = (a -> FingerTree v a -> FingerTree v a)
-> FingerTree v a -> [a] -> FingerTree v a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
(<|) 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.
instance Measured v a => Cons (FingerTree v a) where
  cons :: Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
cons Elem (FingerTree v a)
a  FingerTree v a
Empty                       = a -> FingerTree v a
forall v a. a -> FingerTree v a
Single a
Elem (FingerTree v a)
a
  cons Elem (FingerTree v a)
a (Single a
b                  ) = Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (a -> Digit a
forall a. a -> Digit a
One a
Elem (FingerTree v a)
a) FingerTree v (Node v a)
forall v a. FingerTree v a
Empty (a -> Digit a
forall a. a -> Digit a
One a
b)
  cons Elem (FingerTree v 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 FingerTree v (Node v a) -> FingerTree v a -> FingerTree v a
`seq` v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (a -> v
forall v a. Measured v a => a -> v
measure a
Elem (FingerTree v a)
a v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
v) (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
Elem (FingerTree v a)
a a
b) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
c a
d a
e Elem (FingerTree v (Node v a))
-> FingerTree v (Node v a) -> FingerTree v (Node v a)
forall v. Cons v => Elem v -> v -> v
<| FingerTree v (Node v a)
m) Digit a
sf
  cons Elem (FingerTree v a)
a (Deep v
v Digit a
pr FingerTree v (Node v a)
m Digit a
sf            ) = v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (a -> v
forall v a. Measured v a => a -> v
measure a
Elem (FingerTree v a)
a v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
v) (a -> Digit a -> Digit a
forall a. a -> Digit a -> Digit a
consDigit a
Elem (FingerTree v a)
a Digit a
pr) FingerTree v (Node v a)
m Digit a
sf
  
consDigit :: a -> Digit a -> Digit a
consDigit :: a -> Digit a -> Digit a
consDigit a
a (One a
b)        = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
consDigit a
a (Two a
b a
c)      = a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
a a
b a
c
consDigit a
a (Three a
b a
c a
d)  = a -> a -> a -> a -> Digit a
forall a. a -> a -> a -> a -> Digit a
Four a
a a
b a
c a
d
consDigit a
_ (Four a
_ a
_ a
_ a
_) = String -> Digit a
forall a. String -> a
illegalArgument 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.
instance Measured v a => Snoc (FingerTree v a) where
  snoc :: FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
snoc  FingerTree v a
Empty                       Elem (FingerTree v a)
a = a -> FingerTree v a
forall v a. a -> FingerTree v a
Single a
Elem (FingerTree v a)
a
  snoc (Single a
a                  ) Elem (FingerTree v a)
b = Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (a -> Digit a
forall a. a -> Digit a
One a
a) FingerTree v (Node v a)
forall v a. FingerTree v a
Empty (a -> Digit a
forall a. a -> Digit a
One a
Elem (FingerTree v a)
b)
  snoc (Deep v
v Digit a
pr FingerTree v (Node v a)
m (Four a
a a
b a
c a
d)) Elem (FingerTree v a)
e = FingerTree v (Node v a)
m FingerTree v (Node v a) -> FingerTree v a -> FingerTree v a
`seq` v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (v
v v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
Elem (FingerTree v a)
e) Digit a
pr (FingerTree v (Node v a)
m FingerTree v (Node v a)
-> Elem (FingerTree v (Node v a)) -> FingerTree v (Node v a)
forall v. Snoc v => v -> Elem v -> v
|> a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
d a
Elem (FingerTree v a)
e)
  snoc (Deep v
v Digit a
pr FingerTree v (Node v a)
m Digit a
sf            ) Elem (FingerTree v a)
x = v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (v
v v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
Elem (FingerTree v a)
x) Digit a
pr FingerTree v (Node v a)
m (Digit a -> a -> Digit a
forall a. Digit a -> a -> Digit a
snocDigit Digit a
sf a
Elem (FingerTree v a)
x)
  

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

-- | /O(1)/. Is this the empty sequence?
null :: (Measured v a) => FingerTree v a -> Bool
null :: 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 :: FingerTree v a -> ViewL (FingerTree v) a
viewl FingerTree v a
Empty                 =  ViewL (FingerTree v) a
forall (s :: * -> *) a. ViewL s a
EmptyL
viewl (Single a
x)            =  a
x a -> FingerTree v a -> ViewL (FingerTree v) a
forall (s :: * -> *) a. a -> s a -> ViewL s a
:< FingerTree v 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 a -> FingerTree v a -> ViewL (FingerTree v) a
forall (s :: * -> *) a. a -> s a -> ViewL s a
:< FingerTree v (Node v a) -> Digit a -> FingerTree v 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)      =  Digit a -> a
forall a. Digit a -> a
lheadDigit Digit a
pr a -> FingerTree v a -> ViewL (FingerTree v) a
forall (s :: * -> *) a. a -> s a -> ViewL s a
:< Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (Digit a -> Digit a
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 :: FingerTree v (Node v a) -> Digit a -> FingerTree v a
rotL FingerTree v (Node v a)
m Digit a
sf = case FingerTree v (Node v a) -> ViewL (FingerTree v) (Node v a)
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  -> Digit a -> FingerTree v a
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' -> v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (FingerTree v (Node v a) -> v
forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` Digit a -> v
forall v a. Measured v a => a -> v
measure Digit a
sf) (Node v a -> Digit a
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 :: 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 :: Digit a -> Digit a
ltailDigit (One a
_)        = String -> Digit a
forall a. String -> a
illegalArgument String
"ltailDigit"
ltailDigit (Two a
_ a
b)      = a -> Digit a
forall a. a -> Digit a
One a
b
ltailDigit (Three a
_ a
b a
c)  = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
b a
c
ltailDigit (Four a
_ a
b a
c a
d) = a -> a -> a -> Digit a
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 :: FingerTree v a -> ViewR (FingerTree v) a
viewr FingerTree v a
Empty                 =  ViewR (FingerTree v) a
forall (s :: * -> *) a. ViewR s a
EmptyR
viewr (Single a
x)            =  FingerTree v a
forall v a. FingerTree v a
Empty FingerTree v a -> a -> ViewR (FingerTree v) a
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)) =  Digit a -> FingerTree v (Node v a) -> FingerTree v a
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 FingerTree v a -> a -> ViewR (FingerTree v) a
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)      =  Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
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 -> Digit a
forall a. Digit a -> Digit a
rtailDigit Digit a
sf) FingerTree v a -> a -> ViewR (FingerTree v) a
forall (s :: * -> *) a. s a -> a -> ViewR s a
:> Digit a -> 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 :: Digit a -> FingerTree v (Node v a) -> FingerTree v a
rotR Digit a
pr FingerTree v (Node v a)
m = case FingerTree v (Node v a) -> ViewR (FingerTree v) (Node v a)
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  -> Digit a -> FingerTree v a
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 -> v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
v
-> Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
Deep (Digit a -> v
forall v a. Measured v a => a -> v
measure Digit a
pr v -> FingerTree v (Node v a) -> v
forall v a. Measured v a => v -> FingerTree v a -> v
`mappendVal` FingerTree v (Node v a)
m) Digit a
pr FingerTree v (Node v a)
m' (Node v a -> Digit a
forall v a. Node v a -> Digit a
nodeToDigit Node v a
a)

rheadDigit :: Digit a -> a
rheadDigit :: 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 :: Digit a -> Digit a
rtailDigit (One a
_)        = String -> Digit a
forall a. String -> a
illegalArgument String
"rtailDigit"
rtailDigit (Two a
a a
_)      = a -> Digit a
forall a. a -> Digit a
One a
a
rtailDigit (Three a
a a
b a
_)  = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
rtailDigit (Four a
a a
b a
c a
_) = a -> a -> a -> Digit 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 :: Digit a -> FingerTree v a
digitToTree (One a
a)        = a -> FingerTree v a
forall v a. a -> FingerTree v a
Single a
a
digitToTree (Two a
a a
b)      = Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (a -> Digit a
forall a. a -> Digit a
One a
a) FingerTree v (Node v a)
forall v a. FingerTree v a
Empty (a -> Digit a
forall a. a -> Digit a
One a
b)
digitToTree (Three a
a a
b a
c)  = Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b) FingerTree v (Node v a)
forall v a. FingerTree v a
Empty (a -> Digit a
forall a. a -> Digit a
One a
c)
digitToTree (Four a
a a
b a
c a
d) = Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b) FingerTree v (Node v a)
forall v a. FingerTree v a
Empty (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
c a
d)

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

-- | /O(log(min(n1,n2)))/. Concatenate two sequences.
append :: (Measured v a) => FingerTree v a -> FingerTree v a -> FingerTree v a
append :: FingerTree v a -> FingerTree v a -> FingerTree v a
append =  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 :: 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
Elem (FingerTree v a)
x Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| FingerTree v a
xs
appendTree0 FingerTree v a
xs (Single a
x)                           = FingerTree v a
xs FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v 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) = Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr1 (FingerTree v (Node v a)
-> Digit a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 :: 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 = FingerTree v (Node v a)
-> Node v a -> FingerTree v (Node v a) -> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 FingerTree v (Node v a)
m1 (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a -> FingerTree v (Node v a) -> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a -> FingerTree v (Node v a) -> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 :: FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 FingerTree v a
Empty a
a FingerTree v a
xs                                = a
Elem (FingerTree v a)
a Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| FingerTree v a
xs
appendTree1 FingerTree v a
xs a
a FingerTree v a
Empty                                = FingerTree v a
xs FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
a
appendTree1 (Single a
x) a
a FingerTree v a
xs                           = a
Elem (FingerTree v a)
x Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
a Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| FingerTree v a
xs
appendTree1 FingerTree v a
xs a
a (Single a
x)                           = FingerTree v a
xs FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
a FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v 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) = Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr1 (FingerTree v (Node v a)
-> Digit a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 :: 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 = FingerTree v (Node v a)
-> Node v a -> FingerTree v (Node v a) -> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> FingerTree v a -> FingerTree v a
appendTree1 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
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 :: 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
Elem (FingerTree v a)
a Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
b Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| FingerTree v a
xs
appendTree2 FingerTree v a
xs a
a a
b FingerTree v a
Empty                                = FingerTree v a
xs FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
a FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
b
appendTree2 (Single a
x) a
a a
b FingerTree v a
xs                           = a
Elem (FingerTree v a)
x Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
a Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
b Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| FingerTree v a
xs
appendTree2 FingerTree v a
xs a
a a
b (Single a
x)                           = FingerTree v a
xs FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
a FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
b FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v 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) = Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr1 (FingerTree v (Node v a)
-> Digit a
-> a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 :: 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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
a a
b  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h  ) (a -> a -> Node v a
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 :: 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
Elem (FingerTree v a)
a Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
b Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
c Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| FingerTree v a
xs
appendTree3 FingerTree v a
xs a
a a
b a
c FingerTree v a
Empty                                = FingerTree v a
xs FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
a FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
b FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
c
appendTree3 (Single a
x) a
a a
b a
c FingerTree v a
xs                           = a
Elem (FingerTree v a)
x Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
a Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
b Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
c Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| FingerTree v a
xs
appendTree3 FingerTree v a
xs a
a a
b a
c (Single a
x)                           = FingerTree v a
xs FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
a FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
b FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
c FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v 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) = Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr1 (FingerTree v (Node v a)
-> Digit a
-> a
-> a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 :: 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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) (a -> a -> Node v a
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 :: 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
Elem (FingerTree v a)
a Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
b Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
c Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
d Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| 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 FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
a FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
b FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
c FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
d
appendTree4 (Single a
x) a
a a
b a
c a
d FingerTree v a
xs                           = a
Elem (FingerTree v a)
x Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
a Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
b Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
c Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| a
Elem (FingerTree v a)
d Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| FingerTree v a
xs
appendTree4 FingerTree v a
xs a
a a
b a
c a
d (Single a
x)                           = FingerTree v a
xs FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
a FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
b FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
c FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v a)
d FingerTree v a -> Elem (FingerTree v a) -> FingerTree v a
forall v. Snoc v => v -> Elem v -> v
|> a
Elem (FingerTree v 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) = Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep Digit a
pr1 (FingerTree v (Node v a)
-> Digit a
-> a
-> a
-> a
-> a
-> Digit a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 :: 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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
forall v a.
Measured v a =>
FingerTree v a -> a -> a -> FingerTree v a -> FingerTree v a
appendTree2 FingerTree v (Node v a)
m1 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
d a
e  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> Node v a
forall v a. Measured v a => a -> a -> Node v a
node2 a
g a
h  ) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) (a -> a -> Node v a
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 = FingerTree v (Node v a)
-> Node v a
-> Node v a
-> Node v a
-> Node v a
-> FingerTree v (Node v a)
-> FingerTree v (Node v a)
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 (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
a a
b a
c) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
d a
e a
f) (a -> a -> a -> Node v a
forall v a. Measured v a => a -> a -> a -> Node v a
node3 a
g a
h a
i) (a -> a -> a -> Node v a
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
----------------

-- | /O(log(min(i,n-i)))/. Split a sequence at a point where the predicate
-- on the accumulated measure 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 :: (v -> Bool) -> FingerTree v a -> (FingerTree v a, FingerTree v a)
split v -> Bool
_ FingerTree v a
Empty  =  (FingerTree v a
forall v a. FingerTree v a
Empty, FingerTree v a
forall v a. FingerTree v a
Empty)
split v -> Bool
p FingerTree v a
xs
  | v -> Bool
p (FingerTree v a -> v
forall v a. Measured v a => a -> v
measure FingerTree v a
xs)  =  (FingerTree v a
l, a
Elem (FingerTree v a)
x Elem (FingerTree v a) -> FingerTree v a -> FingerTree v a
forall v. Cons v => Elem v -> v -> v
<| FingerTree v a
r)
  | Bool
otherwise       =  (FingerTree v a
xs, FingerTree v a
forall v a. FingerTree v a
Empty)
  where Split FingerTree v a
l a
x FingerTree v a
r = (v -> Bool) -> v -> FingerTree v a -> Split (FingerTree v a) a
forall v a.
Measured v a =>
(v -> Bool) -> v -> FingerTree v a -> Split (FingerTree v a) a
splitTree v -> Bool
p v
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 :: (v -> Bool) -> FingerTree v a -> FingerTree v a
takeUntil v -> Bool
p  =  (FingerTree v a, FingerTree v a) -> FingerTree v a
forall a b. (a, b) -> a
fst ((FingerTree v a, FingerTree v a) -> FingerTree v a)
-> (FingerTree v a -> (FingerTree v a, FingerTree v a))
-> FingerTree v a
-> FingerTree v a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (v -> Bool) -> FingerTree v a -> (FingerTree v a, FingerTree v a)
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 :: (v -> Bool) -> FingerTree v a -> FingerTree v a
dropUntil v -> Bool
p  =  (FingerTree v a, FingerTree v a) -> FingerTree v a
forall a b. (a, b) -> b
snd ((FingerTree v a, FingerTree v a) -> FingerTree v a)
-> (FingerTree v a -> (FingerTree v a, FingerTree v a))
-> FingerTree v a
-> FingerTree v a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (v -> Bool) -> FingerTree v a -> (FingerTree v a, FingerTree v a)
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 :: (v -> Bool) -> v -> FingerTree v a -> Split (FingerTree v a) a
splitTree v -> Bool
_ v
_ FingerTree v a
Empty = String -> Split (FingerTree v a) a
forall a. String -> a
illegalArgument String
"splitTree"
splitTree v -> Bool
_ v
_ (Single a
x) = FingerTree v a -> a -> FingerTree v a -> Split (FingerTree v a) a
forall t a. t -> a -> t -> Split t a
Split FingerTree v a
forall v a. FingerTree v a
Empty a
x FingerTree v a
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       =  let  Split Maybe (Digit a)
l a
x Maybe (Digit a)
r     =  (v -> Bool) -> v -> Digit a -> Split (Maybe (Digit a)) a
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
                   in   FingerTree v a -> a -> FingerTree v a -> Split (FingerTree v a) a
forall t a. t -> a -> t -> Split t a
Split (FingerTree v a
-> (Digit a -> FingerTree v a) -> Maybe (Digit a) -> FingerTree v a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FingerTree v a
forall v a. FingerTree v a
Empty Digit a -> FingerTree v a
forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree Maybe (Digit a)
l) a
x (Maybe (Digit a)
-> FingerTree v (Node v a) -> Digit a -> FingerTree v a
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        =  let  Split FingerTree v (Node v a)
ml Node v a
xs FingerTree v (Node v a)
mr  =  (v -> Bool)
-> v
-> FingerTree v (Node v a)
-> Split (FingerTree v (Node v a)) (Node v a)
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
                        Split Maybe (Digit a)
l a
x Maybe (Digit a)
r     =  (v -> Bool) -> v -> Node v a -> Split (Maybe (Digit a)) a
forall v a.
Measured v a =>
(v -> Bool) -> v -> Node v a -> Split (Maybe (Digit a)) a
splitNode v -> Bool
p (v
vpr v -> FingerTree v (Node v a) -> v
forall v a. Measured v a => v -> FingerTree v a -> v
`mappendVal` FingerTree v (Node v a)
ml) Node v a
xs
                   in   FingerTree v a -> a -> FingerTree v a -> Split (FingerTree v a) a
forall t a. t -> a -> t -> Split t a
Split (Digit a
-> FingerTree v (Node v a) -> Maybe (Digit a) -> FingerTree v a
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 (Maybe (Digit a)
-> FingerTree v (Node v a) -> Digit a -> FingerTree v a
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   =  let  Split Maybe (Digit a)
l a
x Maybe (Digit a)
r     =  (v -> Bool) -> v -> Digit a -> Split (Maybe (Digit a)) a
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
                   in   FingerTree v a -> a -> FingerTree v a -> Split (FingerTree v a) a
forall t a. t -> a -> t -> Split t a
Split (Digit a
-> FingerTree v (Node v a) -> Maybe (Digit a) -> FingerTree v a
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 (FingerTree v a
-> (Digit a -> FingerTree v a) -> Maybe (Digit a) -> FingerTree v a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FingerTree v a
forall v a. FingerTree v a
Empty Digit a -> FingerTree v a
forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree Maybe (Digit a)
r)
  where vpr :: v
vpr =  v
i    v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend`  Digit a -> v
forall v a. Measured v a => a -> v
measure Digit a
pr
        vm :: v
vm  =  v
vpr  v -> FingerTree v (Node v a) -> v
forall v a. Measured v a => v -> FingerTree v a -> v
`mappendVal` FingerTree v (Node v a)
m

-- Avoid relying on right identity (cf Exercise 7)
mappendVal :: (Measured v a) => v -> FingerTree v a -> v
mappendVal :: v -> FingerTree v a -> v
mappendVal v
v FingerTree v a
Empty = v
v
mappendVal v
v FingerTree v a
t     = v
v v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` FingerTree v a -> v
forall v a. Measured v a => a -> v
measure FingerTree v a
t

deepL :: (Measured v a) => Maybe (Digit a) -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deepL :: 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   =   FingerTree v (Node v a) -> Digit a -> FingerTree v 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
deepL (Just Digit a
pr) FingerTree v (Node v a)
m Digit a
sf =   Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
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 :: 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   =   Digit a -> FingerTree v (Node v a) -> FingerTree v a
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) =   Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
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 :: (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      = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split Maybe (Digit a)
forall a. Maybe a
Nothing a
a (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> Digit a
forall a. a -> Digit a
One a
b))
  | Bool
otherwise = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> Digit a
forall a. a -> Digit a
One a
a)) a
b Maybe (Digit a)
forall a. Maybe a
Nothing
  where va :: v
va = v
i v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
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      = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split Maybe (Digit a)
forall a. Maybe a
Nothing a
a (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
b a
c))
  | v -> Bool
p v
vab     = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> Digit a
forall a. a -> Digit a
One a
a)) a
b (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> Digit a
forall a. a -> Digit a
One a
c))
  | Bool
otherwise = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b)) a
c Maybe (Digit a)
forall a. Maybe a
Nothing
  where va :: v
va  = v
i  v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
        vab :: v
vab = v
va v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
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 :: (v -> Bool) -> v -> Digit a -> Split (Maybe (Digit a)) a
splitDigit v -> Bool
_ v
i (One a
a) = v
i v -> Split (Maybe (Digit a)) a -> Split (Maybe (Digit a)) a
`seq` Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split Maybe (Digit a)
forall a. Maybe a
Nothing a
a Maybe (Digit a)
forall a. Maybe a
Nothing
splitDigit v -> Bool
p v
i (Two a
a a
b)
  | v -> Bool
p v
va        = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split Maybe (Digit a)
forall a. Maybe a
Nothing a
a (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> Digit a
forall a. a -> Digit a
One a
b))
  | Bool
otherwise   = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> Digit a
forall a. a -> Digit a
One a
a)) a
b Maybe (Digit a)
forall a. Maybe a
Nothing
  where va :: v
va = v
i v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
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        = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split Maybe (Digit a)
forall a. Maybe a
Nothing a
a (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
b a
c))
  | v -> Bool
p v
vab       = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> Digit a
forall a. a -> Digit a
One a
a)) a
b (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> Digit a
forall a. a -> Digit a
One a
c))
  | Bool
otherwise   = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b)) a
c Maybe (Digit a)
forall a. Maybe a
Nothing
  where va :: v
va  = v
i v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
        vab :: v
vab = v
va v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
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        = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split Maybe (Digit a)
forall a. Maybe a
Nothing a
a (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
b a
c a
d))
  | v -> Bool
p v
vab       = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> Digit a
forall a. a -> Digit a
One a
a)) a
b (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
c a
d))
  | v -> Bool
p v
vabc      = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b)) a
c (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> Digit a
forall a. a -> Digit a
One a
d))
  | Bool
otherwise   = Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> Maybe (Digit a)
forall a. a -> Maybe a
Just (a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
a a
b a
c)) a
d Maybe (Digit a)
forall a. Maybe a
Nothing
  where va :: v
va    = v
i v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
        vab :: v
vab   = v
va v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
b
        vabc :: v
vabc  = v
vab v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
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 :: FingerTree v a -> FingerTree v a
reverse = (a -> a) -> FingerTree v a -> FingerTree v a
forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
reverseTree a -> a
forall a. a -> a
id

reverseTree :: (Measured v2 a2) => (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
reverseTree :: (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
reverseTree a1 -> a2
_ FingerTree v1 a1
Empty            = FingerTree v2 a2
forall v a. FingerTree v a
Empty
reverseTree a1 -> a2
f (Single a1
x)       = a2 -> FingerTree v2 a2
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) = Digit a2
-> FingerTree v2 (Node v2 a2) -> Digit a2 -> FingerTree v2 a2
forall v a.
Measured v a =>
Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deep ((a1 -> a2) -> Digit a1 -> Digit a2
forall a b. (a -> b) -> Digit a -> Digit b
reverseDigit a1 -> a2
f Digit a1
sf) ((Node v1 a1 -> Node v2 a2)
-> FingerTree v1 (Node v1 a1) -> FingerTree v2 (Node v2 a2)
forall v2 a2 a1 v1.
Measured v2 a2 =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
reverseTree ((a1 -> a2) -> Node v1 a1 -> Node v2 a2
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) ((a1 -> a2) -> Digit a1 -> Digit a2
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 :: (a1 -> a2) -> Node v1 a1 -> Node v2 a2
reverseNode a1 -> a2
f (Node2 v1
_ a1
a a1
b)   = a2 -> a2 -> Node v2 a2
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) = a2 -> a2 -> a2 -> Node v2 a2
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 :: (a -> b) -> Digit a -> Digit b
reverseDigit a -> b
f (One a
a)        = b -> Digit b
forall a. a -> Digit a
One (a -> b
f a
a)
reverseDigit a -> b
f (Two a
a a
b)      = b -> b -> Digit 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)  = b -> b -> b -> Digit b
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) = b -> b -> b -> b -> Digit b
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)

illegalArgument :: String -> a
illegalArgument :: String -> a
illegalArgument String
name = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"Logic error: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name String -> ShowS
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 '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".

-}