module System.Command.QQ.Embed
( Embed(..)
) where
import Control.Applicative
import Data.Int
import Data.Ratio (Ratio)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as Text.Lazy
import Data.Word
import Foreign.C.Types
class Embed a where
embed :: a -> String
default embed :: Show a => a -> String
embed = show
instance Embed Integer
instance Embed Int
instance Embed Int8
instance Embed Int16
instance Embed Int32
instance Embed Int64
instance Embed Word
instance Embed Word8
instance Embed Word16
instance Embed Word32
instance Embed Word64
instance Embed Float
instance Embed Double
instance Embed CChar
instance Embed CSChar
instance Embed CUChar
instance Embed CShort
instance Embed CUShort
instance Embed CInt
instance Embed CUInt
instance Embed CLong
instance Embed CULong
instance Embed CSize
instance Embed CLLong
instance Embed CULLong
instance Embed CFloat
instance Embed CDouble
instance a ~ Integer => Embed (Ratio a) where
embed = embed . (fromRational :: Rational -> Double)
instance Embed Char where
embed = pure
instance Embed String where
embed = id
instance Embed Text.Text where
embed = Text.unpack
instance Embed Text.Lazy.Text where
embed = Text.Lazy.unpack