{-# LANGUAGE StandaloneDeriving, DeriveDataTypeable, ScopedTypeVariables, ExistentialQuantification, GeneralizedNewtypeDeriving, MultiParamTypeClasses, TemplateHaskell #-} -- Copyright 2008 JP Bernardy -- | Basic types useful everywhere we play with buffers. module Yi.Buffer.Basic where import Prelude (reverse) import Data.Binary import Yi.Prelude import qualified Data.ByteString.UTF8 as UTF8 import qualified Data.ByteString.Lazy.UTF8 as LazyUTF8 import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as LB import Data.Char (ord) import Data.Typeable import Data.DeriveTH import Data.Derive.Binary -- | Direction of movement inside a buffer data Direction = Backward | Forward deriving (Eq,Ord,Typeable,Show) $(derive makeBinary ''Direction) reverseDir :: Direction -> Direction reverseDir Forward = Backward reverseDir Backward = Forward -- | reverse if Backward mayReverse :: Direction -> [a] -> [a] mayReverse Forward = id mayReverse Backward = reverse -- | 'direction' is in the same style of 'maybe' or 'either' functions, -- It takes one argument per direction (backward, then forward) and a -- direction to select the output. directionElim :: Direction -> a -> a -> a directionElim Backward b _ = b directionElim Forward _ f = f -- | A mark in a buffer newtype Mark = Mark {markId::Int} deriving (Eq, Ord, Show, Typeable, Binary) -- | Reference to a buffer. newtype BufferRef = BufferRef Int deriving (Eq, Ord, Typeable, Binary) deriving instance Num BufferRef instance Show BufferRef where show (BufferRef r) = "B#" ++ show r -- | A point in a buffer newtype Point = Point {fromPoint :: Int} -- offset in the buffer (#bytes, NOT codepoints) deriving (Eq, Ord, Enum, Bounded, Typeable, Binary) deriving instance Num Point deriving instance Real Point deriving instance Integral Point instance Show Point where show (Point p) = show p -- | Size of a buffer region newtype Size = Size {fromSize :: Int} -- size in bytes (#bytes, NOT codepoints) deriving (Show, Eq, Ord, Num, Enum, Real, Integral, Binary) instance SemiNum Point Size where Point p +~ Size s = Point (p + s) Point p -~ Size s = Point (p - s) Point p ~- Point q = Size (abs (p - q)) utf8Size :: String -> Size utf8Size = Size . B.length . UTF8.fromString utf8CharSize :: Char -> Size utf8CharSize c = case ord c of i | i < 0x80 -> 1 | i < 0x800 -> 2 | i < 0x10000 -> 3 | otherwise -> 4 -- fromUTF8ByteString :: B.ByteString -> String -- fromUTF8ByteString = UTF8.toString fromString :: String -> LB.ByteString fromString = LazyUTF8.fromString