module Database.SQLite.Simple.ToField (ToField(..)) where
import Blaze.ByteString.Builder (toByteString)
import qualified Data.ByteString as SB
import qualified Data.ByteString.Lazy as LB
import Data.Int (Int8, Int16, Int32, Int64)
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Encoding as T
import Data.Time (Day, UTCTime)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import GHC.Float
import Database.SQLite3 as Base
import Database.SQLite.Simple.Types (Null)
import Database.SQLite.Simple.Time
class ToField a where
toField :: a -> SQLData
instance ToField SQLData where
toField a = a
instance (ToField a) => ToField (Maybe a) where
toField Nothing = Base.SQLNull
toField (Just a) = toField a
instance ToField Null where
toField _ = Base.SQLNull
instance ToField Bool where
toField False = SQLInteger 0
toField True = SQLInteger 1
instance ToField Int8 where
toField = SQLInteger . fromIntegral
instance ToField Int16 where
toField = SQLInteger . fromIntegral
instance ToField Int32 where
toField = SQLInteger . fromIntegral
instance ToField Int where
toField = SQLInteger . fromIntegral
instance ToField Int64 where
toField = SQLInteger . fromIntegral
instance ToField Integer where
toField = SQLInteger . fromIntegral
instance ToField Word8 where
toField = SQLInteger . fromIntegral
instance ToField Word16 where
toField = SQLInteger . fromIntegral
instance ToField Word32 where
toField = SQLInteger . fromIntegral
instance ToField Word where
toField = SQLInteger . fromIntegral
instance ToField Word64 where
toField = SQLInteger . fromIntegral
instance ToField Float where
toField = SQLFloat . float2Double
instance ToField Double where
toField = SQLFloat
instance ToField SB.ByteString where
toField = SQLBlob
instance ToField LB.ByteString where
toField = toField . SB.concat . LB.toChunks
instance ToField T.Text where
toField = SQLText
instance ToField [Char] where
toField = SQLText . T.pack
instance ToField LT.Text where
toField = toField . LT.toStrict
instance ToField UTCTime where
toField = SQLText . T.decodeUtf8 . toByteString . utcTimeToBuilder
instance ToField Day where
toField = SQLText . T.decodeUtf8 . toByteString . dayToBuilder