{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Safe #-}
#endif
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE DeriveGeneric #-}
#endif
#if __GLASGOW_HASKELL__ >= 710
{-# LANGUAGE AutoDeriveTypeable #-}
#endif
module Data.FingerTree (
#if TESTING
FingerTree(..), Digit(..), Node(..), deep, node2, node3,
#else
FingerTree,
#endif
Measured(..),
empty, singleton,
(<|), (|>), (><),
fromList,
null,
ViewL(..), viewl,
ViewR(..), viewr,
SearchResult(..), search,
split, takeUntil, dropUntil,
reverse,
fmap', fmapWithPos, fmapWithContext, unsafeFmap,
traverse', traverseWithPos, traverseWithContext, unsafeTraverse,
) where
import Prelude hiding (null, reverse)
#if MIN_VERSION_base(4,6,0)
import GHC.Generics
#endif
#if MIN_VERSION_base(4,8,0)
import qualified Prelude (null)
#else
import Control.Applicative (Applicative(pure, (<*>)), (<$>))
import Data.Monoid
import Data.Foldable (Foldable(foldMap))
#endif
#if (MIN_VERSION_base(4,9,0)) && !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
import Data.Foldable (toList)
infixr 5 ><
infixr 5 <|, :<
infixl 5 |>, :>
data ViewL s a
= EmptyL
| a :< s a
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
#if __GLASGOW_HASKELL__ >= 706
, (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
#endif
)
data ViewR s a
= EmptyR
| s a :> a
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
#if __GLASGOW_HASKELL__ >= 706
, (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
#endif
)
instance (Functor s) => Functor (ViewL s) where
fmap :: (a -> b) -> ViewL s a -> ViewL s b
fmap _ EmptyL = ViewL s b
forall (s :: * -> *) a. ViewL s a
EmptyL
fmap f :: a -> b
f (x :: a
x :< xs :: 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 _ EmptyR = ViewR s b
forall (s :: * -> *) a. ViewR s a
EmptyR
fmap f :: a -> b
f (xs :: s a
xs :> x :: 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
#if MIN_VERSION_base(4,9,0)
instance (Measured v a) => Semigroup (FingerTree v a) where
<> :: FingerTree v a -> FingerTree v a -> FingerTree v a
(<>) = FingerTree v a -> FingerTree v a -> FingerTree v a
forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
(><)
#endif
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
#if !(MIN_VERSION_base(4,11,0))
mappend = (><)
#endif
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
#if __GLASGOW_HASKELL__ >= 706
, (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
#endif
)
instance Foldable Digit where
foldMap :: (a -> m) -> Digit a -> m
foldMap f :: a -> m
f (One a :: a
a) = a -> m
f a
a
foldMap f :: a -> m
f (Two a :: a
a b :: a
b) = a -> m
f a
a m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b
foldMap f :: a -> m
f (Three a :: a
a b :: a
b c :: 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 f :: a -> m
f (Four a :: a
a b :: a
b c :: a
c d :: 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
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
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
#if __GLASGOW_HASKELL__ >= 706
, (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
#endif
)
instance Foldable (Node v) where
foldMap :: (a -> m) -> Node v a -> m
foldMap f :: a -> m
f (Node2 _ a :: a
a b :: a
b) = a -> m
f a
a m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
b
foldMap f :: a -> m
f (Node3 _ a :: a
a b :: a
b c :: 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 :: 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
b c :: 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
v _ _) = v
v
measure (Node3 v :: v
v _ _ _) = v
v
nodeToDigit :: Node v a -> Digit a
nodeToDigit :: Node v a -> Digit a
nodeToDigit (Node2 _ a :: a
a b :: a
b) = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
nodeToDigit (Node3 _ a :: a
a b :: a
b c :: a
c) = a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
a a
b a
c
data FingerTree v a
= Empty
| Single a
| Deep !v !(Digit a) (FingerTree v (Node v a)) !(Digit a)
#if TESTING
deriving (Show
#if __GLASGOW_HASKELL__ >= 706
, Generic
#endif
)
#elif __GLASGOW_HASKELL__ >= 706
deriving ((forall 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)
#endif
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 pr :: Digit a
pr m :: FingerTree v (Node v a)
m sf :: 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 -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` 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) Digit a
pr FingerTree v (Node v a)
m Digit a
sf
instance (Measured v a) => Measured v (FingerTree v a) where
measure :: FingerTree v a -> v
measure Empty = v
forall a. Monoid a => a
mempty
measure (Single x :: a
x) = a -> v
forall v a. Measured v a => a -> v
measure a
x
measure (Deep v :: v
v _ _ _) = v
v
instance Foldable (FingerTree v) where
foldMap :: (a -> m) -> FingerTree v a -> m
foldMap _ Empty = m
forall a. Monoid a => a
mempty
foldMap f :: a -> m
f (Single x :: a
x) = a -> m
f a
x
foldMap f :: a -> m
f (Deep _ pr :: Digit a
pr m :: FingerTree v (Node v a)
m sf :: 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
#if MIN_VERSION_base(4,8,0)
null :: FingerTree v a -> Bool
null Empty = Bool
True
null _ = Bool
False
#endif
instance (Eq a) => Eq (FingerTree v a) where
xs :: FingerTree v a
xs == :: FingerTree v a -> FingerTree v a -> Bool
== ys :: 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 xs :: FingerTree v a
xs ys :: 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)
#if !TESTING
instance (Show a) => Show (FingerTree v a) where
showsPrec :: Int -> FingerTree v a -> ShowS
showsPrec p :: Int
p xs :: FingerTree v a
xs = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString "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)
#endif
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 _ Empty = FingerTree v2 a2
forall v a. FingerTree v a
Empty
mapTree f :: a1 -> a2
f (Single x :: a1
x) = a2 -> FingerTree v2 a2
forall v a. a -> FingerTree v a
Single (a1 -> a2
f a1
x)
mapTree f :: a1 -> a2
f (Deep _ pr :: Digit a1
pr m :: FingerTree v1 (Node v1 a1)
m sf :: 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 f :: a1 -> a2
f (Node2 _ a :: a1
a b :: 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 f :: a1 -> a2
f (Node3 _ a :: a1
a b :: a1
b c :: 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 f :: a -> b
f (One a :: a
a) = b -> Digit b
forall a. a -> Digit a
One (a -> b
f a
a)
mapDigit f :: a -> b
f (Two a :: a
a b :: a
b) = b -> b -> Digit b
forall a. a -> a -> Digit a
Two (a -> b
f a
a) (a -> b
f a
b)
mapDigit f :: a -> b
f (Three a :: a
a b :: a
b c :: 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 f :: a -> b
f (Four a :: a
a b :: a
b c :: a
c d :: 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)
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 f :: 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 _ _ Empty = FingerTree v2 a2
forall v a. FingerTree v a
Empty
mapWPTree f :: v1 -> a1 -> a2
f v :: v1
v (Single x :: a1
x) = a2 -> FingerTree v2 a2
forall v a. a -> FingerTree v a
Single (v1 -> a1 -> a2
f v1
v a1
x)
mapWPTree f :: v1 -> a1 -> a2
f v :: v1
v (Deep _ pr :: Digit a1
pr m :: FingerTree v1 (Node v1 a1)
m sf :: 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 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` FingerTree v1 (Node v1 a1) -> v1
forall v a. Measured v a => a -> v
measure FingerTree v1 (Node v1 a1)
m
mapWPNode :: (Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> a2) -> v1 -> Node v1 a1 -> Node v2 a2
mapWPNode :: (v1 -> a1 -> a2) -> v1 -> Node v1 a1 -> Node v2 a2
mapWPNode f :: v1 -> a1 -> a2
f v :: v1
v (Node2 _ a :: a1
a b :: 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 f :: v1 -> a1 -> a2
f v :: v1
v (Node3 _ a :: a1
a b :: a1
b c :: 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 f :: v -> a -> b
f v :: v
v (One a :: a
a) = b -> Digit b
forall a. a -> Digit a
One (v -> a -> b
f v
v a
a)
mapWPDigit f :: v -> a -> b
f v :: v
v (Two a :: a
a b :: 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 f :: v -> a -> b
f v :: v
v (Three a :: a
a b :: a
b c :: 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 f :: v -> a -> b
f v :: v
v (Four a :: a
a b :: a
b c :: a
c d :: 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
fmapWithContext :: (Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmapWithContext :: (v1 -> a1 -> v1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
fmapWithContext f :: v1 -> a1 -> v1 -> a2
f t :: FingerTree v1 a1
t = (v1 -> a1 -> v1 -> a2)
-> v1 -> FingerTree v1 a1 -> v1 -> FingerTree v2 a2
forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2)
-> v1 -> FingerTree v1 a1 -> v1 -> FingerTree v2 a2
mapWCTree v1 -> a1 -> v1 -> a2
f v1
forall a. Monoid a => a
mempty FingerTree v1 a1
t v1
forall a. Monoid a => a
mempty
mapWCTree :: (Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2) -> v1 -> FingerTree v1 a1 -> v1 -> FingerTree v2 a2
mapWCTree :: (v1 -> a1 -> v1 -> a2)
-> v1 -> FingerTree v1 a1 -> v1 -> FingerTree v2 a2
mapWCTree _ _ Empty _ = FingerTree v2 a2
forall v a. FingerTree v a
Empty
mapWCTree f :: v1 -> a1 -> v1 -> a2
f vl :: v1
vl (Single x :: a1
x) vr :: v1
vr = a2 -> FingerTree v2 a2
forall v a. a -> FingerTree v a
Single (v1 -> a1 -> v1 -> a2
f v1
vl a1
x v1
vr)
mapWCTree f :: v1 -> a1 -> v1 -> a2
f vl :: v1
vl (Deep _ pr :: Digit a1
pr m :: FingerTree v1 (Node v1 a1)
m sf :: Digit a1
sf) vr :: v1
vr =
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 -> v1 -> a2) -> v1 -> Digit a1 -> v1 -> Digit a2
forall v a b.
Measured v a =>
(v -> a -> v -> b) -> v -> Digit a -> v -> Digit b
mapWCDigit v1 -> a1 -> v1 -> a2
f v1
vl Digit a1
pr v1
vmsr)
((v1 -> Node v1 a1 -> v1 -> Node v2 a2)
-> v1
-> FingerTree v1 (Node v1 a1)
-> v1
-> FingerTree v2 (Node v2 a2)
forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2)
-> v1 -> FingerTree v1 a1 -> v1 -> FingerTree v2 a2
mapWCTree ((v1 -> a1 -> v1 -> a2) -> v1 -> Node v1 a1 -> v1 -> Node v2 a2
forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2) -> v1 -> Node v1 a1 -> v1 -> Node v2 a2
mapWCNode v1 -> a1 -> v1 -> a2
f) v1
vlp FingerTree v1 (Node v1 a1)
m v1
vsr)
((v1 -> a1 -> v1 -> a2) -> v1 -> Digit a1 -> v1 -> Digit a2
forall v a b.
Measured v a =>
(v -> a -> v -> b) -> v -> Digit a -> v -> Digit b
mapWCDigit v1 -> a1 -> v1 -> a2
f v1
vlpm Digit a1
sf v1
vr)
where
vlp :: v1
vlp = v1
vl 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
vlpm :: v1
vlpm = v1
vlp v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vm
vmsr :: v1
vmsr = v1
vm v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vsr
vsr :: v1
vsr = Digit a1 -> v1
forall v a. Measured v a => a -> v
measure Digit a1
sf v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vr
vm :: v1
vm = FingerTree v1 (Node v1 a1) -> v1
forall v a. Measured v a => a -> v
measure FingerTree v1 (Node v1 a1)
m
mapWCNode :: (Measured v1 a1, Measured v2 a2) =>
(v1 -> a1 -> v1 -> a2) -> v1 -> Node v1 a1 -> v1 -> Node v2 a2
mapWCNode :: (v1 -> a1 -> v1 -> a2) -> v1 -> Node v1 a1 -> v1 -> Node v2 a2
mapWCNode f :: v1 -> a1 -> v1 -> a2
f vl :: v1
vl (Node2 _ a :: a1
a b :: a1
b) vr :: v1
vr = a2 -> a2 -> Node v2 a2
forall v a. Measured v a => a -> a -> Node v a
node2 (v1 -> a1 -> v1 -> a2
f v1
vl a1
a v1
vb) (v1 -> a1 -> v1 -> a2
f v1
va a1
b v1
vr)
where
va :: v1
va = v1
vl v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` a1 -> v1
forall v a. Measured v a => a -> v
measure a1
a
vb :: v1
vb = a1 -> v1
forall v a. Measured v a => a -> v
measure a1
b v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vr
mapWCNode f :: v1 -> a1 -> v1 -> a2
f vl :: v1
vl (Node3 _ a :: a1
a b :: a1
b c :: a1
c) vr :: v1
vr = a2 -> a2 -> a2 -> Node v2 a2
forall v a. Measured v a => a -> a -> a -> Node v a
node3 (v1 -> a1 -> v1 -> a2
f v1
vl a1
a v1
vbc) (v1 -> a1 -> v1 -> a2
f v1
va a1
b v1
vc) (v1 -> a1 -> v1 -> a2
f v1
vab a1
c v1
vr)
where
va :: v1
va = v1
vl 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
vbc :: v1
vbc = a1 -> v1
forall v a. Measured v a => a -> v
measure a1
b v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vc
vc :: v1
vc = a1 -> v1
forall v a. Measured v a => a -> v
measure a1
c v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vr
mapWCDigit ::
(Measured v a) => (v -> a -> v -> b) -> v -> Digit a -> v -> Digit b
mapWCDigit :: (v -> a -> v -> b) -> v -> Digit a -> v -> Digit b
mapWCDigit f :: v -> a -> v -> b
f vl :: v
vl (One a :: a
a) vr :: v
vr = b -> Digit b
forall a. a -> Digit a
One (v -> a -> v -> b
f v
vl a
a v
vr)
mapWCDigit f :: v -> a -> v -> b
f vl :: v
vl (Two a :: a
a b :: a
b) vr :: v
vr = b -> b -> Digit b
forall a. a -> a -> Digit a
Two (v -> a -> v -> b
f v
vl a
a v
vb) (v -> a -> v -> b
f v
va a
b v
vr)
where
va :: v
va = v
vl v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
vb :: v
vb = a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
mapWCDigit f :: v -> a -> v -> b
f vl :: v
vl (Three a :: a
a b :: a
b c :: a
c) vr :: v
vr = b -> b -> b -> Digit b
forall a. a -> a -> a -> Digit a
Three (v -> a -> v -> b
f v
vl a
a v
vbc) (v -> a -> v -> b
f v
va a
b v
vc) (v -> a -> v -> b
f v
vab a
c v
vr)
where
va :: v
va = v
vl 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
vbc :: v
vbc = a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vc
vc :: v
vc = a -> v
forall v a. Measured v a => a -> v
measure a
c v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
mapWCDigit f :: v -> a -> v -> b
f vl :: v
vl (Four a :: a
a b :: a
b c :: a
c d :: a
d) vr :: v
vr =
b -> b -> b -> b -> Digit b
forall a. a -> a -> a -> a -> Digit a
Four (v -> a -> v -> b
f v
vl a
a v
vbcd) (v -> a -> v -> b
f v
va a
b v
vcd) (v -> a -> v -> b
f v
vab a
c v
vd) (v -> a -> v -> b
f v
vabc a
d v
vr)
where
va :: v
va = v
vl 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
vbcd :: v
vbcd = a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vcd
vcd :: v
vcd = a -> v
forall v a. Measured v a => a -> v
measure a
c v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vd
vd :: v
vd = a -> v
forall v a. Measured v a => a -> v
measure a
d v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
unsafeFmap :: (a -> b) -> FingerTree v a -> FingerTree v b
unsafeFmap :: (a -> b) -> FingerTree v a -> FingerTree v b
unsafeFmap _ Empty = FingerTree v b
forall v a. FingerTree v a
Empty
unsafeFmap f :: a -> b
f (Single x :: a
x) = b -> FingerTree v b
forall v a. a -> FingerTree v a
Single (a -> b
f a
x)
unsafeFmap f :: a -> b
f (Deep v :: v
v pr :: Digit a
pr m :: FingerTree v (Node v a)
m sf :: 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 f :: a -> b
f (Node2 v :: v
v a :: a
a b :: 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 f :: a -> b
f (Node3 v :: v
v a :: a
a b :: a
b c :: 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)
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 _ 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 f :: a1 -> f a2
f (Single x :: 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 f :: a1 -> f a2
f (Deep _ pr :: Digit a1
pr m :: FingerTree v1 (Node v1 a1)
m sf :: 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 f :: a1 -> f a2
f (Node2 _ a :: a1
a b :: 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 f :: a1 -> f a2
f (Node3 _ a :: a1
a b :: a1
b c :: 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 f :: a -> f b
f (One a :: 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 f :: a -> f b
f (Two a :: a
a b :: 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 f :: a -> f b
f (Three a :: a
a b :: a
b c :: 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 f :: a -> f b
f (Four a :: a
a b :: a
b c :: a
c d :: 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
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 f :: 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 _ _ 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 f :: v1 -> a1 -> f a2
f v :: v1
v (Single x :: 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 f :: v1 -> a1 -> f a2
f v :: v1
v (Deep _ pr :: Digit a1
pr m :: FingerTree v1 (Node v1 a1)
m sf :: 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 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` FingerTree v1 (Node v1 a1) -> v1
forall v a. Measured v a => a -> v
measure FingerTree v1 (Node v1 a1)
m
traverseWPNode :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> f a2) -> v1 -> Node v1 a1 -> f (Node v2 a2)
traverseWPNode :: (v1 -> a1 -> f a2) -> v1 -> Node v1 a1 -> f (Node v2 a2)
traverseWPNode f :: v1 -> a1 -> f a2
f v :: v1
v (Node2 _ a :: a1
a b :: 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 f :: v1 -> a1 -> f a2
f v :: v1
v (Node3 _ a :: a1
a b :: a1
b c :: 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 f :: v -> a -> f b
f v :: v
v (One a :: 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 f :: v -> a -> f b
f v :: v
v (Two a :: a
a b :: 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 f :: v -> a -> f b
f v :: v
v (Three a :: a
a b :: a
b c :: 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 f :: v -> a -> f b
f v :: v
v (Four a :: a
a b :: a
b c :: a
c d :: 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
traverseWithContext :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWithContext :: (v1 -> a1 -> v1 -> f a2)
-> FingerTree v1 a1 -> f (FingerTree v2 a2)
traverseWithContext f :: v1 -> a1 -> v1 -> f a2
f t :: FingerTree v1 a1
t = (v1 -> a1 -> v1 -> f a2)
-> v1 -> FingerTree v1 a1 -> v1 -> f (FingerTree v2 a2)
forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2)
-> v1 -> FingerTree v1 a1 -> v1 -> f (FingerTree v2 a2)
traverseWCTree v1 -> a1 -> v1 -> f a2
f v1
forall a. Monoid a => a
mempty FingerTree v1 a1
t v1
forall a. Monoid a => a
mempty
traverseWCTree :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2) -> v1 -> FingerTree v1 a1 -> v1 -> f (FingerTree v2 a2)
traverseWCTree :: (v1 -> a1 -> v1 -> f a2)
-> v1 -> FingerTree v1 a1 -> v1 -> f (FingerTree v2 a2)
traverseWCTree _ _ 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
traverseWCTree f :: v1 -> a1 -> v1 -> f a2
f vl :: v1
vl (Single x :: a1
x) vr :: v1
vr = 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 -> v1 -> f a2
f v1
vl a1
x v1
vr
traverseWCTree f :: v1 -> a1 -> v1 -> f a2
f vl :: v1
vl (Deep _ pr :: Digit a1
pr m :: FingerTree v1 (Node v1 a1)
m sf :: Digit a1
sf) vr :: v1
vr =
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 -> v1 -> f a2) -> v1 -> Digit a1 -> v1 -> f (Digit a2)
forall v a (f :: * -> *) b.
(Measured v a, Applicative f) =>
(v -> a -> v -> f b) -> v -> Digit a -> v -> f (Digit b)
traverseWCDigit v1 -> a1 -> v1 -> f a2
f v1
vl Digit a1
pr v1
vmsr 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 -> v1 -> f (Node v2 a2))
-> v1
-> FingerTree v1 (Node v1 a1)
-> v1
-> f (FingerTree v2 (Node v2 a2))
forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2)
-> v1 -> FingerTree v1 a1 -> v1 -> f (FingerTree v2 a2)
traverseWCTree ((v1 -> a1 -> v1 -> f a2)
-> v1 -> Node v1 a1 -> v1 -> f (Node v2 a2)
forall v1 a1 v2 a2 (f :: * -> *).
(Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2)
-> v1 -> Node v1 a1 -> v1 -> f (Node v2 a2)
traverseWCNode v1 -> a1 -> v1 -> f a2
f) v1
vlp FingerTree v1 (Node v1 a1)
m v1
vsr 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 -> v1 -> f a2) -> v1 -> Digit a1 -> v1 -> f (Digit a2)
forall v a (f :: * -> *) b.
(Measured v a, Applicative f) =>
(v -> a -> v -> f b) -> v -> Digit a -> v -> f (Digit b)
traverseWCDigit v1 -> a1 -> v1 -> f a2
f v1
vlpm Digit a1
sf v1
vr
where
vlp :: v1
vlp = v1
vl 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
vlpm :: v1
vlpm = v1
vlp v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vm
vmsr :: v1
vmsr = v1
vm v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vsr
vsr :: v1
vsr = Digit a1 -> v1
forall v a. Measured v a => a -> v
measure Digit a1
sf v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vr
vm :: v1
vm = FingerTree v1 (Node v1 a1) -> v1
forall v a. Measured v a => a -> v
measure FingerTree v1 (Node v1 a1)
m
traverseWCNode :: (Measured v1 a1, Measured v2 a2, Applicative f) =>
(v1 -> a1 -> v1 -> f a2) -> v1 -> Node v1 a1 -> v1 -> f (Node v2 a2)
traverseWCNode :: (v1 -> a1 -> v1 -> f a2)
-> v1 -> Node v1 a1 -> v1 -> f (Node v2 a2)
traverseWCNode f :: v1 -> a1 -> v1 -> f a2
f vl :: v1
vl (Node2 _ a :: a1
a b :: a1
b) vr :: v1
vr = 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 -> v1 -> f a2
f v1
vl a1
a v1
vb 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 -> v1 -> f a2
f v1
va a1
b v1
vr
where
va :: v1
va = v1
vl v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` a1 -> v1
forall v a. Measured v a => a -> v
measure a1
a
vb :: v1
vb = a1 -> v1
forall v a. Measured v a => a -> v
measure a1
a v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vr
traverseWCNode f :: v1 -> a1 -> v1 -> f a2
f vl :: v1
vl (Node3 _ a :: a1
a b :: a1
b c :: a1
c) vr :: v1
vr =
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 -> v1 -> f a2
f v1
vl a1
a v1
vbc 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 -> v1 -> f a2
f v1
va a1
b v1
vc 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 -> v1 -> f a2
f v1
vab a1
c v1
vr
where
va :: v1
va = v1
vl 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
vc :: v1
vc = a1 -> v1
forall v a. Measured v a => a -> v
measure a1
c v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vr
vbc :: v1
vbc = a1 -> v1
forall v a. Measured v a => a -> v
measure a1
b v1 -> v1 -> v1
forall a. Monoid a => a -> a -> a
`mappend` v1
vc
traverseWCDigit :: (Measured v a, Applicative f) =>
(v -> a -> v -> f b) -> v -> Digit a -> v -> f (Digit b)
traverseWCDigit :: (v -> a -> v -> f b) -> v -> Digit a -> v -> f (Digit b)
traverseWCDigit f :: v -> a -> v -> f b
f vl :: v
vl (One a :: a
a) vr :: v
vr = 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 -> v -> f b
f v
vl a
a v
vr
traverseWCDigit f :: v -> a -> v -> f b
f vl :: v
vl (Two a :: a
a b :: a
b) vr :: v
vr = 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 -> v -> f b
f v
vl a
a v
vb f (b -> Digit b) -> f b -> f (Digit b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> v -> f b
f v
va a
b v
vr
where
va :: v
va = v
vl v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
vb :: v
vb = a -> v
forall v a. Measured v a => a -> v
measure a
a v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
traverseWCDigit f :: v -> a -> v -> f b
f vl :: v
vl (Three a :: a
a b :: a
b c :: a
c) vr :: v
vr =
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 -> v -> f b
f v
vl a
a v
vbc 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 -> v -> f b
f v
va a
b v
vc f (b -> Digit b) -> f b -> f (Digit b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> v -> f b
f v
vab a
c v
vr
where
va :: v
va = v
vl 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
vc :: v
vc = a -> v
forall v a. Measured v a => a -> v
measure a
c v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
vbc :: v
vbc = a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vc
traverseWCDigit f :: v -> a -> v -> f b
f vl :: v
vl (Four a :: a
a b :: a
b c :: a
c d :: a
d) vr :: v
vr =
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 -> v -> f b
f v
vl a
a v
vbcd 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 -> v -> f b
f v
va a
b v
vcd 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 -> v -> f b
f v
vab a
c v
vd f (b -> Digit b) -> f b -> f (Digit b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> v -> a -> v -> f b
f v
vabc a
d v
vr
where
va :: v
va = v
vl 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
vd :: v
vd = a -> v
forall v a. Measured v a => a -> v
measure a
d v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
vcd :: v
vcd = a -> v
forall v a. Measured v a => a -> v
measure a
c v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vd
vbcd :: v
vbcd = a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vcd
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 _ 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 f :: a -> f b
f (Single x :: 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 f :: a -> f b
f (Deep v :: v
v pr :: Digit a
pr m :: FingerTree v (Node v a)
m sf :: 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 f :: a -> f b
f (Node2 v :: v
v a :: a
a b :: 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 f :: a -> f b
f (Node3 v :: v
v a :: a
a b :: a
b c :: 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
empty :: Measured v a => FingerTree v a
empty :: FingerTree v a
empty = FingerTree v a
forall v a. FingerTree v a
Empty
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
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 a. Measured v a => a -> FingerTree v a -> FingerTree v a
(<|) FingerTree v a
forall v a. FingerTree v a
Empty
(<|) :: (Measured v a) => a -> FingerTree v a -> FingerTree v a
a :: a
a <| :: a -> FingerTree v a -> FingerTree v a
<| Empty = a -> FingerTree v a
forall v a. a -> FingerTree v a
Single a
a
a :: a
a <| Single b :: 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)
a :: a
a <| Deep v :: v
v (Four b :: a
b c :: a
c d :: a
d e :: a
e) m :: FingerTree v (Node v a)
m sf :: Digit a
sf = FingerTree v (Node v a)
m FingerTree v (Node v a) -> FingerTree v a -> FingerTree v a
forall a b. a -> b -> b
`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
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
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 Node v a -> FingerTree v (Node v a) -> FingerTree v (Node v a)
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v (Node v a)
m) Digit a
sf
a :: a
a <| Deep v :: v
v pr :: Digit a
pr m :: FingerTree v (Node v a)
m sf :: 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
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
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
a (One b :: a
b) = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
consDigit a :: a
a (Two b :: a
b c :: a
c) = a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
a a
b a
c
consDigit a :: a
a (Three b :: a
b c :: a
c d :: 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 _ (Four _ _ _ _) = String -> Digit a
forall a. String -> a
illegal_argument "consDigit"
(|>) :: (Measured v a) => FingerTree v a -> a -> FingerTree v a
Empty |> :: FingerTree v a -> a -> FingerTree v a
|> a :: a
a = a -> FingerTree v a
forall v a. a -> FingerTree v a
Single a
a
Single a :: a
a |> b :: 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)
Deep v :: v
v pr :: Digit a
pr m :: FingerTree v (Node v a)
m (Four a :: a
a b :: a
b c :: a
c d :: a
d) |> e :: a
e = FingerTree v (Node v a)
m FingerTree v (Node v a) -> FingerTree v a -> FingerTree v a
forall a b. a -> b -> b
`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
e) Digit a
pr (FingerTree v (Node v a)
m FingerTree v (Node v a) -> Node v a -> FingerTree v (Node v a)
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> 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
e)
Deep v :: v
v pr :: Digit a
pr m :: FingerTree v (Node v a)
m sf :: Digit a
sf |> x :: 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
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
x)
snocDigit :: Digit a -> a -> Digit a
snocDigit :: Digit a -> a -> Digit a
snocDigit (One a :: a
a) b :: a
b = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
snocDigit (Two a :: a
a b :: a
b) c :: 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
b c :: a
c) d :: 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 _ _ _ _) _ = String -> Digit a
forall a. String -> a
illegal_argument "snocDigit"
null :: FingerTree v a -> Bool
null :: FingerTree v a -> Bool
null Empty = Bool
True
null _ = Bool
False
viewl :: (Measured v a) => FingerTree v a -> ViewL (FingerTree v) a
viewl :: FingerTree v a -> ViewL (FingerTree v) a
viewl Empty = ViewL (FingerTree v) a
forall (s :: * -> *) a. ViewL s a
EmptyL
viewl (Single x :: 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 _ (One x :: a
x) m :: FingerTree v (Node v a)
m sf :: 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 _ pr :: Digit a
pr m :: FingerTree v (Node v a)
m sf :: 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 m :: FingerTree v (Node v a)
m sf :: 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
EmptyL -> Digit a -> FingerTree v a
forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree Digit a
sf
a :: Node v a
a :< m' :: 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
a
lheadDigit (Two a :: a
a _) = a
a
lheadDigit (Three a :: a
a _ _) = a
a
lheadDigit (Four a :: a
a _ _ _) = a
a
ltailDigit :: Digit a -> Digit a
ltailDigit :: Digit a -> Digit a
ltailDigit (One _) = String -> Digit a
forall a. String -> a
illegal_argument "ltailDigit"
ltailDigit (Two _ b :: a
b) = a -> Digit a
forall a. a -> Digit a
One a
b
ltailDigit (Three _ b :: a
b c :: a
c) = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
b a
c
ltailDigit (Four _ b :: a
b c :: a
c d :: a
d) = a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
b a
c a
d
viewr :: (Measured v a) => FingerTree v a -> ViewR (FingerTree v) a
viewr :: FingerTree v a -> ViewR (FingerTree v) a
viewr Empty = ViewR (FingerTree v) a
forall (s :: * -> *) a. ViewR s a
EmptyR
viewr (Single x :: 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 _ pr :: Digit a
pr m :: FingerTree v (Node v a)
m (One x :: 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 _ pr :: Digit a
pr m :: FingerTree v (Node v a)
m sf :: 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 pr :: Digit a
pr m :: 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
EmptyR -> Digit a -> FingerTree v a
forall v a. Measured v a => Digit a -> FingerTree v a
digitToTree Digit a
pr
m' :: FingerTree v (Node v a)
m' :> a :: 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 -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` FingerTree v (Node v a) -> v
forall v a. Measured v a => a -> v
measure 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
a
rheadDigit (Two _ b :: a
b) = a
b
rheadDigit (Three _ _ c :: a
c) = a
c
rheadDigit (Four _ _ _ d :: a
d) = a
d
rtailDigit :: Digit a -> Digit a
rtailDigit :: Digit a -> Digit a
rtailDigit (One _) = String -> Digit a
forall a. String -> a
illegal_argument "rtailDigit"
rtailDigit (Two a :: a
a _) = a -> Digit a
forall a. a -> Digit a
One a
a
rtailDigit (Three a :: a
a b :: a
b _) = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
rtailDigit (Four a :: a
a b :: a
b c :: a
c _) = 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) = a -> FingerTree v a
forall v a. a -> FingerTree v a
Single a
a
digitToTree (Two a :: a
a b :: 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
b c :: 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
b c :: a
c d :: 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)
(><) :: (Measured v a) => FingerTree v a -> 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 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 Empty xs :: FingerTree v a
xs =
FingerTree v a
xs
appendTree0 xs :: FingerTree v a
xs Empty =
FingerTree v a
xs
appendTree0 (Single x :: a
x) xs :: FingerTree v a
xs =
a
x a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree0 xs :: FingerTree v a
xs (Single x :: a
x) =
FingerTree v a
xs FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
x
appendTree0 (Deep _ pr1 :: Digit a
pr1 m1 :: FingerTree v (Node v a)
m1 sf1 :: Digit a
sf1) (Deep _ pr2 :: Digit a
pr2 m2 :: FingerTree v (Node v a)
m2 sf2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) (One b :: a
b) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) (Two b :: a
b c :: a
c) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) (Three b :: a
b c :: a
c d :: a
d) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) (Four b :: a
b c :: a
c d :: a
d e :: a
e) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) (One c :: a
c) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) (Two c :: a
c d :: a
d) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) (Three c :: a
c d :: a
d e :: a
e) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) (Four c :: a
c d :: a
d e :: a
e f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) (One d :: a
d) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) (Two d :: a
d e :: a
e) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) (Three d :: a
d e :: a
e f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) (Four d :: a
d e :: a
e f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) (One e :: a
e) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) (Two e :: a
e f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) (Three e :: a
e f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) (Four e :: a
e f :: a
f g :: a
g h :: a
h) m2 :: 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 Empty a :: a
a xs :: FingerTree v a
xs =
a
a a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree1 xs :: FingerTree v a
xs a :: a
a Empty =
FingerTree v a
xs FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a
appendTree1 (Single x :: a
x) a :: a
a xs :: FingerTree v a
xs =
a
x a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
a a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree1 xs :: FingerTree v a
xs a :: a
a (Single x :: a
x) =
FingerTree v a
xs FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
x
appendTree1 (Deep _ pr1 :: Digit a
pr1 m1 :: FingerTree v (Node v a)
m1 sf1 :: Digit a
sf1) a :: a
a (Deep _ pr2 :: Digit a
pr2 m2 :: FingerTree v (Node v a)
m2 sf2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b (One c :: a
c) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b (Two c :: a
c d :: a
d) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b (Three c :: a
c d :: a
d e :: a
e) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b (Four c :: a
c d :: a
d e :: a
e f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c (One d :: a
d) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c (Two d :: a
d e :: a
e) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c (Three d :: a
d e :: a
e f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c (Four d :: a
d e :: a
e f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d (One e :: a
e) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d (Two e :: a
e f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d (Three e :: a
e f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d (Four e :: a
e f :: a
f g :: a
g h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e (One f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e (Two f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e (Three f :: a
f g :: a
g h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e (Four f :: a
f g :: a
g h :: a
h i :: a
i) m2 :: 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 Empty a :: a
a b :: a
b xs :: FingerTree v a
xs =
a
a a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree2 xs :: FingerTree v a
xs a :: a
a b :: a
b Empty =
FingerTree v a
xs FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b
appendTree2 (Single x :: a
x) a :: a
a b :: a
b xs :: FingerTree v a
xs =
a
x a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
a a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree2 xs :: FingerTree v a
xs a :: a
a b :: a
b (Single x :: a
x) =
FingerTree v a
xs FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
x
appendTree2 (Deep _ pr1 :: Digit a
pr1 m1 :: FingerTree v (Node v a)
m1 sf1 :: Digit a
sf1) a :: a
a b :: a
b (Deep _ pr2 :: Digit a
pr2 m2 :: FingerTree v (Node v a)
m2 sf2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c (One d :: a
d) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c (Two d :: a
d e :: a
e) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c (Three d :: a
d e :: a
e f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c (Four d :: a
d e :: a
e f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d (One e :: a
e) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d (Two e :: a
e f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d (Three e :: a
e f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d (Four e :: a
e f :: a
f g :: a
g h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e (One f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e (Two f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e (Three f :: a
f g :: a
g h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e (Four f :: a
f g :: a
g h :: a
h i :: a
i) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f (One g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f (Two g :: a
g h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f (Three g :: a
g h :: a
h i :: a
i) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f (Four g :: a
g h :: a
h i :: a
i j :: a
j) m2 :: 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 Empty a :: a
a b :: a
b c :: a
c xs :: FingerTree v a
xs =
a
a a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
c a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree3 xs :: FingerTree v a
xs a :: a
a b :: a
b c :: a
c Empty =
FingerTree v a
xs FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
c
appendTree3 (Single x :: a
x) a :: a
a b :: a
b c :: a
c xs :: FingerTree v a
xs =
a
x a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
a a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
c a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree3 xs :: FingerTree v a
xs a :: a
a b :: a
b c :: a
c (Single x :: a
x) =
FingerTree v a
xs FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
c FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
x
appendTree3 (Deep _ pr1 :: Digit a
pr1 m1 :: FingerTree v (Node v a)
m1 sf1 :: Digit a
sf1) a :: a
a b :: a
b c :: a
c (Deep _ pr2 :: Digit a
pr2 m2 :: FingerTree v (Node v a)
m2 sf2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c d :: a
d (One e :: a
e) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c d :: a
d (Two e :: a
e f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c d :: a
d (Three e :: a
e f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c d :: a
d (Four e :: a
e f :: a
f g :: a
g h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d e :: a
e (One f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d e :: a
e (Two f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d e :: a
e (Three f :: a
f g :: a
g h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d e :: a
e (Four f :: a
f g :: a
g h :: a
h i :: a
i) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e f :: a
f (One g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e f :: a
f (Two g :: a
g h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e f :: a
f (Three g :: a
g h :: a
h i :: a
i) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e f :: a
f (Four g :: a
g h :: a
h i :: a
i j :: a
j) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f g :: a
g (One h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f g :: a
g (Two h :: a
h i :: a
i) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f g :: a
g (Three h :: a
h i :: a
i j :: a
j) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f g :: a
g (Four h :: a
h i :: a
i j :: a
j k :: a
k) m2 :: 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 Empty a :: a
a b :: a
b c :: a
c d :: a
d xs :: FingerTree v a
xs =
a
a a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
c a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
d a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree4 xs :: FingerTree v a
xs a :: a
a b :: a
b c :: a
c d :: a
d Empty =
FingerTree v a
xs FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
c FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
d
appendTree4 (Single x :: a
x) a :: a
a b :: a
b c :: a
c d :: a
d xs :: FingerTree v a
xs =
a
x a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
a a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
b a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
c a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| a
d a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
xs
appendTree4 xs :: FingerTree v a
xs a :: a
a b :: a
b c :: a
c d :: a
d (Single x :: a
x) =
FingerTree v a
xs FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
a FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
b FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
c FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
d FingerTree v a -> a -> FingerTree v a
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> a
x
appendTree4 (Deep _ pr1 :: Digit a
pr1 m1 :: FingerTree v (Node v a)
m1 sf1 :: Digit a
sf1) a :: a
a b :: a
b c :: a
c d :: a
d (Deep _ pr2 :: Digit a
pr2 m2 :: FingerTree v (Node v a)
m2 sf2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c d :: a
d e :: a
e (One f :: a
f) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c d :: a
d e :: a
e (Two f :: a
f g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c d :: a
d e :: a
e (Three f :: a
f g :: a
g h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (One a :: a
a) b :: a
b c :: a
c d :: a
d e :: a
e (Four f :: a
f g :: a
g h :: a
h i :: a
i) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d e :: a
e f :: a
f (One g :: a
g) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d e :: a
e f :: a
f (Two g :: a
g h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d e :: a
e f :: a
f (Three g :: a
g h :: a
h i :: a
i) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Two a :: a
a b :: a
b) c :: a
c d :: a
d e :: a
e f :: a
f (Four g :: a
g h :: a
h i :: a
i j :: a
j) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e f :: a
f g :: a
g (One h :: a
h) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e f :: a
f g :: a
g (Two h :: a
h i :: a
i) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e f :: a
f g :: a
g (Three h :: a
h i :: a
i j :: a
j) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Three a :: a
a b :: a
b c :: a
c) d :: a
d e :: a
e f :: a
f g :: a
g (Four h :: a
h i :: a
i j :: a
j k :: a
k) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f g :: a
g h :: a
h (One i :: a
i) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f g :: a
g h :: a
h (Two i :: a
i j :: a
j) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f g :: a
g h :: a
h (Three i :: a
i j :: a
j k :: a
k) m2 :: 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 m1 :: FingerTree v (Node v a)
m1 (Four a :: a
a b :: a
b c :: a
c d :: a
d) e :: a
e f :: a
f g :: a
g h :: a
h (Four i :: a
i j :: a
j k :: a
k l :: a
l) m2 :: 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
data SearchResult v a
= Position (FingerTree v a) a (FingerTree v a)
| OnLeft
| OnRight
| Nowhere
deriving (SearchResult v a -> SearchResult v a -> Bool
(SearchResult v a -> SearchResult v a -> Bool)
-> (SearchResult v a -> SearchResult v a -> Bool)
-> Eq (SearchResult v a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall v a. Eq a => SearchResult v a -> SearchResult v a -> Bool
/= :: SearchResult v a -> SearchResult v a -> Bool
$c/= :: forall v a. Eq a => SearchResult v a -> SearchResult v a -> Bool
== :: SearchResult v a -> SearchResult v a -> Bool
$c== :: forall v a. Eq a => SearchResult v a -> SearchResult v a -> Bool
Eq, Eq (SearchResult v a)
Eq (SearchResult v a) =>
(SearchResult v a -> SearchResult v a -> Ordering)
-> (SearchResult v a -> SearchResult v a -> Bool)
-> (SearchResult v a -> SearchResult v a -> Bool)
-> (SearchResult v a -> SearchResult v a -> Bool)
-> (SearchResult v a -> SearchResult v a -> Bool)
-> (SearchResult v a -> SearchResult v a -> SearchResult v a)
-> (SearchResult v a -> SearchResult v a -> SearchResult v a)
-> Ord (SearchResult v a)
SearchResult v a -> SearchResult v a -> Bool
SearchResult v a -> SearchResult v a -> Ordering
SearchResult v a -> SearchResult v a -> SearchResult v 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 v a. Ord a => Eq (SearchResult v a)
forall v a. Ord a => SearchResult v a -> SearchResult v a -> Bool
forall v a.
Ord a =>
SearchResult v a -> SearchResult v a -> Ordering
forall v a.
Ord a =>
SearchResult v a -> SearchResult v a -> SearchResult v a
min :: SearchResult v a -> SearchResult v a -> SearchResult v a
$cmin :: forall v a.
Ord a =>
SearchResult v a -> SearchResult v a -> SearchResult v a
max :: SearchResult v a -> SearchResult v a -> SearchResult v a
$cmax :: forall v a.
Ord a =>
SearchResult v a -> SearchResult v a -> SearchResult v a
>= :: SearchResult v a -> SearchResult v a -> Bool
$c>= :: forall v a. Ord a => SearchResult v a -> SearchResult v a -> Bool
> :: SearchResult v a -> SearchResult v a -> Bool
$c> :: forall v a. Ord a => SearchResult v a -> SearchResult v a -> Bool
<= :: SearchResult v a -> SearchResult v a -> Bool
$c<= :: forall v a. Ord a => SearchResult v a -> SearchResult v a -> Bool
< :: SearchResult v a -> SearchResult v a -> Bool
$c< :: forall v a. Ord a => SearchResult v a -> SearchResult v a -> Bool
compare :: SearchResult v a -> SearchResult v a -> Ordering
$ccompare :: forall v a.
Ord a =>
SearchResult v a -> SearchResult v a -> Ordering
$cp1Ord :: forall v a. Ord a => Eq (SearchResult v a)
Ord, Int -> SearchResult v a -> ShowS
[SearchResult v a] -> ShowS
SearchResult v a -> String
(Int -> SearchResult v a -> ShowS)
-> (SearchResult v a -> String)
-> ([SearchResult v a] -> ShowS)
-> Show (SearchResult v a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall v a. Show a => Int -> SearchResult v a -> ShowS
forall v a. Show a => [SearchResult v a] -> ShowS
forall v a. Show a => SearchResult v a -> String
showList :: [SearchResult v a] -> ShowS
$cshowList :: forall v a. Show a => [SearchResult v a] -> ShowS
show :: SearchResult v a -> String
$cshow :: forall v a. Show a => SearchResult v a -> String
showsPrec :: Int -> SearchResult v a -> ShowS
$cshowsPrec :: forall v a. Show a => Int -> SearchResult v a -> ShowS
Show
#if __GLASGOW_HASKELL__ >= 706
, (forall x. SearchResult v a -> Rep (SearchResult v a) x)
-> (forall x. Rep (SearchResult v a) x -> SearchResult v a)
-> Generic (SearchResult v a)
forall x. Rep (SearchResult v a) x -> SearchResult v a
forall x. SearchResult v a -> Rep (SearchResult v a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v a x. Rep (SearchResult v a) x -> SearchResult v a
forall v a x. SearchResult v a -> Rep (SearchResult v a) x
$cto :: forall v a x. Rep (SearchResult v a) x -> SearchResult v a
$cfrom :: forall v a x. SearchResult v a -> Rep (SearchResult v a) x
Generic
#endif
)
search :: (Measured v a) =>
(v -> v -> Bool) -> FingerTree v a -> SearchResult v a
search :: (v -> v -> Bool) -> FingerTree v a -> SearchResult v a
search p :: v -> v -> Bool
p t :: FingerTree v a
t
| Bool
p_left Bool -> Bool -> Bool
&& Bool
p_right = SearchResult v a
forall v a. SearchResult v a
OnLeft
| Bool -> Bool
not Bool
p_left Bool -> Bool -> Bool
&& Bool
p_right = case (v -> v -> Bool)
-> v -> FingerTree v a -> v -> Split (FingerTree v a) a
forall v a.
Measured v a =>
(v -> v -> Bool)
-> v -> FingerTree v a -> v -> Split (FingerTree v a) a
searchTree v -> v -> Bool
p v
forall a. Monoid a => a
mempty FingerTree v a
t v
forall a. Monoid a => a
mempty of
Split l :: FingerTree v a
l x :: a
x r :: FingerTree v a
r -> FingerTree v a -> a -> FingerTree v a -> SearchResult v a
forall v a.
FingerTree v a -> a -> FingerTree v a -> SearchResult v a
Position FingerTree v a
l a
x FingerTree v a
r
| Bool -> Bool
not Bool
p_left Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
p_right = SearchResult v a
forall v a. SearchResult v a
OnRight
| Bool
otherwise = SearchResult v a
forall v a. SearchResult v a
Nowhere
where
p_left :: Bool
p_left = v -> v -> Bool
p v
forall a. Monoid a => a
mempty v
vt
p_right :: Bool
p_right = v -> v -> Bool
p v
vt v
forall a. Monoid a => a
mempty
vt :: v
vt = FingerTree v a -> v
forall v a. Measured v a => a -> v
measure FingerTree v a
t
searchTree :: (Measured v a) =>
(v -> v -> Bool) -> v -> FingerTree v a -> v -> Split (FingerTree v a) a
searchTree :: (v -> v -> Bool)
-> v -> FingerTree v a -> v -> Split (FingerTree v a) a
searchTree _ _ Empty _ = String -> Split (FingerTree v a) a
forall a. String -> a
illegal_argument "searchTree"
searchTree _ _ (Single x :: 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
searchTree p :: v -> v -> Bool
p vl :: v
vl (Deep _ pr :: Digit a
pr m :: FingerTree v (Node v a)
m sf :: Digit a
sf) vr :: v
vr
| v -> v -> Bool
p v
vlp v
vmsr = let Split l :: Maybe (Digit a)
l x :: a
x r :: Maybe (Digit a)
r = (v -> v -> Bool) -> v -> Digit a -> v -> Split (Maybe (Digit a)) a
forall v a.
Measured v a =>
(v -> v -> Bool) -> v -> Digit a -> v -> Split (Maybe (Digit a)) a
searchDigit v -> v -> Bool
p v
vl Digit a
pr v
vmsr
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 -> v -> Bool
p v
vlpm v
vsr = let Split ml :: FingerTree v (Node v a)
ml xs :: Node v a
xs mr :: FingerTree v (Node v a)
mr = (v -> v -> Bool)
-> v
-> FingerTree v (Node v a)
-> v
-> Split (FingerTree v (Node v a)) (Node v a)
forall v a.
Measured v a =>
(v -> v -> Bool)
-> v -> FingerTree v a -> v -> Split (FingerTree v a) a
searchTree v -> v -> Bool
p v
vlp FingerTree v (Node v a)
m v
vsr
Split l :: Maybe (Digit a)
l x :: a
x r :: Maybe (Digit a)
r = (v -> v -> Bool) -> v -> Node v a -> v -> Split (Maybe (Digit a)) a
forall v a.
Measured v a =>
(v -> v -> Bool) -> v -> Node v a -> v -> Split (Maybe (Digit a)) a
searchNode v -> v -> Bool
p (v
vlp v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` FingerTree v (Node v a) -> v
forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
ml) Node v a
xs (FingerTree v (Node v a) -> v
forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
mr v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vsr)
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 l :: Maybe (Digit a)
l x :: a
x r :: Maybe (Digit a)
r = (v -> v -> Bool) -> v -> Digit a -> v -> Split (Maybe (Digit a)) a
forall v a.
Measured v a =>
(v -> v -> Bool) -> v -> Digit a -> v -> Split (Maybe (Digit a)) a
searchDigit v -> v -> Bool
p v
vlpm Digit a
sf v
vr
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
vlp :: v
vlp = v
vl 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
vlpm :: v
vlpm = v
vlp v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vm
vmsr :: v
vmsr = v
vm v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vsr
vsr :: v
vsr = Digit a -> v
forall v a. Measured v a => a -> v
measure Digit a
sf v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
vm :: v
vm = FingerTree v (Node v a) -> v
forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m
searchNode :: (Measured v a) =>
(v -> v -> Bool) -> v -> Node v a -> v -> Split (Maybe (Digit a)) a
searchNode :: (v -> v -> Bool) -> v -> Node v a -> v -> Split (Maybe (Digit a)) a
searchNode p :: v -> v -> Bool
p vl :: v
vl (Node2 _ a :: a
a b :: a
b) vr :: v
vr
| v -> v -> Bool
p v
va v
vb = 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
vl v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
vb :: v
vb = a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
searchNode p :: v -> v -> Bool
p vl :: v
vl (Node3 _ a :: a
a b :: a
b c :: a
c) vr :: v
vr
| v -> v -> Bool
p v
va v
vbc = 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 -> v -> Bool
p v
vab v
vc = 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
vl 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
vc :: v
vc = a -> v
forall v a. Measured v a => a -> v
measure a
c v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
vbc :: v
vbc = a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vc
searchDigit :: (Measured v a) =>
(v -> v -> Bool) -> v -> Digit a -> v -> Split (Maybe (Digit a)) a
searchDigit :: (v -> v -> Bool) -> v -> Digit a -> v -> Split (Maybe (Digit a)) a
searchDigit _ vl :: v
vl (One a :: a
a) vr :: v
vr = v
vl v -> Split (Maybe (Digit a)) a -> Split (Maybe (Digit a)) a
forall a b. a -> b -> b
`seq` v
vr v -> Split (Maybe (Digit a)) a -> Split (Maybe (Digit a)) a
forall a b. a -> b -> b
`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
searchDigit p :: v -> v -> Bool
p vl :: v
vl (Two a :: a
a b :: a
b) vr :: v
vr
| v -> v -> Bool
p v
va v
vb = 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
vl v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` a -> v
forall v a. Measured v a => a -> v
measure a
a
vb :: v
vb = a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
searchDigit p :: v -> v -> Bool
p vl :: v
vl (Three a :: a
a b :: a
b c :: a
c) vr :: v
vr
| v -> v -> Bool
p v
va v
vbc = 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 -> v -> Bool
p v
vab v
vc = 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
vl 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
vbc :: v
vbc = a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vc
vc :: v
vc = a -> v
forall v a. Measured v a => a -> v
measure a
c v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
searchDigit p :: v -> v -> Bool
p vl :: v
vl (Four a :: a
a b :: a
b c :: a
c d :: a
d) vr :: v
vr
| v -> v -> Bool
p v
va v
vbcd = 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 -> v -> Bool
p v
vab v
vcd = 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 -> v -> Bool
p v
vabc v
vd = 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
vl 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
vbcd :: v
vbcd = a -> v
forall v a. Measured v a => a -> v
measure a
b v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vcd
vcd :: v
vcd = a -> v
forall v a. Measured v a => a -> v
measure a
c v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vd
vd :: v
vd = a -> v
forall v a. Measured v a => a -> v
measure a
d v -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` v
vr
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 _ Empty = (FingerTree v a
forall v a. FingerTree v a
Empty, FingerTree v a
forall v a. FingerTree v a
Empty)
split p :: v -> Bool
p xs :: 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
x a -> FingerTree v a -> FingerTree v a
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree v a
r)
| Bool
otherwise = (FingerTree v a
xs, FingerTree v a
forall v a. FingerTree v a
Empty)
where
Split l :: FingerTree v a
l x :: a
x r :: 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
takeUntil :: (Measured v a) => (v -> Bool) -> FingerTree v a -> FingerTree v a
takeUntil :: (v -> Bool) -> FingerTree v a -> FingerTree v a
takeUntil p :: 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
dropUntil :: (Measured v a) => (v -> Bool) -> FingerTree v a -> FingerTree v a
dropUntil :: (v -> Bool) -> FingerTree v a -> FingerTree v a
dropUntil p :: 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 _ _ Empty = String -> Split (FingerTree v a) a
forall a. String -> a
illegal_argument "splitTree"
splitTree _ _ (Single x :: 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 p :: v -> Bool
p i :: v
i (Deep _ pr :: Digit a
pr m :: FingerTree v (Node v a)
m sf :: Digit a
sf)
| v -> Bool
p v
vpr = let Split l :: Maybe (Digit a)
l x :: a
x r :: 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 ml :: FingerTree v (Node v a)
ml xs :: Node v a
xs mr :: 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 l :: Maybe (Digit a)
l x :: a
x r :: 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 -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` FingerTree v (Node v a) -> v
forall v a. Measured v a => a -> v
measure 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 l :: Maybe (Digit a)
l x :: a
x r :: 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 -> v -> v
forall a. Monoid a => a -> a -> a
`mappend` FingerTree v (Node v a) -> v
forall v a. Measured v a => a -> v
measure FingerTree v (Node v a)
m
deepL :: (Measured v a) =>
Maybe (Digit a) -> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deepL :: Maybe (Digit a)
-> FingerTree v (Node v a) -> Digit a -> FingerTree v a
deepL Nothing m :: FingerTree v (Node v a)
m sf :: 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 pr :: Digit a
pr) m :: FingerTree v (Node v a)
m sf :: 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 pr :: Digit a
pr m :: FingerTree v (Node v a)
m 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 pr :: Digit a
pr m :: FingerTree v (Node v a)
m (Just sf :: 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 p :: v -> Bool
p i :: v
i (Node2 _ a :: a
a b :: 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 p :: v -> Bool
p i :: v
i (Node3 _ a :: a
a b :: a
b c :: 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 _ i :: v
i (One a :: a
a) = v
i v -> Split (Maybe (Digit a)) a -> Split (Maybe (Digit a)) a
forall a b. a -> b -> b
`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 p :: v -> Bool
p i :: v
i (Two a :: a
a b :: 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 p :: v -> Bool
p i :: v
i (Three a :: a
a b :: a
b c :: 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 p :: v -> Bool
p i :: v
i (Four a :: a
a b :: a
b c :: a
c d :: 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
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 _ Empty = FingerTree v2 a2
forall v a. FingerTree v a
Empty
reverseTree f :: a1 -> a2
f (Single x :: a1
x) = a2 -> FingerTree v2 a2
forall v a. a -> FingerTree v a
Single (a1 -> a2
f a1
x)
reverseTree f :: a1 -> a2
f (Deep _ pr :: Digit a1
pr m :: FingerTree v1 (Node v1 a1)
m sf :: 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 f :: a1 -> a2
f (Node2 _ a :: a1
a b :: 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 f :: a1 -> a2
f (Node3 _ a :: a1
a b :: a1
b c :: 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 f :: a -> b
f (One a :: a
a) = b -> Digit b
forall a. a -> Digit a
One (a -> b
f a
a)
reverseDigit f :: a -> b
f (Two a :: a
a b :: a
b) = b -> b -> Digit b
forall a. a -> a -> Digit a
Two (a -> b
f a
b) (a -> b
f a
a)
reverseDigit f :: a -> b
f (Three a :: a
a b :: a
b c :: 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 f :: a -> b
f (Four a :: a
a b :: a
b c :: a
c d :: 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)
illegal_argument :: String -> a
illegal_argument :: String -> a
illegal_argument name :: String
name =
String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ "Logic error: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ " called with illegal argument"