module Text.StringLike (StringLike(..), fromString, castString) where
import Data.String
import Data.Typeable
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as LBS
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT
class (Typeable a, Eq a, IsString a) => StringLike a where
empty :: a
cons :: Char -> a -> a
uncons :: a -> Maybe (Char, a)
toString :: a -> String
fromChar :: Char -> a
strConcat :: [a] -> a
strNull :: a -> Bool
append :: a -> a -> a
castString :: (StringLike a, StringLike b) => a -> b
castString = fromString . toString
instance StringLike String where
uncons [] = Nothing
uncons (x:xs) = Just (x, xs)
toString = id
fromChar = (:[])
strConcat = concat
empty = []
strNull = null
cons c = (c:)
append = (++)
instance StringLike BS.ByteString where
uncons = BS.uncons
toString = BS.unpack
fromChar = BS.singleton
strConcat = BS.concat
empty = BS.empty
strNull = BS.null
cons = BS.cons
append = BS.append
instance StringLike LBS.ByteString where
uncons = LBS.uncons
toString = LBS.unpack
fromChar = LBS.singleton
strConcat = LBS.concat
empty = LBS.empty
strNull = LBS.null
cons = LBS.cons
append = LBS.append
instance StringLike T.Text where
uncons = T.uncons
toString = T.unpack
fromChar = T.singleton
strConcat = T.concat
empty = T.empty
strNull = T.null
cons = T.cons
append = T.append
instance StringLike LT.Text where
uncons = LT.uncons
toString = LT.unpack
fromChar = LT.singleton
strConcat = LT.concat
empty = LT.empty
strNull = LT.null
cons = LT.cons
append = LT.append