module Database.MySQL.Simple.Param
    (
      Action(..)
    , Param(..)
    , inQuotes
    ) where
import Blaze.ByteString.Builder (Builder, fromByteString, fromLazyByteString,
                                 toByteString)
import Blaze.ByteString.Builder.Char8 (fromChar)
import Blaze.Text (integral, double, float)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Base16 as B16
import qualified Data.ByteString.Base16.Lazy as L16
import Data.Int (Int8, Int16, Int32, Int64)
import Data.List (intersperse)
import Data.Monoid (mappend)
import Data.Time.Calendar (Day, showGregorian)
import Data.Time.Clock (UTCTime)
import Data.Time.Format (formatTime)
import Data.Time.LocalTime (TimeOfDay)
import Data.Typeable (Typeable)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import Database.MySQL.Simple.Types (Binary(..), In(..), Null)
import System.Locale (defaultTimeLocale)
import qualified Blaze.ByteString.Builder.Char.Utf8 as Utf8
import qualified Data.ByteString as SB
import qualified Data.ByteString.Lazy as LB
import qualified Data.Text as ST
import qualified Data.Text.Encoding as ST
import qualified Data.Text.Lazy as LT
data Action =
    Plain Builder
    
    
    
    
  | Escape ByteString
    
    
    
  | Many [Action]
    
    deriving (Typeable)
instance Show Action where
    show (Plain b)  = "Plain " ++ show (toByteString b)
    show (Escape b) = "Escape " ++ show b
    show (Many b)   = "Many " ++ show b
class Param a where
    render :: a -> Action
    
instance Param Action where
    render a = a
    
instance (Param a) => Param (Maybe a) where
    render Nothing  = renderNull
    render (Just a) = render a
    
instance (Param a) => Param (In [a]) where
    render (In []) = Plain $ fromByteString "(null)"
    render (In xs) = Many $
        Plain (fromChar '(') :
        (intersperse (Plain (fromChar ',')) . map render $ xs) ++
        [Plain (fromChar ')')]
instance Param (Binary SB.ByteString) where
    render (Binary bs) = Plain $ fromByteString "x'" `mappend`
                                 fromByteString (B16.encode bs) `mappend`
                                 fromChar '\''
instance Param (Binary LB.ByteString) where
    render (Binary bs) = Plain $ fromByteString "x'" `mappend`
                                 fromLazyByteString (L16.encode bs) `mappend`
                                 fromChar '\''
renderNull :: Action
renderNull = Plain (fromByteString "null")
instance Param Null where
    render _ = renderNull
    
instance Param Bool where
    render = Plain . integral . fromEnum
    
instance Param Int8 where
    render = Plain . integral
    
instance Param Int16 where
    render = Plain . integral
    
instance Param Int32 where
    render = Plain . integral
    
instance Param Int where
    render = Plain . integral
    
instance Param Int64 where
    render = Plain . integral
    
instance Param Integer where
    render = Plain . integral
    
instance Param Word8 where
    render = Plain . integral
    
instance Param Word16 where
    render = Plain . integral
    
instance Param Word32 where
    render = Plain . integral
    
instance Param Word where
    render = Plain . integral
    
instance Param Word64 where
    render = Plain . integral
    
instance Param Float where
    render v | isNaN v || isInfinite v = renderNull
             | otherwise               = Plain (float v)
    
instance Param Double where
    render v | isNaN v || isInfinite v = renderNull
             | otherwise               = Plain (double v)
    
instance Param SB.ByteString where
    render = Escape
    
instance Param LB.ByteString where
    render = render . SB.concat . LB.toChunks
    
instance Param ST.Text where
    render = Escape . ST.encodeUtf8
    
instance Param [Char] where
    render = Escape . toByteString . Utf8.fromString
    
instance Param LT.Text where
    render = render . LT.toStrict
    
instance Param UTCTime where
    render = Plain . Utf8.fromString . formatTime defaultTimeLocale "'%F %T'"
    
instance Param Day where
    render = Plain . inQuotes . Utf8.fromString . showGregorian
    
instance Param TimeOfDay where
    render = Plain . inQuotes . Utf8.fromString . show
    
inQuotes :: Builder -> Builder
inQuotes b = quote `mappend` b `mappend` quote
  where quote = Utf8.fromChar '\''