{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Core.Text.Rope
(
Rope
, emptyRope
, singletonRope
, packRope
, replicateRope
, replicateChar
, widthRope
, unconsRope
, splitRope
, takeRope
, insertRope
, containsCharacter
, findIndexRope
, Textual (fromRope, intoRope, appendRope)
, hWrite
, unRope
, nullRope
, unsafeIntoRope
, copyRope
, Width (..)
) where
import Control.DeepSeq (NFData (..))
import Core.Text.Bytes
import Data.ByteString qualified as B (ByteString)
import Data.ByteString.Builder qualified as B
( Builder
, hPutBuilder
, toLazyByteString
)
import Data.ByteString.Lazy qualified as L
( ByteString
, foldrChunks
, toStrict
)
import Data.FingerTree qualified as F
( FingerTree
, Measured (..)
, SearchResult (..)
, ViewL (..)
, empty
, null
, search
, singleton
, viewl
, (<|)
, (><)
, (|>)
)
import Data.Foldable (foldl', toList)
import Data.Hashable (Hashable, hashWithSalt)
import Data.String (IsString (..))
import Data.Text qualified as T (Text)
import Data.Text.Lazy qualified as U
( Text
, foldrChunks
, fromChunks
, toStrict
)
import Data.Text.Lazy.Builder qualified as U
( Builder
, fromText
, toLazyText
)
import Data.Text.Short qualified as S
( ShortText
, any
, append
, empty
, findIndex
, fromByteString
, fromText
, length
, pack
, replicate
, singleton
, splitAt
, toBuilder
, toText
, uncons
, unpack
)
import Data.Text.Short.Unsafe qualified as S (fromByteStringUnsafe)
import GHC.Generics (Generic)
import Prettyprinter (Pretty (..), emptyDoc)
import System.IO (Handle)
newtype Rope
= Rope (F.FingerTree Width S.ShortText)
deriving (forall x. Rep Rope x -> Rope
forall x. Rope -> Rep Rope x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Rope x -> Rope
$cfrom :: forall x. Rope -> Rep Rope x
Generic)
instance NFData Rope where
rnf :: Rope -> ()
rnf (Rope FingerTree Width ShortText
x) = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (\ShortText
piece -> forall a. NFData a => a -> ()
rnf ShortText
piece) FingerTree Width ShortText
x
instance Show Rope where
show :: Rope -> [Char]
show Rope
text = [Char]
"\"" forall a. [a] -> [a] -> [a]
++ forall α. Textual α => Rope -> α
fromRope Rope
text forall a. [a] -> [a] -> [a]
++ [Char]
"\""
instance Eq Rope where
== :: Rope -> Rope -> Bool
(==) (Rope FingerTree Width ShortText
x1) (Rope FingerTree Width ShortText
x2) = forall a. Eq a => a -> a -> Bool
(==) (forall {t :: * -> *}. Foldable t => t ShortText -> [Char]
stream FingerTree Width ShortText
x1) (forall {t :: * -> *}. Foldable t => t ShortText -> [Char]
stream FingerTree Width ShortText
x2)
where
stream :: t ShortText -> [Char]
stream t ShortText
x = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ShortText -> [Char]
S.unpack t ShortText
x
instance Ord Rope where
compare :: Rope -> Rope -> Ordering
compare (Rope FingerTree Width ShortText
x1) (Rope FingerTree Width ShortText
x2) = forall a. Ord a => a -> a -> Ordering
compare FingerTree Width ShortText
x1 FingerTree Width ShortText
x2
instance Pretty Rope where
pretty :: forall ann. Rope -> Doc ann
pretty (Rope FingerTree Width ShortText
x) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall a. Semigroup a => a -> a -> a
(<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a ann. Pretty a => a -> Doc ann
pretty forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> Text
S.toText) forall ann. Doc ann
emptyDoc FingerTree Width ShortText
x
unRope :: Rope -> F.FingerTree Width S.ShortText
unRope :: Rope -> FingerTree Width ShortText
unRope (Rope FingerTree Width ShortText
x) = FingerTree Width ShortText
x
{-# INLINE unRope #-}
newtype Width = Width Int
deriving (Width -> Width -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Width -> Width -> Bool
$c/= :: Width -> Width -> Bool
== :: Width -> Width -> Bool
$c== :: Width -> Width -> Bool
Eq, Eq Width
Width -> Width -> Bool
Width -> Width -> Ordering
Width -> Width -> Width
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
min :: Width -> Width -> Width
$cmin :: Width -> Width -> Width
max :: Width -> Width -> Width
$cmax :: Width -> Width -> Width
>= :: Width -> Width -> Bool
$c>= :: Width -> Width -> Bool
> :: Width -> Width -> Bool
$c> :: Width -> Width -> Bool
<= :: Width -> Width -> Bool
$c<= :: Width -> Width -> Bool
< :: Width -> Width -> Bool
$c< :: Width -> Width -> Bool
compare :: Width -> Width -> Ordering
$ccompare :: Width -> Width -> Ordering
Ord, Int -> Width -> ShowS
[Width] -> ShowS
Width -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Width] -> ShowS
$cshowList :: [Width] -> ShowS
show :: Width -> [Char]
$cshow :: Width -> [Char]
showsPrec :: Int -> Width -> ShowS
$cshowsPrec :: Int -> Width -> ShowS
Show, Integer -> Width
Width -> Width
Width -> Width -> Width
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Width
$cfromInteger :: Integer -> Width
signum :: Width -> Width
$csignum :: Width -> Width
abs :: Width -> Width
$cabs :: Width -> Width
negate :: Width -> Width
$cnegate :: Width -> Width
* :: Width -> Width -> Width
$c* :: Width -> Width -> Width
- :: Width -> Width -> Width
$c- :: Width -> Width -> Width
+ :: Width -> Width -> Width
$c+ :: Width -> Width -> Width
Num, forall x. Rep Width x -> Width
forall x. Width -> Rep Width x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Width x -> Width
$cfrom :: forall x. Width -> Rep Width x
Generic)
instance F.Measured Width S.ShortText where
measure :: S.ShortText -> Width
measure :: ShortText -> Width
measure ShortText
piece = Int -> Width
Width (ShortText -> Int
S.length ShortText
piece)
instance Semigroup Width where
<> :: Width -> Width -> Width
(<>) (Width Int
w1) (Width Int
w2) = Int -> Width
Width (Int
w1 forall a. Num a => a -> a -> a
+ Int
w2)
instance Monoid Width where
mempty :: Width
mempty = Int -> Width
Width Int
0
mappend :: Width -> Width -> Width
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance IsString Rope where
fromString :: [Char] -> Rope
fromString [Char]
"" = Rope
emptyRope
fromString [Char]
xs = FingerTree Width ShortText -> Rope
Rope forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v a. Measured v a => a -> FingerTree v a
F.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShortText
S.pack forall a b. (a -> b) -> a -> b
$ [Char]
xs
instance Semigroup Rope where
<> :: Rope -> Rope -> Rope
(<>) text1 :: Rope
text1@(Rope FingerTree Width ShortText
x1) text2 :: Rope
text2@(Rope FingerTree Width ShortText
x2) =
if forall v a. FingerTree v a -> Bool
F.null FingerTree Width ShortText
x2
then Rope
text1
else
if forall v a. FingerTree v a -> Bool
F.null FingerTree Width ShortText
x1
then Rope
text2
else FingerTree Width ShortText -> Rope
Rope (forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
(F.><) FingerTree Width ShortText
x1 FingerTree Width ShortText
x2)
instance Monoid Rope where
mempty :: Rope
mempty = Rope
emptyRope
mappend :: Rope -> Rope -> Rope
mappend = forall a. Semigroup a => a -> a -> a
(<>)
emptyRope :: Rope
emptyRope :: Rope
emptyRope = FingerTree Width ShortText -> Rope
Rope forall v a. Measured v a => FingerTree v a
F.empty
{-# INLINEABLE emptyRope #-}
singletonRope :: Char -> Rope
singletonRope :: Char -> Rope
singletonRope = FingerTree Width ShortText -> Rope
Rope forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v a. Measured v a => a -> FingerTree v a
F.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShortText
S.singleton
packRope :: String -> Rope
packRope :: [Char] -> Rope
packRope [Char]
xs = FingerTree Width ShortText -> Rope
Rope forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v a. Measured v a => a -> FingerTree v a
F.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShortText
S.pack forall a b. (a -> b) -> a -> b
$ [Char]
xs
replicateRope :: Int -> Rope -> Rope
replicateRope :: Int -> Rope -> Rope
replicateRope Int
count (Rope FingerTree Width ShortText
x) =
let x' :: FingerTree Width ShortText
x' = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\Int
_ FingerTree Width ShortText
acc -> forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
(F.><) FingerTree Width ShortText
x FingerTree Width ShortText
acc) forall v a. Measured v a => FingerTree v a
F.empty [Int
1 .. Int
count]
in FingerTree Width ShortText -> Rope
Rope FingerTree Width ShortText
x'
replicateChar :: Int -> Char -> Rope
replicateChar :: Int -> Char -> Rope
replicateChar Int
count = FingerTree Width ShortText -> Rope
Rope forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v a. Measured v a => a -> FingerTree v a
F.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShortText -> ShortText
S.replicate Int
count forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShortText
S.singleton
widthRope :: Rope -> Int
widthRope :: Rope -> Int
widthRope Rope
text =
let x :: FingerTree Width ShortText
x = Rope -> FingerTree Width ShortText
unRope Rope
text
(Width Int
w) = forall v a. Measured v a => a -> v
F.measure FingerTree Width ShortText
x
in Int
w
nullRope :: Rope -> Bool
nullRope :: Rope -> Bool
nullRope Rope
text = Rope -> Int
widthRope Rope
text forall a. Eq a => a -> a -> Bool
== Int
0
unconsRope :: Rope -> Maybe (Char, Rope)
unconsRope :: Rope -> Maybe (Char, Rope)
unconsRope Rope
text =
let x :: FingerTree Width ShortText
x = Rope -> FingerTree Width ShortText
unRope Rope
text
in case forall v a.
Measured v a =>
FingerTree v a -> ViewL (FingerTree v) a
F.viewl FingerTree Width ShortText
x of
ViewL (FingerTree Width) ShortText
F.EmptyL -> forall a. Maybe a
Nothing
(F.:<) ShortText
piece FingerTree Width ShortText
x' ->
case ShortText -> Maybe (Char, ShortText)
S.uncons ShortText
piece of
Maybe (Char, ShortText)
Nothing -> forall a. Maybe a
Nothing
Just (Char
c, ShortText
piece') -> forall a. a -> Maybe a
Just (Char
c, FingerTree Width ShortText -> Rope
Rope (forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
(F.<|) ShortText
piece' FingerTree Width ShortText
x'))
splitRope :: Int -> Rope -> (Rope, Rope)
splitRope :: Int -> Rope -> (Rope, Rope)
splitRope Int
i text :: Rope
text@(Rope FingerTree Width ShortText
x) =
let pos :: Width
pos = Int -> Width
Width Int
i
result :: SearchResult Width ShortText
result = forall v a.
Measured v a =>
(v -> v -> Bool) -> FingerTree v a -> SearchResult v a
F.search (\Width
w1 Width
_ -> Width
w1 forall a. Ord a => a -> a -> Bool
>= Width
pos) FingerTree Width ShortText
x
in case SearchResult Width ShortText
result of
F.Position FingerTree Width ShortText
before ShortText
piece FingerTree Width ShortText
after ->
let (Width Int
w) = forall v a. Measured v a => a -> v
F.measure FingerTree Width ShortText
before
(ShortText
one, ShortText
two) = Int -> ShortText -> (ShortText, ShortText)
S.splitAt (Int
i forall a. Num a => a -> a -> a
- Int
w) ShortText
piece
in (FingerTree Width ShortText -> Rope
Rope (forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
(F.|>) FingerTree Width ShortText
before ShortText
one), FingerTree Width ShortText -> Rope
Rope (forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
(F.<|) ShortText
two FingerTree Width ShortText
after))
SearchResult Width ShortText
F.OnLeft -> (FingerTree Width ShortText -> Rope
Rope forall v a. Measured v a => FingerTree v a
F.empty, Rope
text)
SearchResult Width ShortText
F.OnRight -> (Rope
text, FingerTree Width ShortText -> Rope
Rope forall v a. Measured v a => FingerTree v a
F.empty)
SearchResult Width ShortText
F.Nowhere -> forall a. HasCallStack => [Char] -> a
error [Char]
"Position not found in split. Probable cause: predicate function given not monotonic. This is supposed to be unreachable"
takeRope :: Int -> Rope -> Rope
takeRope :: Int -> Rope -> Rope
takeRope Int
i Rope
text =
let (Rope
before, Rope
_) = Int -> Rope -> (Rope, Rope)
splitRope Int
i Rope
text
in Rope
before
insertRope :: Int -> Rope -> Rope -> Rope
insertRope :: Int -> Rope -> Rope -> Rope
insertRope Int
0 (Rope FingerTree Width ShortText
new) (Rope FingerTree Width ShortText
x) = FingerTree Width ShortText -> Rope
Rope (forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
(F.><) FingerTree Width ShortText
new FingerTree Width ShortText
x)
insertRope Int
i (Rope FingerTree Width ShortText
new) Rope
text =
let (Rope FingerTree Width ShortText
before, Rope FingerTree Width ShortText
after) = Int -> Rope -> (Rope, Rope)
splitRope Int
i Rope
text
in FingerTree Width ShortText -> Rope
Rope (forall a. Monoid a => [a] -> a
mconcat [FingerTree Width ShortText
before, FingerTree Width ShortText
new, FingerTree Width ShortText
after])
findIndexRope :: (Char -> Bool) -> Rope -> Maybe Int
findIndexRope :: (Char -> Bool) -> Rope -> Maybe Int
findIndexRope Char -> Bool
predicate = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (Maybe Int, Int) -> ShortText -> (Maybe Int, Int)
f (forall a. Maybe a
Nothing, Int
0) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rope -> FingerTree Width ShortText
unRope
where
f :: (Maybe Int, Int) -> S.ShortText -> (Maybe Int, Int)
f :: (Maybe Int, Int) -> ShortText -> (Maybe Int, Int)
f (Maybe Int, Int)
acc ShortText
piece = case (Maybe Int, Int)
acc of
(Just Int
j, Int
_) -> (forall a. a -> Maybe a
Just Int
j, Int
0)
(Maybe Int
Nothing, !Int
i) -> case (Char -> Bool) -> ShortText -> Maybe Int
S.findIndex Char -> Bool
predicate ShortText
piece of
Maybe Int
Nothing -> (forall a. Maybe a
Nothing, Int
i forall a. Num a => a -> a -> a
+ ShortText -> Int
S.length ShortText
piece)
Just !Int
j -> (forall a. a -> Maybe a
Just (Int
i forall a. Num a => a -> a -> a
+ Int
j), Int
0)
instance Hashable Rope where
hashWithSalt :: Int -> Rope -> Int
hashWithSalt Int
salt Rope
text =
let (Rope FingerTree Width ShortText
x') = Rope -> Rope
copyRope Rope
text
piece :: ShortText
piece = case forall v a.
Measured v a =>
FingerTree v a -> ViewL (FingerTree v) a
F.viewl FingerTree Width ShortText
x' of
ViewL (FingerTree Width) ShortText
F.EmptyL -> ShortText
S.empty
(F.:<) ShortText
first FingerTree Width ShortText
_ -> ShortText
first
in forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt ShortText
piece
copyRope :: Rope -> Rope
copyRope :: Rope -> Rope
copyRope text :: Rope
text@(Rope FingerTree Width ShortText
x) =
case forall v a.
Measured v a =>
FingerTree v a -> ViewL (FingerTree v) a
F.viewl FingerTree Width ShortText
x of
ViewL (FingerTree Width) ShortText
F.EmptyL -> Rope
text
(F.:<) ShortText
_ FingerTree Width ShortText
x' -> case forall v a.
Measured v a =>
FingerTree v a -> ViewL (FingerTree v) a
F.viewl FingerTree Width ShortText
x' of
ViewL (FingerTree Width) ShortText
F.EmptyL -> Rope
text
ViewL (FingerTree Width) ShortText
_ -> FingerTree Width ShortText -> Rope
Rope (forall v a. Measured v a => a -> FingerTree v a
F.singleton (forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ShortText -> ShortText -> ShortText
S.append ShortText
S.empty FingerTree Width ShortText
x))
class Textual α where
fromRope :: Rope -> α
intoRope :: α -> Rope
appendRope :: α -> Rope -> Rope
appendRope α
thing Rope
text = Rope
text forall a. Semigroup a => a -> a -> a
<> forall α. Textual α => α -> Rope
intoRope α
thing
instance Textual (F.FingerTree Width S.ShortText) where
fromRope :: Rope -> FingerTree Width ShortText
fromRope = Rope -> FingerTree Width ShortText
unRope
intoRope :: FingerTree Width ShortText -> Rope
intoRope = FingerTree Width ShortText -> Rope
Rope
instance Textual Rope where
fromRope :: Rope -> Rope
fromRope = forall a. a -> a
id
intoRope :: Rope -> Rope
intoRope = forall a. a -> a
id
appendRope :: Rope -> Rope -> Rope
appendRope (Rope FingerTree Width ShortText
x2) (Rope FingerTree Width ShortText
x1) = FingerTree Width ShortText -> Rope
Rope (forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
(F.><) FingerTree Width ShortText
x1 FingerTree Width ShortText
x2)
instance Textual S.ShortText where
fromRope :: Rope -> ShortText
fromRope = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ShortText -> ShortText -> ShortText
S.append ShortText
S.empty forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rope -> FingerTree Width ShortText
unRope
intoRope :: ShortText -> Rope
intoRope = FingerTree Width ShortText -> Rope
Rope forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v a. Measured v a => a -> FingerTree v a
F.singleton
appendRope :: ShortText -> Rope -> Rope
appendRope ShortText
piece (Rope FingerTree Width ShortText
x) = FingerTree Width ShortText -> Rope
Rope (forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
(F.|>) FingerTree Width ShortText
x ShortText
piece)
instance Textual T.Text where
fromRope :: Rope -> Text
fromRope = Text -> Text
U.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
U.toLazyText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ShortText -> Builder -> Builder
f forall a. Monoid a => a
mempty forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rope -> FingerTree Width ShortText
unRope
where
f :: S.ShortText -> U.Builder -> U.Builder
f :: ShortText -> Builder -> Builder
f ShortText
piece Builder
built = forall a. Semigroup a => a -> a -> a
(<>) (Text -> Builder
U.fromText (ShortText -> Text
S.toText ShortText
piece)) Builder
built
intoRope :: Text -> Rope
intoRope Text
t = FingerTree Width ShortText -> Rope
Rope (forall v a. Measured v a => a -> FingerTree v a
F.singleton (Text -> ShortText
S.fromText Text
t))
appendRope :: Text -> Rope -> Rope
appendRope Text
chunk (Rope FingerTree Width ShortText
x) = FingerTree Width ShortText -> Rope
Rope (forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
(F.|>) FingerTree Width ShortText
x (Text -> ShortText
S.fromText Text
chunk))
instance Textual U.Text where
fromRope :: Rope -> Text
fromRope (Rope FingerTree Width ShortText
x) = [Text] -> Text
U.fromChunks forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShortText -> Text
S.toText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ FingerTree Width ShortText
x
intoRope :: Text -> Rope
intoRope Text
t = FingerTree Width ShortText -> Rope
Rope (forall a. (Text -> a -> a) -> a -> Text -> a
U.foldrChunks (forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
(F.<|) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ShortText
S.fromText) forall v a. Measured v a => FingerTree v a
F.empty Text
t)
instance Textual B.ByteString where
fromRope :: Rope -> ByteString
fromRope = ByteString -> ByteString
L.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
B.toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ShortText -> Builder -> Builder
g forall a. Monoid a => a
mempty forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rope -> FingerTree Width ShortText
unRope
where
g :: ShortText -> Builder -> Builder
g ShortText
piece Builder
built = forall a. Semigroup a => a -> a -> a
(<>) (ShortText -> Builder
S.toBuilder ShortText
piece) Builder
built
intoRope :: ByteString -> Rope
intoRope ByteString
b' = case ByteString -> Maybe ShortText
S.fromByteString ByteString
b' of
Just ShortText
piece -> FingerTree Width ShortText -> Rope
Rope (forall v a. Measured v a => a -> FingerTree v a
F.singleton ShortText
piece)
Maybe ShortText
Nothing -> FingerTree Width ShortText -> Rope
Rope forall v a. Measured v a => FingerTree v a
F.empty
appendRope :: ByteString -> Rope -> Rope
appendRope ByteString
b' (Rope FingerTree Width ShortText
x) = case ByteString -> Maybe ShortText
S.fromByteString ByteString
b' of
Just ShortText
piece -> FingerTree Width ShortText -> Rope
Rope (forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
(F.|>) FingerTree Width ShortText
x ShortText
piece)
Maybe ShortText
Nothing -> (FingerTree Width ShortText -> Rope
Rope FingerTree Width ShortText
x)
instance Textual B.Builder where
fromRope :: Rope -> Builder
fromRope = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ShortText -> Builder -> Builder
g forall a. Monoid a => a
mempty forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rope -> FingerTree Width ShortText
unRope
where
g :: ShortText -> Builder -> Builder
g ShortText
piece Builder
built = forall a. Semigroup a => a -> a -> a
(<>) (ShortText -> Builder
S.toBuilder ShortText
piece) Builder
built
intoRope :: Builder -> Rope
intoRope =
FingerTree Width ShortText -> Rope
Rope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ( forall a. (ByteString -> a -> a) -> a -> ByteString -> a
L.foldrChunks
( forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
(F.<|) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortText
S.fromByteStringUnsafe
)
forall v a. Measured v a => FingerTree v a
F.empty
)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
B.toLazyByteString
instance Textual L.ByteString where
fromRope :: Rope -> ByteString
fromRope = Builder -> ByteString
B.toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ShortText -> Builder -> Builder
g forall a. Monoid a => a
mempty forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rope -> FingerTree Width ShortText
unRope
where
g :: ShortText -> Builder -> Builder
g ShortText
piece Builder
built = forall a. Semigroup a => a -> a -> a
(<>) (ShortText -> Builder
S.toBuilder ShortText
piece) Builder
built
intoRope :: ByteString -> Rope
intoRope ByteString
b' = FingerTree Width ShortText -> Rope
Rope (forall a. (ByteString -> a -> a) -> a -> ByteString -> a
L.foldrChunks (forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
(F.<|) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortText
check) forall v a. Measured v a => FingerTree v a
F.empty ByteString
b')
where
check :: ByteString -> ShortText
check ByteString
chunk = case ByteString -> Maybe ShortText
S.fromByteString ByteString
chunk of
Just ShortText
piece -> ShortText
piece
Maybe ShortText
Nothing -> ShortText
S.empty
instance Textual Bytes where
fromRope :: Rope -> Bytes
fromRope = forall α. Binary α => α -> Bytes
intoBytes forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall α. Textual α => Rope -> α
fromRope :: Rope -> B.ByteString)
intoRope :: Bytes -> Rope
intoRope = forall α. Textual α => α -> Rope
intoRope forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bytes -> ByteString
unBytes
instance Binary Rope where
fromBytes :: Bytes -> Rope
fromBytes = forall α. Textual α => α -> Rope
intoRope forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bytes -> ByteString
unBytes
intoBytes :: Rope -> Bytes
intoBytes = forall α. Binary α => α -> Bytes
intoBytes forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall α. Textual α => Rope -> α
fromRope :: Rope -> B.ByteString)
unsafeIntoRope :: B.ByteString -> Rope
unsafeIntoRope :: ByteString -> Rope
unsafeIntoRope = FingerTree Width ShortText -> Rope
Rope forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v a. Measured v a => a -> FingerTree v a
F.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortText
S.fromByteStringUnsafe
instance Textual [Char] where
fromRope :: Rope -> [Char]
fromRope (Rope FingerTree Width ShortText
x) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ShortText -> ShowS
h [] FingerTree Width ShortText
x
where
h :: ShortText -> ShowS
h ShortText
piece [Char]
string = (ShortText -> [Char]
S.unpack ShortText
piece) forall a. [a] -> [a] -> [a]
++ [Char]
string
intoRope :: [Char] -> Rope
intoRope = FingerTree Width ShortText -> Rope
Rope forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v a. Measured v a => a -> FingerTree v a
F.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShortText
S.pack
hWrite :: Handle -> Rope -> IO ()
hWrite :: Handle -> Rope -> IO ()
hWrite Handle
handle (Rope FingerTree Width ShortText
x) = Handle -> Builder -> IO ()
B.hPutBuilder Handle
handle (forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ShortText -> Builder -> Builder
j forall a. Monoid a => a
mempty FingerTree Width ShortText
x)
where
j :: ShortText -> Builder -> Builder
j ShortText
piece Builder
built = forall a. Semigroup a => a -> a -> a
(<>) (ShortText -> Builder
S.toBuilder ShortText
piece) Builder
built
containsCharacter :: Char -> Rope -> Bool
containsCharacter :: Char -> Rope -> Bool
containsCharacter Char
q (Rope FingerTree Width ShortText
x) = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ShortText -> Bool
j FingerTree Width ShortText
x
where
j :: ShortText -> Bool
j ShortText
piece = (Char -> Bool) -> ShortText -> Bool
S.any (\Char
c -> Char
c forall a. Eq a => a -> a -> Bool
== Char
q) ShortText
piece