{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module Text.Trifecta.Rope
( Rope(..)
, rope
, ropeBS
, Strand(..)
, strand
, strands
, grabRest
, grabLine
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString as Strict
import qualified Data.ByteString.Lazy as Lazy
import qualified Data.ByteString.UTF8 as UTF8
import Data.Data
import Data.FingerTree as FingerTree
import Data.Foldable (toList)
import Data.Hashable
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
import Data.Semigroup.Reducer
import GHC.Generics
import Text.Trifecta.Delta
import Text.Trifecta.Util.Combinators as Util
data Strand
= Strand {-# UNPACK #-} !ByteString !Delta
| Skipping !Delta
deriving (Show, Data, Typeable, Generic)
strand :: ByteString -> Strand
strand bs = Strand bs (delta bs)
instance Measured Delta Strand where
measure (Strand _ s) = delta s
measure (Skipping d) = d
instance Hashable Strand
instance HasDelta Strand where
delta = measure
instance HasBytes Strand where
bytes (Strand _ d) = bytes d
bytes _ = 0
data Rope = Rope !Delta !(FingerTree Delta Strand) deriving Show
rope :: FingerTree Delta Strand -> Rope
rope r = Rope (measure r) r
ropeBS :: ByteString -> Rope
ropeBS = rope . singleton . strand
strands :: Rope -> FingerTree Delta Strand
strands (Rope _ r) = r
grabRest
:: Delta
-> Rope
-> r
-> (Delta -> Lazy.ByteString -> r)
-> r
grabRest offset input failure success = trim (delta l) (bytes offset - bytes l) (toList r) where
trim offset' 0 (Strand str _ : xs) = go offset' str xs
trim _ k (Strand str _ : xs) = go offset (Strict.drop (fromIntegral k) str) xs
trim offset' k (Skipping p : xs) = trim (offset' <> p) k xs
trim _ _ [] = failure
go offset' str strands'
= success offset' (Lazy.fromChunks (str : [ a | Strand a _ <- strands' ]))
(l, r) = splitRopeAt offset input
splitRopeAt :: Delta -> Rope -> (FingerTree Delta Strand, FingerTree Delta Strand)
splitRopeAt splitPos = FingerTree.split (\pos -> bytes pos > bytes splitPos) . strands
grabLine
:: Delta
-> Rope
-> r
-> (Delta -> Strict.ByteString -> r)
-> r
grabLine offset input failure success
= grabRest offset input failure (\d -> success d . Util.fromLazy . Util.takeLine)
instance HasBytes Rope where
bytes = bytes . measure
instance HasDelta Rope where
delta = measure
instance Measured Delta Rope where
measure (Rope s _) = s
instance Monoid Rope where
mempty = Rope mempty mempty
mappend = (<>)
instance Semigroup Rope where
Rope mx x <> Rope my y = Rope (mx <> my) (x `mappend` y)
instance Reducer Rope Rope where
unit = id
instance Reducer Strand Rope where
unit s = rope (FingerTree.singleton s)
cons s (Rope mt t) = Rope (delta s `mappend` mt) (s <| t)
snoc (Rope mt t) !s = Rope (mt `mappend` delta s) (t |> s)
instance Reducer Strict.ByteString Rope where
unit = unit . strand
cons = cons . strand
snoc r = snoc r . strand
instance Reducer [Char] Rope where
unit = unit . strand . UTF8.fromString
cons = cons . strand . UTF8.fromString
snoc r = snoc r . strand . UTF8.fromString