{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DeriveGeneric #-}
module Codec.Compression.Zlib.FingerTree (
FingerTree,
Measured(..),
empty,
(|>),
dropTakeCombine,
split,
toBuilder
) where
import Prelude hiding (null, reverse)
import GHC.Generics
import qualified Data.ByteString as S
import Data.ByteString.Builder(Builder, byteString)
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Internal as L
type Measure = Int
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, (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)
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, (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)
instance (Functor s) => Functor (ViewL s) where
fmap :: (a -> b) -> ViewL s a -> ViewL s b
fmap a -> b
_ ViewL s a
EmptyL = ViewL s b
forall (s :: * -> *) a. ViewL s a
EmptyL
fmap a -> b
f (a
x :< s a
xs) = a -> b
f a
x b -> s b -> ViewL s b
forall (s :: * -> *) a. a -> s a -> ViewL s a
:< (a -> b) -> s a -> s b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f s a
xs
instance (Functor s) => Functor (ViewR s) where
fmap :: (a -> b) -> ViewR s a -> ViewR s b
fmap a -> b
_ ViewR s a
EmptyR = ViewR s b
forall (s :: * -> *) a. ViewR s a
EmptyR
fmap a -> b
f (s a
xs :> a
x) = (a -> b) -> s a -> s b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f s a
xs s b -> b -> ViewR s b
forall (s :: * -> *) a. s a -> a -> ViewR s a
:> a -> b
f a
x
instance (Measured a) => Semigroup (FingerTree a) where
<> :: FingerTree a -> FingerTree a -> FingerTree a
(<>) = FingerTree a -> FingerTree a -> FingerTree a
forall a.
Measured a =>
FingerTree a -> FingerTree a -> FingerTree a
(><)
instance (Measured a) => Monoid (FingerTree a) where
mempty :: FingerTree a
mempty = FingerTree a
forall a. Measured a => FingerTree a
empty
mappend :: FingerTree a -> FingerTree a -> FingerTree a
mappend = FingerTree a -> FingerTree a -> FingerTree a
forall a.
Measured a =>
FingerTree a -> FingerTree a -> FingerTree a
(><)
instance Measured S.ByteString where
measure :: ByteString -> Int
measure = ByteString -> Int
S.length
{-# INLINE measure #-}
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)
class Measured a where
measure :: a -> Measure
instance (Measured a) => Measured (Digit a) where
measure :: Digit a -> Int
measure (One a
a1) = a -> Int
forall a. Measured a => a -> Int
measure a
a1
measure (Two a
a1 a
a2) = a -> Int
forall a. Measured a => a -> Int
measure a
a1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a2
measure (Three a
a1 a
a2 a
a3) = a -> Int
forall a. Measured a => a -> Int
measure a
a1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a3
measure (Four a
a1 a
a2 a
a3 a
a4) = a -> Int
forall a. Measured a => a -> Int
measure a
a1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a3 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a4
data Node a = Node2 !Measure a a | Node3 !Measure a a a
deriving (Int -> Node a -> ShowS
[Node a] -> ShowS
Node a -> String
(Int -> Node a -> ShowS)
-> (Node a -> String) -> ([Node a] -> ShowS) -> Show (Node a)
forall a. Show a => Int -> Node a -> ShowS
forall a. Show a => [Node a] -> ShowS
forall a. Show a => Node a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Node a] -> ShowS
$cshowList :: forall a. Show a => [Node a] -> ShowS
show :: Node a -> String
$cshow :: forall a. Show a => Node a -> String
showsPrec :: Int -> Node a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Node a -> ShowS
Show)
node2 :: (Measured a) => a -> a -> Node a
node2 :: a -> a -> Node a
node2 a
a a
b = Int -> a -> a -> Node a
forall a. Int -> a -> a -> Node a
Node2 (a -> Int
forall a. Measured a => a -> Int
measure a
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
b) a
a a
b
node3 :: (Measured a) => a -> a -> a -> Node a
node3 :: a -> a -> a -> Node a
node3 a
a a
b a
c = Int -> a -> a -> a -> Node a
forall a. Int -> a -> a -> a -> Node a
Node3 (a -> Int
forall a. Measured a => a -> Int
measure a
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
c) a
a a
b a
c
instance Measured (Node a) where
measure :: Node a -> Int
measure (Node2 Int
v a
_ a
_) = Int
v
measure (Node3 Int
v a
_ a
_ a
_) = Int
v
nodeToDigit :: Node a -> Digit a
nodeToDigit :: Node a -> Digit a
nodeToDigit (Node2 Int
_ a
a a
b) = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
nodeToDigit (Node3 Int
_ a
a a
b a
c) = a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
a a
b a
c
data FingerTree a
= Empty
| Single a
| Deep !Measure !(Digit a) (FingerTree (Node a)) !(Digit a)
deriving (Int -> FingerTree a -> ShowS
[FingerTree a] -> ShowS
FingerTree a -> String
(Int -> FingerTree a -> ShowS)
-> (FingerTree a -> String)
-> ([FingerTree a] -> ShowS)
-> Show (FingerTree a)
forall a. Show a => Int -> FingerTree a -> ShowS
forall a. Show a => [FingerTree a] -> ShowS
forall a. Show a => FingerTree a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FingerTree a] -> ShowS
$cshowList :: forall a. Show a => [FingerTree a] -> ShowS
show :: FingerTree a -> String
$cshow :: forall a. Show a => FingerTree a -> String
showsPrec :: Int -> FingerTree a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> FingerTree a -> ShowS
Show)
deep :: (Measured a) => Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep :: Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep Digit a
pr FingerTree (Node a)
m Digit a
sf =
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep ((Digit a -> Int
forall a. Measured a => a -> Int
measure Digit a
pr Int -> Int -> Int
forall a. Num a => a -> a -> a
+ FingerTree (Node a) -> Int
forall a. Measured a => a -> Int
measure FingerTree (Node a)
m) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Digit a -> Int
forall a. Measured a => a -> Int
measure Digit a
sf) Digit a
pr FingerTree (Node a)
m Digit a
sf
instance (Measured a) => Measured (FingerTree a) where
measure :: FingerTree a -> Int
measure FingerTree a
Empty = Int
0
measure (Single a
x) = a -> Int
forall a. Measured a => a -> Int
measure a
x
measure (Deep Int
v Digit a
_ FingerTree (Node a)
_ Digit a
_) = Int
v
empty :: Measured a => FingerTree a
empty :: FingerTree a
empty = FingerTree a
forall a. FingerTree a
Empty
(<|) :: (Measured a) => a -> FingerTree a -> FingerTree a
a
a <| :: a -> FingerTree a -> FingerTree a
<| FingerTree a
Empty = a -> FingerTree a
forall a. a -> FingerTree a
Single a
a
a
a <| Single a
b = Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep (a -> Digit a
forall a. a -> Digit a
One a
a) FingerTree (Node a)
forall a. FingerTree a
Empty (a -> Digit a
forall a. a -> Digit a
One a
b)
a
a <| Deep Int
v (Four a
b a
c a
d a
e) FingerTree (Node a)
m Digit a
sf = FingerTree (Node a)
m FingerTree (Node a) -> FingerTree a -> FingerTree a
`seq`
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep (a -> Int
forall a. Measured a => a -> Int
measure a
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
v) (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
c a
d a
e Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree (Node a)
m) Digit a
sf
a
a <| Deep Int
v Digit a
pr FingerTree (Node a)
m Digit a
sf =
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep (a -> Int
forall a. Measured a => a -> Int
measure a
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
v) (a -> Digit a -> Digit a
forall a. a -> Digit a -> Digit a
consDigit a
a Digit a
pr) FingerTree (Node a)
m Digit a
sf
consDigit :: a -> Digit a -> Digit a
consDigit :: a -> Digit a -> Digit a
consDigit a
a (One a
b) = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
consDigit a
a (Two a
b a
c) = a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
a a
b a
c
consDigit a
a (Three a
b a
c a
d) = a -> a -> a -> a -> Digit a
forall a. a -> a -> a -> a -> Digit a
Four a
a a
b a
c a
d
consDigit a
_ (Four a
_ a
_ a
_ a
_) = String -> Digit a
forall a. String -> a
illegal_argument String
"consDigit"
(|>) :: (Measured a) => FingerTree a -> a -> FingerTree a
FingerTree a
Empty |> :: FingerTree a -> a -> FingerTree a
|> a
a = a -> FingerTree a
forall a. a -> FingerTree a
Single a
a
Single a
a |> a
b = Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep (a -> Digit a
forall a. a -> Digit a
One a
a) FingerTree (Node a)
forall a. FingerTree a
Empty (a -> Digit a
forall a. a -> Digit a
One a
b)
Deep Int
v Digit a
pr FingerTree (Node a)
m (Four a
a a
b a
c a
d) |> a
e = FingerTree (Node a)
m FingerTree (Node a) -> FingerTree a -> FingerTree a
`seq`
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep (Int
v Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
e) Digit a
pr (FingerTree (Node a)
m FingerTree (Node a) -> Node a -> FingerTree (Node a)
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
d a
e)
Deep Int
v Digit a
pr FingerTree (Node a)
m Digit a
sf |> a
x =
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep (Int
v Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
x) Digit a
pr FingerTree (Node 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 -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
snocDigit (Two a
a a
b) a
c = a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
a a
b a
c
snocDigit (Three a
a a
b a
c) a
d = a -> a -> a -> a -> Digit a
forall a. a -> a -> a -> a -> Digit a
Four a
a a
b a
c a
d
snocDigit (Four a
_ a
_ a
_ a
_) a
_ = String -> Digit a
forall a. String -> a
illegal_argument String
"snocDigit"
viewl :: (Measured a) => FingerTree a -> ViewL FingerTree a
viewl :: FingerTree a -> ViewL FingerTree a
viewl FingerTree a
Empty = ViewL FingerTree a
forall (s :: * -> *) a. ViewL s a
EmptyL
viewl (Single a
x) = a
x a -> FingerTree a -> ViewL FingerTree a
forall (s :: * -> *) a. a -> s a -> ViewL s a
:< FingerTree a
forall a. FingerTree a
Empty
viewl (Deep Int
_ (One a
x) FingerTree (Node a)
m Digit a
sf) = a
x a -> FingerTree a -> ViewL FingerTree a
forall (s :: * -> *) a. a -> s a -> ViewL s a
:< FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
FingerTree (Node a) -> Digit a -> FingerTree a
rotL FingerTree (Node a)
m Digit a
sf
viewl (Deep Int
_ Digit a
pr FingerTree (Node a)
m Digit a
sf) = Digit a -> a
forall a. Digit a -> a
lheadDigit Digit a
pr a -> FingerTree a -> ViewL FingerTree a
forall (s :: * -> *) a. a -> s a -> ViewL s a
:< Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep (Digit a -> Digit a
forall a. Digit a -> Digit a
ltailDigit Digit a
pr) FingerTree (Node a)
m Digit a
sf
dropTakeCombine :: Int -> Int -> FingerTree S.ByteString -> L.ByteString
dropTakeCombine :: Int -> Int -> FingerTree ByteString -> ByteString
dropTakeCombine !Int
amountToSkip !Int
amountToKeep !FingerTree ByteString
tree =
case FingerTree ByteString
tree of
FingerTree ByteString
Empty -> ByteString
L.empty
Single ByteString
x -> Int -> FingerTree ByteString -> ByteString
go Int
amountToKeep (ByteString -> FingerTree ByteString
forall a. a -> FingerTree a
Single (Int -> ByteString -> ByteString
S.drop Int
amountToSkip ByteString
x))
Deep Int
_ (One ByteString
x) FingerTree (Node ByteString)
m Digit ByteString
sf -> Int -> FingerTree ByteString -> ByteString
go Int
amountToKeep (Int
-> Digit ByteString
-> FingerTree (Node ByteString)
-> Digit ByteString
-> FingerTree ByteString
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep Int
0 (ByteString -> Digit ByteString
forall a. a -> Digit a
One (Int -> ByteString -> ByteString
S.drop Int
amountToSkip ByteString
x)) FingerTree (Node ByteString)
m Digit ByteString
sf)
Deep Int
_ (Two ByteString
x ByteString
r) FingerTree (Node ByteString)
m Digit ByteString
sf -> Int -> FingerTree ByteString -> ByteString
go Int
amountToKeep (Int
-> Digit ByteString
-> FingerTree (Node ByteString)
-> Digit ByteString
-> FingerTree ByteString
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep Int
0 (ByteString -> ByteString -> Digit ByteString
forall a. a -> a -> Digit a
Two (Int -> ByteString -> ByteString
S.drop Int
amountToSkip ByteString
x) ByteString
r) FingerTree (Node ByteString)
m Digit ByteString
sf)
Deep Int
_ (Three ByteString
x ByteString
r ByteString
s) FingerTree (Node ByteString)
m Digit ByteString
sf -> Int -> FingerTree ByteString -> ByteString
go Int
amountToKeep (Int
-> Digit ByteString
-> FingerTree (Node ByteString)
-> Digit ByteString
-> FingerTree ByteString
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep Int
0 (ByteString -> ByteString -> ByteString -> Digit ByteString
forall a. a -> a -> a -> Digit a
Three (Int -> ByteString -> ByteString
S.drop Int
amountToSkip ByteString
x) ByteString
r ByteString
s) FingerTree (Node ByteString)
m Digit ByteString
sf)
Deep Int
_ (Four ByteString
x ByteString
r ByteString
s ByteString
t) FingerTree (Node ByteString)
m Digit ByteString
sf -> Int -> FingerTree ByteString -> ByteString
go Int
amountToKeep (Int
-> Digit ByteString
-> FingerTree (Node ByteString)
-> Digit ByteString
-> FingerTree ByteString
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep Int
0 (ByteString
-> ByteString -> ByteString -> ByteString -> Digit ByteString
forall a. a -> a -> a -> a -> Digit a
Four (Int -> ByteString -> ByteString
S.drop Int
amountToSkip ByteString
x) ByteString
r ByteString
s ByteString
t) FingerTree (Node ByteString)
m Digit ByteString
sf)
where
go :: Int -> FingerTree ByteString -> ByteString
go Int
0 FingerTree ByteString
_ = ByteString
L.empty
go Int
left FingerTree ByteString
ftr =
case FingerTree ByteString
ftr of
FingerTree ByteString
Empty -> ByteString
L.empty
Single ByteString
x -> ByteString -> ByteString -> ByteString
L.Chunk (Int -> ByteString -> ByteString
S.take Int
left ByteString
x) ByteString
L.Empty
Deep Int
_ (One ByteString
x) FingerTree (Node ByteString)
m Digit ByteString
sf -> Int -> ByteString -> FingerTree ByteString -> ByteString
keepSection Int
left ByteString
x (FingerTree (Node ByteString)
-> Digit ByteString -> FingerTree ByteString
forall a.
Measured a =>
FingerTree (Node a) -> Digit a -> FingerTree a
rotL FingerTree (Node ByteString)
m Digit ByteString
sf)
Deep Int
_ (Two ByteString
x ByteString
r) FingerTree (Node ByteString)
m Digit ByteString
sf -> Int -> ByteString -> FingerTree ByteString -> ByteString
keepSection Int
left ByteString
x (Int
-> Digit ByteString
-> FingerTree (Node ByteString)
-> Digit ByteString
-> FingerTree ByteString
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep Int
0 (ByteString -> Digit ByteString
forall a. a -> Digit a
One ByteString
r) FingerTree (Node ByteString)
m Digit ByteString
sf)
Deep Int
_ (Three ByteString
x ByteString
r ByteString
s) FingerTree (Node ByteString)
m Digit ByteString
sf -> Int -> ByteString -> FingerTree ByteString -> ByteString
keepSection Int
left ByteString
x (Int
-> Digit ByteString
-> FingerTree (Node ByteString)
-> Digit ByteString
-> FingerTree ByteString
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep Int
0 (ByteString -> ByteString -> Digit ByteString
forall a. a -> a -> Digit a
Two ByteString
r ByteString
s) FingerTree (Node ByteString)
m Digit ByteString
sf)
Deep Int
_ (Four ByteString
x ByteString
r ByteString
s ByteString
t) FingerTree (Node ByteString)
m Digit ByteString
sf -> Int -> ByteString -> FingerTree ByteString -> ByteString
keepSection Int
left ByteString
x (Int
-> Digit ByteString
-> FingerTree (Node ByteString)
-> Digit ByteString
-> FingerTree ByteString
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep Int
0 (ByteString -> ByteString -> ByteString -> Digit ByteString
forall a. a -> a -> a -> Digit a
Three ByteString
r ByteString
s ByteString
t) FingerTree (Node ByteString)
m Digit ByteString
sf)
keepSection :: Int -> ByteString -> FingerTree ByteString -> ByteString
keepSection Int
left ByteString
chunk FingerTree ByteString
rest
| ByteString -> Int
S.length ByteString
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
left = ByteString -> ByteString -> ByteString
L.Chunk (Int -> ByteString -> ByteString
S.take Int
left ByteString
chunk) ByteString
L.Empty
| Bool
otherwise = ByteString -> ByteString -> ByteString
L.Chunk ByteString
chunk (Int -> FingerTree ByteString -> ByteString
go (Int
left Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
S.length ByteString
chunk) FingerTree ByteString
rest)
rotL :: (Measured a) => FingerTree (Node a) -> Digit a -> FingerTree a
rotL :: FingerTree (Node a) -> Digit a -> FingerTree a
rotL FingerTree (Node a)
m Digit a
sf = case FingerTree (Node a) -> ViewL FingerTree (Node a)
forall a. Measured a => FingerTree a -> ViewL FingerTree a
viewl FingerTree (Node a)
m of
ViewL FingerTree (Node a)
EmptyL -> Digit a -> FingerTree a
forall a. Measured a => Digit a -> FingerTree a
digitToTree Digit a
sf
Node a
a :< FingerTree (Node a)
m' -> Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep (FingerTree (Node a) -> Int
forall a. Measured a => a -> Int
measure FingerTree (Node a)
m Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Digit a -> Int
forall a. Measured a => a -> Int
measure Digit a
sf) (Node a -> Digit a
forall a. Node a -> Digit a
nodeToDigit Node a
a) FingerTree (Node a)
m' Digit a
sf
lheadDigit :: Digit a -> a
lheadDigit :: Digit a -> a
lheadDigit (One a
a) = a
a
lheadDigit (Two a
a a
_) = a
a
lheadDigit (Three a
a a
_ a
_) = a
a
lheadDigit (Four a
a a
_ a
_ a
_) = a
a
ltailDigit :: Digit a -> Digit a
ltailDigit :: Digit a -> Digit a
ltailDigit (One a
_) = String -> Digit a
forall a. String -> a
illegal_argument String
"ltailDigit"
ltailDigit (Two a
_ a
b) = a -> Digit a
forall a. a -> Digit a
One a
b
ltailDigit (Three a
_ a
b a
c) = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
b a
c
ltailDigit (Four a
_ a
b a
c a
d) = a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
b a
c a
d
viewr :: (Measured a) => FingerTree a -> ViewR FingerTree a
viewr :: FingerTree a -> ViewR FingerTree a
viewr FingerTree a
Empty = ViewR FingerTree a
forall (s :: * -> *) a. ViewR s a
EmptyR
viewr (Single a
x) = FingerTree a
forall a. FingerTree a
Empty FingerTree a -> a -> ViewR FingerTree a
forall (s :: * -> *) a. s a -> a -> ViewR s a
:> a
x
viewr (Deep Int
_ Digit a
pr FingerTree (Node a)
m (One a
x)) = Digit a -> FingerTree (Node a) -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> FingerTree a
rotR Digit a
pr FingerTree (Node a)
m FingerTree a -> a -> ViewR FingerTree a
forall (s :: * -> *) a. s a -> a -> ViewR s a
:> a
x
viewr (Deep Int
_ Digit a
pr FingerTree (Node a)
m Digit a
sf) = Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep Digit a
pr FingerTree (Node a)
m (Digit a -> Digit a
forall a. Digit a -> Digit a
rtailDigit Digit a
sf) FingerTree a -> a -> ViewR FingerTree a
forall (s :: * -> *) a. s a -> a -> ViewR s a
:> Digit a -> a
forall a. Digit a -> a
rheadDigit Digit a
sf
rotR :: (Measured a) => Digit a -> FingerTree (Node a) -> FingerTree a
rotR :: Digit a -> FingerTree (Node a) -> FingerTree a
rotR Digit a
pr FingerTree (Node a)
m = case FingerTree (Node a) -> ViewR FingerTree (Node a)
forall a. Measured a => FingerTree a -> ViewR FingerTree a
viewr FingerTree (Node a)
m of
ViewR FingerTree (Node a)
EmptyR -> Digit a -> FingerTree a
forall a. Measured a => Digit a -> FingerTree a
digitToTree Digit a
pr
FingerTree (Node a)
m' :> Node a
a -> Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Int -> Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
Deep (Digit a -> Int
forall a. Measured a => a -> Int
measure Digit a
pr Int -> Int -> Int
forall a. Num a => a -> a -> a
+ FingerTree (Node a) -> Int
forall a. Measured a => a -> Int
measure FingerTree (Node a)
m) Digit a
pr FingerTree (Node a)
m' (Node a -> Digit a
forall a. Node a -> Digit a
nodeToDigit Node a
a)
rheadDigit :: Digit a -> a
rheadDigit :: Digit a -> a
rheadDigit (One a
a) = a
a
rheadDigit (Two a
_ a
b) = a
b
rheadDigit (Three a
_ a
_ a
c) = a
c
rheadDigit (Four a
_ a
_ a
_ a
d) = a
d
rtailDigit :: Digit a -> Digit a
rtailDigit :: Digit a -> Digit a
rtailDigit (One a
_) = String -> Digit a
forall a. String -> a
illegal_argument String
"rtailDigit"
rtailDigit (Two a
a a
_) = a -> Digit a
forall a. a -> Digit a
One a
a
rtailDigit (Three a
a a
b a
_) = a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b
rtailDigit (Four a
a a
b a
c a
_) = a -> a -> a -> Digit a
forall a. a -> a -> a -> Digit a
Three a
a a
b a
c
digitToTree :: (Measured a) => Digit a -> FingerTree a
digitToTree :: Digit a -> FingerTree a
digitToTree (One a
a) = a -> FingerTree a
forall a. a -> FingerTree a
Single a
a
digitToTree (Two a
a a
b) = Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep (a -> Digit a
forall a. a -> Digit a
One a
a) FingerTree (Node a)
forall a. FingerTree a
Empty (a -> Digit a
forall a. a -> Digit a
One a
b)
digitToTree (Three a
a a
b a
c) = Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b) FingerTree (Node a)
forall a. FingerTree a
Empty (a -> Digit a
forall a. a -> Digit a
One a
c)
digitToTree (Four a
a a
b a
c a
d) = Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
a a
b) FingerTree (Node a)
forall a. FingerTree a
Empty (a -> a -> Digit a
forall a. a -> a -> Digit a
Two a
c a
d)
(><) :: (Measured a) => FingerTree a -> FingerTree a -> FingerTree a
>< :: FingerTree a -> FingerTree a -> FingerTree a
(><) = FingerTree a -> FingerTree a -> FingerTree a
forall a.
Measured a =>
FingerTree a -> FingerTree a -> FingerTree a
appendTree0
appendTree0 :: (Measured a) => FingerTree a -> FingerTree a -> FingerTree a
appendTree0 :: FingerTree a -> FingerTree a -> FingerTree a
appendTree0 FingerTree a
Empty FingerTree a
xs =
FingerTree a
xs
appendTree0 FingerTree a
xs FingerTree a
Empty =
FingerTree a
xs
appendTree0 (Single a
x) FingerTree a
xs =
a
x a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree a
xs
appendTree0 FingerTree a
xs (Single a
x) =
FingerTree a
xs FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
x
appendTree0 (Deep Int
_ Digit a
pr1 FingerTree (Node a)
m1 Digit a
sf1) (Deep Int
_ Digit a
pr2 FingerTree (Node a)
m2 Digit a
sf2) =
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep Digit a
pr1 (FingerTree (Node a)
-> Digit a -> Digit a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree (Node a)
-> Digit a -> Digit a -> FingerTree (Node a) -> FingerTree (Node a)
addDigits0 FingerTree (Node a)
m1 Digit a
sf1 Digit a
pr2 FingerTree (Node a)
m2) Digit a
sf2
addDigits0 :: (Measured a) => FingerTree (Node a) -> Digit a -> Digit a -> FingerTree (Node a) -> FingerTree (Node a)
addDigits0 :: FingerTree (Node a)
-> Digit a -> Digit a -> FingerTree (Node a) -> FingerTree (Node a)
addDigits0 FingerTree (Node a)
m1 (One a
a) (One a
b) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> FingerTree a -> FingerTree a
appendTree1 FingerTree (Node a)
m1 (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
a a
b) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (One a
a) (Two a
b a
c) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> FingerTree a -> FingerTree a
appendTree1 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (One a
a) (Three a
b a
c a
d) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
a a
b) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
c a
d) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (One a
a) (Four a
b a
c a
d a
e) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Two a
a a
b) (One a
c) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> FingerTree a -> FingerTree a
appendTree1 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Two a
a a
b) (Two a
c a
d) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
a a
b) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
c a
d) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Two a
a a
b) (Three a
c a
d a
e) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Two a
a a
b) (Four a
c a
d a
e a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Three a
a a
b a
c) (One a
d) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
a a
b) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
c a
d) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Three a
a a
b a
c) (Two a
d a
e) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Three a
a a
b a
c) (Three a
d a
e a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Three a
a a
b a
c) (Four a
d a
e a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) (One a
e) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) (Two a
e a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) (Three a
e a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits0 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) (Four a
e a
f a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
appendTree1 :: (Measured a) => FingerTree a -> a -> FingerTree a -> FingerTree a
appendTree1 :: FingerTree a -> a -> FingerTree a -> FingerTree a
appendTree1 FingerTree a
Empty a
a FingerTree a
xs =
a
a a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree a
xs
appendTree1 FingerTree a
xs a
a FingerTree a
Empty =
FingerTree a
xs FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
a
appendTree1 (Single a
x) a
a FingerTree a
xs =
a
x a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
a a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree a
xs
appendTree1 FingerTree a
xs a
a (Single a
x) =
FingerTree a
xs FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
a FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
x
appendTree1 (Deep Int
_ Digit a
pr1 FingerTree (Node a)
m1 Digit a
sf1) a
a (Deep Int
_ Digit a
pr2 FingerTree (Node a)
m2 Digit a
sf2) =
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep Digit a
pr1 (FingerTree (Node a)
-> Digit a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree (Node a)
-> Digit a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
addDigits1 FingerTree (Node a)
m1 Digit a
sf1 a
a Digit a
pr2 FingerTree (Node a)
m2) Digit a
sf2
addDigits1 :: (Measured a) => FingerTree (Node a) -> Digit a -> a -> Digit a -> FingerTree (Node a) -> FingerTree (Node a)
addDigits1 :: FingerTree (Node a)
-> Digit a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
addDigits1 FingerTree (Node a)
m1 (One a
a) a
b (One a
c) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> FingerTree a -> FingerTree a
appendTree1 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (One a
a) a
b (Two a
c a
d) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
a a
b) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
c a
d) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (One a
a) a
b (Three a
c a
d a
e) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (One a
a) a
b (Four a
c a
d a
e a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Two a
a a
b) a
c (One a
d) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
a a
b) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
c a
d) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Two a
a a
b) a
c (Two a
d a
e) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Two a
a a
b) a
c (Three a
d a
e a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Two a
a a
b) a
c (Four a
d a
e a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d (One a
e) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d (Two a
e a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d (Three a
e a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d (Four a
e a
f a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e (One a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e (Two a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e (Three a
f a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits1 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e (Four a
f a
g a
h a
i) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) FingerTree (Node a)
m2
appendTree2 :: (Measured a) => FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 :: FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree a
Empty a
a a
b FingerTree a
xs =
a
a a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
b a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree a
xs
appendTree2 FingerTree a
xs a
a a
b FingerTree a
Empty =
FingerTree a
xs FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
a FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
b
appendTree2 (Single a
x) a
a a
b FingerTree a
xs =
a
x a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
a a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
b a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree a
xs
appendTree2 FingerTree a
xs a
a a
b (Single a
x) =
FingerTree a
xs FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
a FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
b FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
x
appendTree2 (Deep Int
_ Digit a
pr1 FingerTree (Node a)
m1 Digit a
sf1) a
a a
b (Deep Int
_ Digit a
pr2 FingerTree (Node a)
m2 Digit a
sf2) =
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep Digit a
pr1 (FingerTree (Node a)
-> Digit a
-> a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree (Node a)
-> Digit a
-> a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
addDigits2 FingerTree (Node a)
m1 Digit a
sf1 a
a a
b Digit a
pr2 FingerTree (Node a)
m2) Digit a
sf2
addDigits2 :: (Measured a) => FingerTree (Node a) -> Digit a -> a -> a -> Digit a -> FingerTree (Node a) -> FingerTree (Node a)
addDigits2 :: FingerTree (Node a)
-> Digit a
-> a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
addDigits2 FingerTree (Node a)
m1 (One a
a) a
b a
c (One a
d) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
a a
b) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
c a
d) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (One a
a) a
b a
c (Two a
d a
e) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (One a
a) a
b a
c (Three a
d a
e a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (One a
a) a
b a
c (Four a
d a
e a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d (One a
e) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d (Two a
e a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d (Three a
e a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d (Four a
e a
f a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e (One a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e (Two a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e (Three a
f a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e (Four a
f a
g a
h a
i) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f (One a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f (Two a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f (Three a
g a
h a
i) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) FingerTree (Node a)
m2
addDigits2 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f (Four a
g a
h a
i a
j) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
i a
j) FingerTree (Node a)
m2
appendTree3 :: (Measured a) => FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 :: FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree a
Empty a
a a
b a
c FingerTree a
xs =
a
a a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
b a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
c a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree a
xs
appendTree3 FingerTree a
xs a
a a
b a
c FingerTree a
Empty =
FingerTree a
xs FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
a FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
b FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
c
appendTree3 (Single a
x) a
a a
b a
c FingerTree a
xs =
a
x a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
a a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
b a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
c a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree a
xs
appendTree3 FingerTree a
xs a
a a
b a
c (Single a
x) =
FingerTree a
xs FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
a FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
b FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
c FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
x
appendTree3 (Deep Int
_ Digit a
pr1 FingerTree (Node a)
m1 Digit a
sf1) a
a a
b a
c (Deep Int
_ Digit a
pr2 FingerTree (Node a)
m2 Digit a
sf2) =
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep Digit a
pr1 (FingerTree (Node a)
-> Digit a
-> a
-> a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree (Node a)
-> Digit a
-> a
-> a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
addDigits3 FingerTree (Node a)
m1 Digit a
sf1 a
a a
b a
c Digit a
pr2 FingerTree (Node a)
m2) Digit a
sf2
addDigits3 :: (Measured a) => FingerTree (Node a) -> Digit a -> a -> a -> a -> Digit a -> FingerTree (Node a) -> FingerTree (Node a)
addDigits3 :: FingerTree (Node a)
-> Digit a
-> a
-> a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
addDigits3 FingerTree (Node a)
m1 (One a
a) a
b a
c a
d (One a
e) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (One a
a) a
b a
c a
d (Two a
e a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (One a
a) a
b a
c a
d (Three a
e a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (One a
a) a
b a
c a
d (Four a
e a
f a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d a
e (One a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d a
e (Two a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d a
e (Three a
f a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d a
e (Four a
f a
g a
h a
i) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e a
f (One a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e a
f (Two a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e a
f (Three a
g a
h a
i) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e a
f (Four a
g a
h a
i a
j) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
i a
j) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g (One a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g (Two a
h a
i) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g (Three a
h a
i a
j) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
i a
j) FingerTree (Node a)
m2
addDigits3 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g (Four a
h a
i a
j a
k) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
j a
k) FingerTree (Node a)
m2
appendTree4 :: (Measured a) => FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 :: FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree a
Empty a
a a
b a
c a
d FingerTree a
xs =
a
a a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
b a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
c a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
d a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree a
xs
appendTree4 FingerTree a
xs a
a a
b a
c a
d FingerTree a
Empty =
FingerTree a
xs FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
a FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
b FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
c FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
d
appendTree4 (Single a
x) a
a a
b a
c a
d FingerTree a
xs =
a
x a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
a a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
b a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
c a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| a
d a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree a
xs
appendTree4 FingerTree a
xs a
a a
b a
c a
d (Single a
x) =
FingerTree a
xs FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
a FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
b FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
c FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
d FingerTree a -> a -> FingerTree a
forall a. Measured a => FingerTree a -> a -> FingerTree a
|> a
x
appendTree4 (Deep Int
_ Digit a
pr1 FingerTree (Node a)
m1 Digit a
sf1) a
a a
b a
c a
d (Deep Int
_ Digit a
pr2 FingerTree (Node a)
m2 Digit a
sf2) =
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep Digit a
pr1 (FingerTree (Node a)
-> Digit a
-> a
-> a
-> a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree (Node a)
-> Digit a
-> a
-> a
-> a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
addDigits4 FingerTree (Node a)
m1 Digit a
sf1 a
a a
b a
c a
d Digit a
pr2 FingerTree (Node a)
m2) Digit a
sf2
addDigits4 :: (Measured a) => FingerTree (Node a) -> Digit a -> a -> a -> a -> a -> Digit a -> FingerTree (Node a) -> FingerTree (Node a)
addDigits4 :: FingerTree (Node a)
-> Digit a
-> a
-> a
-> a
-> a
-> Digit a
-> FingerTree (Node a)
-> FingerTree (Node a)
addDigits4 FingerTree (Node a)
m1 (One a
a) a
b a
c a
d a
e (One a
f) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a -> Node a -> FingerTree (Node a) -> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> FingerTree a -> FingerTree a
appendTree2 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (One a
a) a
b a
c a
d a
e (Two a
f a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (One a
a) a
b a
c a
d a
e (Three a
f a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (One a
a) a
b a
c a
d a
e (Four a
f a
g a
h a
i) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d a
e a
f (One a
g) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
d a
e) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
f a
g) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d a
e a
f (Two a
g a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d a
e a
f (Three a
g a
h a
i) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Two a
a a
b) a
c a
d a
e a
f (Four a
g a
h a
i a
j) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
i a
j) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e a
f a
g (One a
h) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e a
f a
g (Two a
h a
i) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e a
f a
g (Three a
h a
i a
j) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
i a
j) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Three a
a a
b a
c) a
d a
e a
f a
g (Four a
h a
i a
j a
k) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
j a
k) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g a
h (One a
i) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree3 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g a
h (Two a
i a
j) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
g a
h) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
i a
j) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g a
h (Three a
i a
j a
k) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) (a -> a -> Node a
forall a. Measured a => a -> a -> Node a
node2 a
j a
k) FingerTree (Node a)
m2
addDigits4 FingerTree (Node a)
m1 (Four a
a a
b a
c a
d) a
e a
f a
g a
h (Four a
i a
j a
k a
l) FingerTree (Node a)
m2 =
FingerTree (Node a)
-> Node a
-> Node a
-> Node a
-> Node a
-> FingerTree (Node a)
-> FingerTree (Node a)
forall a.
Measured a =>
FingerTree a -> a -> a -> a -> a -> FingerTree a -> FingerTree a
appendTree4 FingerTree (Node a)
m1 (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
a a
b a
c) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
d a
e a
f) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
g a
h a
i) (a -> a -> a -> Node a
forall a. Measured a => a -> a -> a -> Node a
node3 a
j a
k a
l) FingerTree (Node a)
m2
split :: (Measured a) =>
Measure -> FingerTree a -> (FingerTree a, FingerTree a)
split :: Int -> FingerTree a -> (FingerTree a, FingerTree a)
split Int
_ FingerTree a
Empty = (FingerTree a
forall a. FingerTree a
Empty, FingerTree a
forall a. FingerTree a
Empty)
split Int
p FingerTree a
xs
| (FingerTree a -> Int
forall a. Measured a => a -> Int
measure FingerTree a
xs) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
p = (FingerTree a
l, a
x a -> FingerTree a -> FingerTree a
forall a. Measured a => a -> FingerTree a -> FingerTree a
<| FingerTree a
r)
| Bool
otherwise = (FingerTree a
xs, FingerTree a
forall a. FingerTree a
Empty)
where
Split FingerTree a
l a
x FingerTree a
r = Int -> Int -> FingerTree a -> Split (FingerTree a) a
forall a.
Measured a =>
Int -> Int -> FingerTree a -> Split (FingerTree a) a
splitTree Int
p Int
0 FingerTree a
xs
data Split t a = Split t a t
splitTree :: (Measured a) =>
Measure -> Measure -> FingerTree a -> Split (FingerTree a) a
splitTree :: Int -> Int -> FingerTree a -> Split (FingerTree a) a
splitTree Int
_ Int
_ FingerTree a
Empty = String -> Split (FingerTree a) a
forall a. String -> a
illegal_argument String
"splitTree"
splitTree Int
_ Int
_ (Single a
x) = FingerTree a -> a -> FingerTree a -> Split (FingerTree a) a
forall t a. t -> a -> t -> Split t a
Split FingerTree a
forall a. FingerTree a
Empty a
x FingerTree a
forall a. FingerTree a
Empty
splitTree Int
p Int
i (Deep Int
_ Digit a
pr FingerTree (Node a)
m Digit a
sf)
| Int
vpr Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = let Split Maybe (Digit a)
l a
x Maybe (Digit a)
r = Int -> Int -> Digit a -> Split (Maybe (Digit a)) a
forall a.
Measured a =>
Int -> Int -> Digit a -> Split (Maybe (Digit a)) a
splitDigit Int
p Int
i Digit a
pr
in FingerTree a -> a -> FingerTree a -> Split (FingerTree a) a
forall t a. t -> a -> t -> Split t a
Split (FingerTree a
-> (Digit a -> FingerTree a) -> Maybe (Digit a) -> FingerTree a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FingerTree a
forall a. FingerTree a
Empty Digit a -> FingerTree a
forall a. Measured a => Digit a -> FingerTree a
digitToTree Maybe (Digit a)
l) a
x (Maybe (Digit a) -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Maybe (Digit a) -> FingerTree (Node a) -> Digit a -> FingerTree a
deepL Maybe (Digit a)
r FingerTree (Node a)
m Digit a
sf)
| Int
vm Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = let Split FingerTree (Node a)
ml Node a
xs FingerTree (Node a)
mr = Int
-> Int
-> FingerTree (Node a)
-> Split (FingerTree (Node a)) (Node a)
forall a.
Measured a =>
Int -> Int -> FingerTree a -> Split (FingerTree a) a
splitTree Int
p Int
vpr FingerTree (Node a)
m
Split Maybe (Digit a)
l a
x Maybe (Digit a)
r = Int -> Int -> Node a -> Split (Maybe (Digit a)) a
forall a.
Measured a =>
Int -> Int -> Node a -> Split (Maybe (Digit a)) a
splitNode Int
p (Int
vpr Int -> Int -> Int
forall a. Num a => a -> a -> a
+ FingerTree (Node a) -> Int
forall a. Measured a => a -> Int
measure FingerTree (Node a)
ml) Node a
xs
in FingerTree a -> a -> FingerTree a -> Split (FingerTree a) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> FingerTree (Node a) -> Maybe (Digit a) -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Maybe (Digit a) -> FingerTree a
deepR Digit a
pr FingerTree (Node a)
ml Maybe (Digit a)
l) a
x (Maybe (Digit a) -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Maybe (Digit a) -> FingerTree (Node a) -> Digit a -> FingerTree a
deepL Maybe (Digit a)
r FingerTree (Node a)
mr Digit a
sf)
| Bool
otherwise = let Split Maybe (Digit a)
l a
x Maybe (Digit a)
r = Int -> Int -> Digit a -> Split (Maybe (Digit a)) a
forall a.
Measured a =>
Int -> Int -> Digit a -> Split (Maybe (Digit a)) a
splitDigit Int
p Int
vm Digit a
sf
in FingerTree a -> a -> FingerTree a -> Split (FingerTree a) a
forall t a. t -> a -> t -> Split t a
Split (Digit a -> FingerTree (Node a) -> Maybe (Digit a) -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Maybe (Digit a) -> FingerTree a
deepR Digit a
pr FingerTree (Node a)
m Maybe (Digit a)
l) a
x (FingerTree a
-> (Digit a -> FingerTree a) -> Maybe (Digit a) -> FingerTree a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FingerTree a
forall a. FingerTree a
Empty Digit a -> FingerTree a
forall a. Measured a => Digit a -> FingerTree a
digitToTree Maybe (Digit a)
r)
where
vpr :: Int
vpr = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Digit a -> Int
forall a. Measured a => a -> Int
measure Digit a
pr
vm :: Int
vm = Int
vpr Int -> Int -> Int
forall a. Num a => a -> a -> a
+ FingerTree (Node a) -> Int
forall a. Measured a => a -> Int
measure FingerTree (Node a)
m
deepL :: (Measured a) =>
Maybe (Digit a) -> FingerTree (Node a) -> Digit a -> FingerTree a
deepL :: Maybe (Digit a) -> FingerTree (Node a) -> Digit a -> FingerTree a
deepL Maybe (Digit a)
Nothing FingerTree (Node a)
m Digit a
sf = FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
FingerTree (Node a) -> Digit a -> FingerTree a
rotL FingerTree (Node a)
m Digit a
sf
deepL (Just Digit a
pr) FingerTree (Node a)
m Digit a
sf = Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep Digit a
pr FingerTree (Node a)
m Digit a
sf
deepR :: (Measured a) =>
Digit a -> FingerTree (Node a) -> Maybe (Digit a) -> FingerTree a
deepR :: Digit a -> FingerTree (Node a) -> Maybe (Digit a) -> FingerTree a
deepR Digit a
pr FingerTree (Node a)
m Maybe (Digit a)
Nothing = Digit a -> FingerTree (Node a) -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> FingerTree a
rotR Digit a
pr FingerTree (Node a)
m
deepR Digit a
pr FingerTree (Node a)
m (Just Digit a
sf) = Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
forall a.
Measured a =>
Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a
deep Digit a
pr FingerTree (Node a)
m Digit a
sf
splitNode :: (Measured a) =>
Measure -> Measure -> Node a -> Split (Maybe (Digit a)) a
splitNode :: Int -> Int -> Node a -> Split (Maybe (Digit a)) a
splitNode Int
p Int
i (Node2 Int
_ a
a a
b)
| Int
va Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = 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 :: Int
va = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a
splitNode Int
p Int
i (Node3 Int
_ a
a a
b a
c)
| Int
va Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = 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))
| Int
vab Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = 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 :: Int
va = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a
vab :: Int
vab = Int
va Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
b
splitDigit :: (Measured a) =>
Measure -> Measure -> Digit a -> Split (Maybe (Digit a)) a
splitDigit :: Int -> Int -> Digit a -> Split (Maybe (Digit a)) a
splitDigit Int
_ Int
i (One a
a) = Int
i Int -> Split (Maybe (Digit a)) a -> Split (Maybe (Digit a)) a
`seq` Maybe (Digit a)
-> a -> Maybe (Digit a) -> Split (Maybe (Digit a)) a
forall t a. t -> a -> t -> Split t a
Split Maybe (Digit a)
forall a. Maybe a
Nothing a
a Maybe (Digit a)
forall a. Maybe a
Nothing
splitDigit Int
p Int
i (Two a
a a
b)
| Int
va Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = 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 :: Int
va = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a
splitDigit Int
p Int
i (Three a
a a
b a
c)
| Int
va Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = 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))
| Int
vab Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = 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 :: Int
va = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a
vab :: Int
vab = Int
va Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
b
splitDigit Int
p Int
i (Four a
a a
b a
c a
d)
| Int
va Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = 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))
| Int
vab Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = 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))
| Int
vabc Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p = 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 :: Int
va = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
a
vab :: Int
vab = Int
va Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
b
vabc :: Int
vabc = Int
vab Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Measured a => a -> Int
measure a
c
illegal_argument :: String -> a
illegal_argument :: String -> a
illegal_argument String
name =
String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"Logic error: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" called with illegal argument"
class ToBuilder a where
toBuilder :: a -> Builder
instance ToBuilder S.ByteString where
toBuilder :: ByteString -> Builder
toBuilder ByteString
x = ByteString -> Builder
byteString ByteString
x
instance ToBuilder a => ToBuilder (FingerTree a) where
toBuilder :: FingerTree a -> Builder
toBuilder FingerTree a
ft =
case FingerTree a
ft of
FingerTree a
Empty -> Builder
forall a. Monoid a => a
mempty
Single a
x -> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
x
Deep Int
_ Digit a
a FingerTree (Node a)
b Digit a
c -> Digit a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder Digit a
a Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> FingerTree (Node a) -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder FingerTree (Node a)
b Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Digit a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder Digit a
c
instance ToBuilder a => ToBuilder (Node a) where
toBuilder :: Node a -> Builder
toBuilder Node a
n =
case Node a
n of
Node2 Int
_ a
a a
b -> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
a Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
b
Node3 Int
_ a
a a
b a
c -> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
a Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
b Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
c
instance ToBuilder a => ToBuilder (Digit a) where
toBuilder :: Digit a -> Builder
toBuilder Digit a
d =
case Digit a
d of
One a
a -> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
a
Two a
a a
b -> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
a Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
b
Three a
a a
b a
c -> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
a Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
b Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
c
Four a
a a
b a
c a
e -> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
a Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
b Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
c Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. ToBuilder a => a -> Builder
toBuilder a
e