module Database.MySQL.Nem.Result
( ResultError(..)
, Result(..)
) where
import Control.Exception (Exception, throw)
import Data.Int
import Data.Scientific (Scientific, fromFloatDigits)
import Data.Time.Calendar (Day)
import Data.Time.LocalTime (LocalTime)
import Data.Typeable (Typeable)
import Database.MySQL.Base (MySQLValue(..), ColumnDef(..))
import qualified Data.ByteString as ByteString (ByteString, unpack)
import qualified Data.Text as Text (Text, unpack)
data ResultError
= Incompatible { errColumnName :: String
, errHaskellType :: String
, errMessage :: String}
| ConversionFailed { errColumnName :: String
, errHaskellType :: String
, errMessage :: String}
deriving (Eq, Show, Typeable)
instance Exception ResultError
class Result a where
convert :: ColumnDef -> MySQLValue -> a
instance (Result a) =>
Result (Maybe a) where
convert def val =
case val of
MySQLNull -> Nothing
_ -> Just $ convert def val
instance Result Int where
convert = intConvert "Int"
instance Result Int8 where
convert def val =
case val of
MySQLInt8U i -> fromIntegral i
MySQLInt8 i -> fromIntegral i
_ -> throw $ conversionFailed "Int8" val def
instance Result Int16 where
convert def val =
case val of
MySQLInt8U i -> fromIntegral i
MySQLInt16U i -> fromIntegral i
MySQLInt8 i -> fromIntegral i
MySQLInt16 i -> fromIntegral i
_ -> throw $ conversionFailed "Int16" val def
instance Result Int32 where
convert def val =
case val of
MySQLInt8U i -> fromIntegral i
MySQLInt16U i -> fromIntegral i
MySQLInt32U i -> fromIntegral i
MySQLInt8 i -> fromIntegral i
MySQLInt16 i -> fromIntegral i
MySQLInt32 i -> fromIntegral i
_ -> throw $ conversionFailed "Int32" val def
instance Result Int64 where
convert = intConvert "Int64"
instance Result Float where
convert def val =
case val of
MySQLFloat f -> f
_ -> throw $ conversionFailed "Float" val def
instance Result Double where
convert def val =
case val of
MySQLDouble d -> d
_ -> throw $ conversionFailed "Double" val def
instance Result Text.Text where
convert def val =
case val of
MySQLText t -> t
_ -> throw $ conversionFailed "Text" val def
instance Result String where
convert def val =
case val of
MySQLText t -> Text.unpack t
_ -> throw $ conversionFailed "String" val def
instance Result ByteString.ByteString where
convert def val =
case val of
MySQLBytes t -> t
_ -> throw $ conversionFailed "ByteString" val def
instance Result Day where
convert def val =
case val of
MySQLDate d -> d
_ -> throw $ conversionFailed "Day" val def
instance Result LocalTime where
convert def val =
case val of
MySQLDateTime d -> d
MySQLTimeStamp d -> d
_ -> throw $ conversionFailed "LocalTime" val def
instance Result Scientific where
convert def val =
case val of
MySQLDecimal d -> d
MySQLFloat f -> fromFloatDigits f
MySQLDouble f -> fromFloatDigits f
MySQLInt8U i -> fromIntegral i
MySQLInt16U i -> fromIntegral i
MySQLInt32U i -> fromIntegral i
MySQLInt64U i -> fromIntegral i
MySQLInt8 i -> fromIntegral i
MySQLInt16 i -> fromIntegral i
MySQLInt32 i -> fromIntegral i
MySQLInt64 i -> fromIntegral i
_ -> throw $ conversionFailed "Scientific" val def
intConvert
:: Num a
=> String -> ColumnDef -> MySQLValue -> a
intConvert t def val =
case val of
MySQLInt8U i -> fromIntegral i
MySQLInt16U i -> fromIntegral i
MySQLInt32U i -> fromIntegral i
MySQLInt64U i -> fromIntegral i
MySQLInt8 i -> fromIntegral i
MySQLInt16 i -> fromIntegral i
MySQLInt32 i -> fromIntegral i
MySQLInt64 i -> fromIntegral i
_ -> throw $ conversionFailed t val def
conversionFailed t v def =
Incompatible
(show . ByteString.unpack . columnName $ def)
t
("Could not convert: " ++ show v)