module Database.SQLite.Simple.FromField
(
FromField(..)
, FieldParser
, ResultError(..)
, Field
, fieldData
, returnError
) where
import Control.Applicative (Applicative, (<$>), pure)
import Control.Exception (SomeException(..), Exception)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy as LB
import Data.Int (Int16, Int32, Int64)
import Data.Time (UTCTime, Day)
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT
import Data.Typeable (Typeable, typeOf)
import GHC.Float (double2Float)
import Database.SQLite3 as Base
import Database.SQLite.Simple.Types
import Database.SQLite.Simple.Internal
import Database.SQLite.Simple.Ok
import Database.SQLite.Simple.Time
data ResultError = Incompatible { errSQLType :: String
, errHaskellType :: String
, errMessage :: String }
| UnexpectedNull { errSQLType :: String
, errHaskellType :: String
, errMessage :: String }
| ConversionFailed { errSQLType :: String
, errHaskellType :: String
, errMessage :: String }
deriving (Eq, Show, Typeable)
instance Exception ResultError
left :: Exception a => a -> Ok b
left = Errors . (:[]) . SomeException
type FieldParser a = Field -> Ok a
class FromField a where
fromField :: FieldParser a
instance (FromField a) => FromField (Maybe a) where
fromField (Field SQLNull _) = pure Nothing
fromField f = Just <$> fromField f
instance FromField Null where
fromField (Field SQLNull _) = pure Null
fromField f = returnError ConversionFailed f "data is not null"
takeInt :: (Num a, Typeable a) => Field -> Ok a
takeInt (Field (SQLInteger i) _) = Ok . fromIntegral $ i
takeInt f = returnError ConversionFailed f "need an int"
instance FromField Int16 where
fromField = takeInt
instance FromField Int32 where
fromField = takeInt
instance FromField Int where
fromField = takeInt
instance FromField Int64 where
fromField = takeInt
instance FromField Integer where
fromField = takeInt
instance FromField Double where
fromField (Field (SQLFloat flt) _) = Ok flt
fromField f = returnError ConversionFailed f "need a float"
instance FromField Float where
fromField (Field (SQLFloat flt) _) = Ok . double2Float $ flt
fromField f = returnError ConversionFailed f "need a float"
instance FromField Bool where
fromField f@(Field (SQLInteger b) _)
| (b == 0) || (b == 1) = Ok (b /= 0)
| otherwise = returnError ConversionFailed f ("bool must be 0 or 1, got " ++ show b)
fromField f = returnError ConversionFailed f "need a float"
instance FromField T.Text where
fromField (Field (SQLText txt) _) = Ok txt
fromField f = returnError ConversionFailed f "need a text"
instance FromField LT.Text where
fromField (Field (SQLText txt) _) = Ok . LT.fromStrict $ txt
fromField f = returnError ConversionFailed f "need a text"
instance FromField [Char] where
fromField (Field (SQLText t) _) = Ok $ T.unpack t
fromField f = returnError ConversionFailed f "expecting SQLText column type"
instance FromField ByteString where
fromField (Field (SQLBlob blb) _) = Ok blb
fromField f = returnError ConversionFailed f "expecting SQLBlob column type"
instance FromField LB.ByteString where
fromField (Field (SQLBlob blb) _) = Ok . LB.fromChunks $ [blb]
fromField f = returnError ConversionFailed f "expecting SQLBlob column type"
instance FromField UTCTime where
fromField f@(Field (SQLText t) _) =
case parseUTCTime t of
Right t -> Ok t
Left e -> returnError ConversionFailed f ("couldn't parse UTCTime field: " ++ e)
fromField f = returnError ConversionFailed f "expecting SQLText column type"
instance FromField Day where
fromField f@(Field (SQLText t) _) =
case parseDay t of
Right t -> Ok t
Left e -> returnError ConversionFailed f ("couldn't parse Day field: " ++ e)
fromField f = returnError ConversionFailed f "expecting SQLText column type"
fieldTypename :: Field -> String
fieldTypename = B.unpack . gettypename . result
fieldData :: Field -> SQLData
fieldData = result
returnError :: forall a err . (Typeable a, Exception err)
=> (String -> String -> String -> err)
-> Field -> String -> Ok a
returnError mkErr f = left . mkErr (fieldTypename f)
(show (typeOf (undefined :: a)))