{-# LANGUAGE TypeFamilies #-}
module Text.Reprinter.StringLike
( StringLike(..)
, IsString(..)
) where
import Data.List (uncons)
import Data.String (IsString(..))
import qualified Data.Text as TextStrict
import qualified Data.Text.Lazy as TextLazy
import qualified Data.ByteString.Char8 as BSCStrict
import qualified Data.ByteString.Lazy.Char8 as BSCLazy
class (Monoid a, IsString a) => StringLike a where
slCons :: Char -> a -> a
slUncons :: a -> Maybe (Char, a)
slNull :: a -> Bool
slReverse :: a -> a
slToString :: a -> String
instance (a ~ Char) => StringLike [a] where
slCons :: Char -> [a] -> [a]
slCons = (:)
slUncons :: [a] -> Maybe (Char, [a])
slUncons = [a] -> Maybe (Char, [a])
forall a. [a] -> Maybe (a, [a])
uncons
slNull :: [a] -> Bool
slNull = [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null
slReverse :: [a] -> [a]
slReverse = [a] -> [a]
forall a. [a] -> [a]
reverse
slToString :: [a] -> String
slToString = [a] -> String
forall a. a -> a
id
instance StringLike TextStrict.Text where
slCons :: Char -> Text -> Text
slCons = Char -> Text -> Text
TextStrict.cons
slUncons :: Text -> Maybe (Char, Text)
slUncons = Text -> Maybe (Char, Text)
TextStrict.uncons
slNull :: Text -> Bool
slNull = Text -> Bool
TextStrict.null
slReverse :: Text -> Text
slReverse = Text -> Text
TextStrict.reverse
slToString :: Text -> String
slToString = Text -> String
TextStrict.unpack
instance StringLike TextLazy.Text where
slCons :: Char -> Text -> Text
slCons = Char -> Text -> Text
TextLazy.cons
slUncons :: Text -> Maybe (Char, Text)
slUncons = Text -> Maybe (Char, Text)
TextLazy.uncons
slNull :: Text -> Bool
slNull = Text -> Bool
TextLazy.null
slReverse :: Text -> Text
slReverse = Text -> Text
TextLazy.reverse
slToString :: Text -> String
slToString = Text -> String
TextLazy.unpack
instance StringLike BSCStrict.ByteString where
slCons :: Char -> ByteString -> ByteString
slCons = Char -> ByteString -> ByteString
BSCStrict.cons
slUncons :: ByteString -> Maybe (Char, ByteString)
slUncons = ByteString -> Maybe (Char, ByteString)
BSCStrict.uncons
slNull :: ByteString -> Bool
slNull = ByteString -> Bool
BSCStrict.null
slReverse :: ByteString -> ByteString
slReverse = ByteString -> ByteString
BSCStrict.reverse
slToString :: ByteString -> String
slToString = ByteString -> String
BSCStrict.unpack
instance StringLike BSCLazy.ByteString where
slCons :: Char -> ByteString -> ByteString
slCons = Char -> ByteString -> ByteString
BSCLazy.cons
slUncons :: ByteString -> Maybe (Char, ByteString)
slUncons = ByteString -> Maybe (Char, ByteString)
BSCLazy.uncons
slNull :: ByteString -> Bool
slNull = ByteString -> Bool
BSCLazy.null
slReverse :: ByteString -> ByteString
slReverse = ByteString -> ByteString
BSCLazy.reverse
slToString :: ByteString -> String
slToString = ByteString -> String
BSCLazy.unpack