{-# language BangPatterns #-}
{-# language GeneralizedNewtypeDeriving #-}
{-# language MultiParamTypeClasses #-}
module Data.Rope.UTF16.Internal where
import Data.Foldable as Foldable
import Data.Function
import Data.List
import Data.Semigroup
import Data.String
import Data.Text(Text)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as Lazy
import qualified Data.Text.Unsafe as Unsafe
import Data.Rope.UTF16.Internal.Position
import Data.Rope.UTF16.Internal.Text
import Data.SplayTree(SplayTree)
import qualified Data.SplayTree as SplayTree
data Chunk = Chunk { chunkText :: !Text, chunkMeasure :: !Position }
instance Show Chunk where
show (Chunk t _) = show t
instance Semigroup Chunk where
Chunk t1 m1 <> Chunk t2 m2 = Chunk (t1 <> t2) (m1 <> m2)
chunk :: Text -> Chunk
chunk t = Chunk t $ Position len $ go 0 $ RowColumn 0 0
where
len = Unsafe.lengthWord16 t
go i !v
| i >= len = v
| otherwise = case Unsafe.iter t i of
Unsafe.Iter '\n' delta -> go (i + delta) (v <> RowColumn 1 0)
Unsafe.Iter _ delta -> go (i + delta) (v <> RowColumn 0 delta)
instance SplayTree.Measured Position Chunk where
measure (Chunk _ m) = m
newtype Rope = Rope { unrope :: SplayTree Position Chunk }
deriving (SplayTree.Measured Position, Show)
chunkLength :: Int
chunkLength = 1000
instance Semigroup Rope where
Rope r1 <> Rope r2 = case (SplayTree.unsnoc r1, SplayTree.uncons r2) of
(Nothing, _) -> Rope r2
(_, Nothing) -> Rope r1
(Just (r1', a), Just (b, r2'))
| codeUnits (SplayTree.measure a) + codeUnits (SplayTree.measure b) <= chunkLength
-> Rope $ r1' <> ((a <> b) SplayTree.<| r2')
| otherwise
-> Rope $ r1' <> (a SplayTree.<| b SplayTree.<| r2')
instance Monoid Rope where
mempty = Rope mempty
mappend = (<>)
instance Eq Rope where
(==) = (==) `on` toText
instance Ord Rope where
compare = compare `on` toText
instance IsString Rope where
fromString = fromText . Text.pack
{-# INLINE null #-}
null :: Rope -> Bool
null (Rope r) = SplayTree.null r
length :: Rope -> Int
length = codeUnits . SplayTree.measure
rows :: Rope -> Int
rows (Rope r) = row $ rowColumn $ SplayTree.measure r
columns :: Rope -> Int
columns (Rope r) = column $ rowColumn $ SplayTree.measure r
toText :: Rope -> Text
toText = Text.concat . toChunks
toLazyText :: Rope -> Lazy.Text
toLazyText = Lazy.fromChunks . toChunks
fromText :: Text -> Rope
fromText t
| Text.null t = mempty
| otherwise = Rope $ go numChunks chunks
where
chunks = chunks16Of chunkLength t
numChunks = Prelude.length chunks
go !_ [] = mempty
go len cs = SplayTree.fork (go mid pre) (chunk c) (go (len - mid - 1) post)
where
(pre, c:post) = Prelude.splitAt mid cs
mid = len `div` 2
fromShortText :: Text -> Rope
fromShortText t
| Text.null t = mempty
| otherwise = Rope $ SplayTree.singleton $ chunk t
toString :: Rope -> String
toString = Foldable.concatMap Text.unpack . toChunks
map :: (Char -> Char) -> Rope -> Rope
map f (Rope r) = Rope $ SplayTree.map (chunk . Text.map f . chunkText) r
intercalate :: Rope -> [Rope] -> Rope
intercalate r rs = mconcat $ intersperse r rs
toChunks :: Rope -> [Text]
toChunks = fmap chunkText . toList . unrope
unconsChunk :: Rope -> Maybe (Text, Rope)
unconsChunk (Rope r) = case SplayTree.uncons r of
Nothing -> Nothing
Just (Chunk t _, r') -> Just (t, Rope r')
unsnocChunk :: Rope -> Maybe (Rope, Text)
unsnocChunk (Rope r) = case SplayTree.unsnoc r of
Nothing -> Nothing
Just (r', Chunk t _) -> Just (Rope r', t)
splitAt :: Int -> Rope -> (Rope, Rope)
splitAt n (Rope r) = case SplayTree.split ((> n) . codeUnits) r of
SplayTree.Outside
| n < 0 -> (mempty, Rope r)
| otherwise -> (Rope r, mempty)
SplayTree.Inside pre (Chunk t _) post -> (Rope pre <> fromShortText pret, fromShortText postt <> Rope post)
where
n' = n - codeUnits (SplayTree.measure pre)
(pret, postt) = split16At n' t
take :: Int -> Rope -> Rope
take n = fst . Data.Rope.UTF16.Internal.splitAt n
drop :: Int -> Rope -> Rope
drop n = snd . Data.Rope.UTF16.Internal.splitAt n
rowColumnCodeUnits :: RowColumn -> Rope -> Int
rowColumnCodeUnits v (Rope r) = case SplayTree.split ((> v) . rowColumn) r of
SplayTree.Outside
| v <= RowColumn 0 0 -> 0
| otherwise -> codeUnits $ SplayTree.measure r
SplayTree.Inside pre (Chunk t _) _ -> go 0 $ rowColumn prePos
where
prePos = SplayTree.measure pre
len = Unsafe.lengthWord16 t
go i !v'
| v <= v' || i >= len = codeUnits prePos + i
| otherwise = case Unsafe.iter t i of
Unsafe.Iter '\n' delta -> go (i + delta) (v' <> RowColumn 1 0)
Unsafe.Iter _ 2 | v == v' <> RowColumn 0 1 -> codeUnits prePos + i
Unsafe.Iter _ delta -> go (i + delta) (v' <> RowColumn 0 delta)
splitAtLine :: Int -> Rope -> (Rope, Rope)
splitAtLine r rope = Data.Rope.UTF16.Internal.splitAt i rope
where
i = rowColumnCodeUnits (RowColumn r 0) rope
span :: (Char -> Bool) -> Rope -> (Rope, Rope)
span f (Rope r) = case SplayTree.uncons r of
Nothing -> (mempty, mempty)
Just (t, r')
| Text.null postt -> (Rope (SplayTree.singleton t) <> pre', post')
| otherwise -> (fromShortText pret, fromShortText postt <> Rope r')
where
(pret, postt) = Text.span f $ chunkText t
(pre', post') = Data.Rope.UTF16.Internal.span f $ Rope r'
break :: (Char -> Bool) -> Rope -> (Rope, Rope)
break f = Data.Rope.UTF16.Internal.span (not . f)
takeWhile :: (Char -> Bool) -> Rope -> Rope
takeWhile f = fst . Data.Rope.UTF16.Internal.span f
dropWhile :: (Char -> Bool) -> Rope -> Rope
dropWhile f = snd . Data.Rope.UTF16.Internal.span f
foldl :: (a -> Char -> a) -> a -> Rope -> a
foldl f a (Rope r) = Foldable.foldl (\a' c -> Text.foldl f a' $ chunkText c) a r
foldl' :: (a -> Char -> a) -> a -> Rope -> a
foldl' f a (Rope r) = Foldable.foldl' (\a' c -> Text.foldl' f a' $ chunkText c) a r
foldr :: (Char -> a -> a) -> a -> Rope -> a
foldr f a (Rope r) = Foldable.foldr (\c a' -> Text.foldr f a' $ chunkText c) a r
any :: (Char -> Bool) -> Rope -> Bool
any p (Rope r) = getAny $ foldMap (Any . Text.any p . chunkText) r
all :: (Char -> Bool) -> Rope -> Bool
all p (Rope r) = getAll $ foldMap (All . Text.all p . chunkText) r