module Rasa.Internal.Buffer
( Buffer
, HasBuffer(..)
, BufRef(..)
, text
, mkBuffer
, ref
) where
import Rasa.Internal.Extensions
import qualified Yi.Rope as Y
import Control.Lens hiding (matching)
import Data.Map as M
import Data.List
newtype BufRef =
BufRef Int
deriving (Show, Eq, Ord)
data Buffer = Buffer
{ _text' :: Y.YiString
, _bufExts' :: ExtMap
, _ref :: BufRef
}
makeLenses ''Buffer
instance HasExts Buffer where
exts = bufExts'
instance Show Buffer where
show b = "text:" ++ (Y.toString . Y.take 30 $ (b^.text)) ++ "...,\n"
++ "exts: " ++ extText ++ "}>\n"
where
extText = intercalate "\n" $ show <$> b^.exts.to M.toList
class HasBuffer a where
buffer :: Lens' a Buffer
instance HasBuffer Buffer where
buffer = lens id (flip const)
text :: HasBuffer b => Lens' b Y.YiString
text = buffer.text'
mkBuffer :: Y.YiString -> BufRef -> Buffer
mkBuffer txt bRef =
Buffer
{ _text' = txt
, _bufExts' = empty
, _ref = bRef
}