module Data.Sext.Class
( Sextable(..)
)
where
import Prelude
import qualified Prelude as P
#ifdef WITH_BS
import qualified Data.ByteString as B
import GHC.Word
#endif
#ifdef WITH_TEXT
import qualified Data.Text as T
#endif
import GHC.TypeLits
class Sextable a where
data Sext (i :: Nat) a
type Elem a
unsafeCreate :: a -> Sext i a
unwrap :: Sext i a -> a
length :: a -> Int
append :: a -> a -> a
replicate :: Int -> Elem a -> a
map :: (Elem a -> Elem a) -> a -> a
take :: Int -> a -> a
drop :: Int -> a -> a
instance (Show a, Sextable a) => Show (Sext i a) where
show s = show $ unwrap s
instance Sextable [a] where
type Elem [a] = a
data Sext i [a] = List [a]
unsafeCreate = List
unwrap (List l) = l
length = P.length
append = (P.++)
replicate = P.replicate
map = P.map
take = P.take
drop = P.drop
#ifdef WITH_TEXT
instance Sextable T.Text where
type Elem T.Text = Char
data Sext i T.Text = Text T.Text
unsafeCreate = Text
unwrap (Text t) = t
length = T.length
append = T.append
replicate = \n c -> T.replicate n (T.singleton c)
map = T.map
take = T.take
drop = T.drop
#endif
#ifdef WITH_BS
instance Sextable B.ByteString where
type Elem B.ByteString = Word8
data Sext i B.ByteString = ByteString B.ByteString
unsafeCreate = ByteString
unwrap (ByteString t) = t
length = B.length
append = B.append
replicate = B.replicate
map = B.map
take = B.take
drop = B.drop
#endif