{-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor #-}
{-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}
{-# LANGUAGE PatternGuards, ScopedTypeVariables #-}
{-# LANGUAGE RecordWildCards #-}
module Database.PostgreSQL.Simple.FromField
(
FromField(..)
, FieldParser
, Conversion()
, runConversion
, conversionMap
, conversionError
, ResultError(..)
, returnError
, Field
, typename
, TypeInfo(..)
, Attribute(..)
, typeInfo
, typeInfoByOid
, name
, tableOid
, tableColumn
, format
, typeOid
, PQ.Oid(..)
, PQ.Format(..)
, pgArrayFieldParser
, optionalField
, fromJSONField
) where
#include "MachDeps.h"
import Control.Applicative ( (<|>), (<$>), pure, (*>), (<*) )
import Control.Concurrent.MVar (MVar, newMVar)
import Control.Exception (Exception)
import qualified Data.Aeson as JSON
import qualified Data.Aeson.Internal as JSON
import qualified Data.Aeson.Parser as JSON (value')
import Data.Attoparsec.ByteString.Char8 hiding (Result)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B
import Data.Int (Int16, Int32, Int64)
import Data.IORef (IORef, newIORef)
import Data.Ratio (Ratio)
import Data.Time ( UTCTime, ZonedTime, LocalTime, Day, TimeOfDay )
import Data.Typeable (Typeable, typeOf)
import Data.Vector (Vector)
import Data.Vector.Mutable (IOVector)
import qualified Data.Vector as V
import Database.PostgreSQL.Simple.Internal
import Database.PostgreSQL.Simple.Compat
import Database.PostgreSQL.Simple.Ok
import Database.PostgreSQL.Simple.Types
import Database.PostgreSQL.Simple.TypeInfo as TI
import qualified Database.PostgreSQL.Simple.TypeInfo.Static as TI
import Database.PostgreSQL.Simple.Time
import Database.PostgreSQL.Simple.Arrays as Arrays
import qualified Database.PostgreSQL.LibPQ as PQ
import qualified Data.ByteString as SB
import qualified Data.ByteString.Char8 as B8
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
import Data.CaseInsensitive (CI)
import qualified Data.CaseInsensitive as CI
import Data.UUID.Types (UUID)
import qualified Data.UUID.Types as UUID
import Data.Scientific (Scientific)
import GHC.Real (infinity, notANumber)
data ResultError = Incompatible { errSQLType :: String
, errSQLTableOid :: Maybe PQ.Oid
, errSQLField :: String
, errHaskellType :: String
, errMessage :: String }
| UnexpectedNull { errSQLType :: String
, errSQLTableOid :: Maybe PQ.Oid
, errSQLField :: String
, errHaskellType :: String
, errMessage :: String }
| ConversionFailed { errSQLType :: String
, errSQLTableOid :: Maybe PQ.Oid
, errSQLField :: String
, errHaskellType :: String
, errMessage :: String }
deriving (Eq, Show, Typeable)
instance Exception ResultError
left :: Exception a => a -> Conversion b
left = conversionError
type FieldParser a = Field -> Maybe ByteString -> Conversion a
class FromField a where
fromField :: FieldParser a
typename :: Field -> Conversion ByteString
typename field = typname <$> typeInfo field
typeInfo :: Field -> Conversion TypeInfo
typeInfo Field{..} = Conversion $ \conn -> do
Ok <$> (getTypeInfo conn typeOid)
typeInfoByOid :: PQ.Oid -> Conversion TypeInfo
typeInfoByOid oid = Conversion $ \conn -> do
Ok <$> (getTypeInfo conn oid)
name :: Field -> Maybe ByteString
name Field{..} = unsafeDupablePerformIO (PQ.fname result column)
tableOid :: Field -> Maybe PQ.Oid
tableOid Field{..} = toMaybeOid (unsafeDupablePerformIO (PQ.ftable result column))
where
toMaybeOid x
= if x == PQ.invalidOid
then Nothing
else Just x
tableColumn :: Field -> Int
tableColumn Field{..} = fromCol (unsafeDupablePerformIO (PQ.ftablecol result column))
where
fromCol (PQ.Col x) = fromIntegral x
format :: Field -> PQ.Format
format Field{..} = unsafeDupablePerformIO (PQ.fformat result column)
instance FromField () where
fromField f _bs
| typeOid f /= TI.voidOid = returnError Incompatible f ""
| otherwise = pure ()
instance FromField a => FromField (Maybe a) where
fromField = optionalField fromField
optionalField :: FieldParser a -> FieldParser (Maybe a)
optionalField p f mv =
case mv of
Nothing -> pure Nothing
Just _ -> Just <$> p f mv
{-# INLINE optionalField #-}
instance FromField Null where
fromField _ Nothing = pure Null
fromField f (Just _) = returnError ConversionFailed f "data is not null"
instance FromField Bool where
fromField f bs
| typeOid f /= TI.boolOid = returnError Incompatible f ""
| bs == Nothing = returnError UnexpectedNull f ""
| bs == Just "t" = pure True
| bs == Just "f" = pure False
| otherwise = returnError ConversionFailed f ""
instance FromField Char where
fromField f bs0 =
if (eq TI.charOid \/ eq TI.bpcharOid) (typeOid f)
then case bs0 of
Nothing -> returnError UnexpectedNull f ""
Just bs -> if B.length bs /= 1
then returnError ConversionFailed f "length not 1"
else return $! (B.head bs)
else returnError Incompatible f ""
instance FromField Int16 where
fromField = atto ok16 $ signed decimal
instance FromField Int32 where
fromField = atto ok32 $ signed decimal
#if WORD_SIZE_IN_BITS < 64
#else
#endif
instance FromField Int where
fromField = atto okInt $ signed decimal
instance FromField Int64 where
fromField = atto ok64 $ signed decimal
instance FromField Integer where
fromField = atto ok64 $ signed decimal
instance FromField Float where
fromField = atto ok (realToFrac <$> pg_double)
where ok = eq TI.float4Oid \/ eq TI.int2Oid
instance FromField Double where
fromField = atto ok pg_double
where ok = eq TI.float4Oid \/ eq TI.float8Oid \/ eq TI.int2Oid \/ eq TI.int4Oid
instance FromField (Ratio Integer) where
fromField = atto ok pg_rational
where ok = eq TI.float4Oid \/ eq TI.float8Oid \/ eq TI.int2Oid \/ eq TI.int4Oid \/ eq TI.int8Oid \/ eq TI.numericOid
instance FromField Scientific where
fromField = atto ok rational
where ok = eq TI.float4Oid \/ eq TI.float8Oid \/ eq TI.int2Oid \/ eq TI.int4Oid \/ eq TI.int8Oid \/ eq TI.numericOid
unBinary :: Binary t -> t
unBinary (Binary x) = x
pg_double :: Parser Double
pg_double
= (string "NaN" *> pure ( 0 / 0))
<|> (string "Infinity" *> pure ( 1 / 0))
<|> (string "-Infinity" *> pure (-1 / 0))
<|> double
pg_rational :: Parser Rational
pg_rational
= (string "NaN" *> pure notANumber )
<|> (string "Infinity" *> pure infinity )
<|> (string "-Infinity" *> pure (-infinity))
<|> rational
instance FromField SB.ByteString where
fromField f dat = if typeOid f == TI.byteaOid
then unBinary <$> fromField f dat
else doFromField f okText' pure dat
instance FromField PQ.Oid where
fromField f dat = PQ.Oid <$> atto (== TI.oidOid) decimal f dat
instance FromField LB.ByteString where
fromField f dat = LB.fromChunks . (:[]) <$> fromField f dat
unescapeBytea :: Field -> SB.ByteString
-> Conversion (Binary SB.ByteString)
unescapeBytea f str' = case unsafeDupablePerformIO (PQ.unescapeBytea str') of
Nothing -> returnError ConversionFailed f "unescapeBytea failed"
Just str -> pure (Binary str)
instance FromField (Binary SB.ByteString) where
fromField f dat = case format f of
PQ.Text -> doFromField f okBinary (unescapeBytea f) dat
PQ.Binary -> doFromField f okBinary (pure . Binary) dat
instance FromField (Binary LB.ByteString) where
fromField f dat = Binary . LB.fromChunks . (:[]) . unBinary <$> fromField f dat
instance FromField ST.Text where
fromField f = doFromField f okText $ (either left pure . ST.decodeUtf8')
instance FromField LT.Text where
fromField f dat = LT.fromStrict <$> fromField f dat
instance FromField (CI ST.Text) where
fromField f mdat = do
typ <- typename f
if typ /= "citext"
then returnError Incompatible f ""
else case mdat of
Nothing -> returnError UnexpectedNull f ""
Just dat -> either left (pure . CI.mk)
(ST.decodeUtf8' dat)
instance FromField (CI LT.Text) where
fromField f mdat = do
typ <- typename f
if typ /= "citext"
then returnError Incompatible f ""
else case mdat of
Nothing -> returnError UnexpectedNull f ""
Just dat -> either left (pure . CI.mk . LT.fromStrict)
(ST.decodeUtf8' dat)
instance FromField [Char] where
fromField f dat = ST.unpack <$> fromField f dat
instance FromField UTCTime where
fromField = ff TI.timestamptzOid "UTCTime" parseUTCTime
instance FromField ZonedTime where
fromField = ff TI.timestamptzOid "ZonedTime" parseZonedTime
instance FromField LocalTime where
fromField = ff TI.timestampOid "LocalTime" parseLocalTime
instance FromField Day where
fromField = ff TI.dateOid "Day" parseDay
instance FromField TimeOfDay where
fromField = ff TI.timeOid "TimeOfDay" parseTimeOfDay
instance FromField UTCTimestamp where
fromField = ff TI.timestamptzOid "UTCTimestamp" parseUTCTimestamp
instance FromField ZonedTimestamp where
fromField = ff TI.timestamptzOid "ZonedTimestamp" parseZonedTimestamp
instance FromField LocalTimestamp where
fromField = ff TI.timestampOid "LocalTimestamp" parseLocalTimestamp
instance FromField Date where
fromField = ff TI.dateOid "Date" parseDate
ff :: PQ.Oid -> String -> (B8.ByteString -> Either String a)
-> Field -> Maybe B8.ByteString -> Conversion a
ff compatOid hsType parseBS f mstr =
if typeOid f /= compatOid
then err Incompatible ""
else case mstr of
Nothing -> err UnexpectedNull ""
Just str -> case parseBS str of
Left msg -> err ConversionFailed msg
Right val -> return val
where
err errC msg = do
typnam <- typename f
left $ errC (B8.unpack typnam)
(tableOid f)
(maybe "" B8.unpack (name f))
hsType
msg
{-# INLINE ff #-}
instance (FromField a, FromField b) => FromField (Either a b) where
fromField f dat = (Right <$> fromField f dat)
<|> (Left <$> fromField f dat)
instance (FromField a, Typeable a) => FromField (PGArray a) where
fromField = pgArrayFieldParser fromField
pgArrayFieldParser :: Typeable a => FieldParser a -> FieldParser (PGArray a)
pgArrayFieldParser fieldParser f mdat = do
info <- typeInfo f
case info of
TI.Array{} ->
case mdat of
Nothing -> returnError UnexpectedNull f ""
Just dat -> do
case parseOnly (fromArray fieldParser info f) dat of
Left err -> returnError ConversionFailed f err
Right conv -> PGArray <$> conv
_ -> returnError Incompatible f ""
fromArray :: FieldParser a -> TypeInfo -> Field -> Parser (Conversion [a])
fromArray fieldParser typInfo f = sequence . (parseIt <$>) <$> array delim
where
delim = typdelim (typelem typInfo)
fElem = f{ typeOid = typoid (typelem typInfo) }
parseIt item =
fieldParser f' $ if item == Arrays.Plain "NULL" then Nothing else Just item'
where
item' = fmt delim item
f' | Arrays.Array _ <- item = f
| otherwise = fElem
instance (FromField a, Typeable a) => FromField (Vector a) where
fromField f v = V.fromList . fromPGArray <$> fromField f v
instance (FromField a, Typeable a) => FromField (IOVector a) where
fromField f v = liftConversion . V.unsafeThaw =<< fromField f v
instance FromField UUID where
fromField f mbs =
if typeOid f /= TI.uuidOid
then returnError Incompatible f ""
else case mbs of
Nothing -> returnError UnexpectedNull f ""
Just bs ->
case UUID.fromASCIIBytes bs of
Nothing -> returnError ConversionFailed f "Invalid UUID"
Just uuid -> pure uuid
instance FromField JSON.Value where
fromField f mbs = parseBS =<< fromFieldJSONByteString f mbs
where parseBS bs = case parseOnly (JSON.value' <* endOfInput) bs of
Left err -> returnError ConversionFailed f err
Right val -> pure val
fromFieldJSONByteString :: Field -> Maybe ByteString -> Conversion ByteString
fromFieldJSONByteString f mbs =
if typeOid f /= TI.jsonOid && typeOid f /= TI.jsonbOid
then returnError Incompatible f ""
else case mbs of
Nothing -> returnError UnexpectedNull f ""
Just bs -> pure bs
fromJSONField :: (JSON.FromJSON a, Typeable a) => FieldParser a
fromJSONField f mbBs = do
value <- fromField f mbBs
case JSON.ifromJSON value of
JSON.IError path err -> returnError ConversionFailed f $
"JSON decoding error: " ++ (JSON.formatError path err)
JSON.ISuccess x -> pure x
instance FromField a => FromField (IORef a) where
fromField f v = liftConversion . newIORef =<< fromField f v
instance FromField a => FromField (MVar a) where
fromField f v = liftConversion . newMVar =<< fromField f v
type Compat = PQ.Oid -> Bool
okText, okText', okBinary, ok16, ok32, ok64, okInt :: Compat
okText = eq TI.nameOid \/ eq TI.textOid \/ eq TI.charOid
\/ eq TI.bpcharOid \/ eq TI.varcharOid
okText' = eq TI.nameOid \/ eq TI.textOid \/ eq TI.charOid
\/ eq TI.bpcharOid \/ eq TI.varcharOid \/ eq TI.unknownOid
okBinary = eq TI.byteaOid
ok16 = eq TI.int2Oid
ok32 = eq TI.int2Oid \/ eq TI.int4Oid
ok64 = eq TI.int2Oid \/ eq TI.int4Oid \/ eq TI.int8Oid
#if WORD_SIZE_IN_BITS < 64
okInt = ok32
#else
okInt = ok64
#endif
eq :: PQ.Oid -> PQ.Oid -> Bool
eq = (==)
{-# INLINE eq #-}
infixr 2 \/
(\/) :: (PQ.Oid -> Bool)
-> (PQ.Oid -> Bool)
-> (PQ.Oid -> Bool)
f \/ g = \x -> f x || g x
{-# INLINE (\/) #-}
doFromField :: forall a . (Typeable a)
=> Field -> Compat -> (ByteString -> Conversion a)
-> Maybe ByteString -> Conversion a
doFromField f isCompat cvt (Just bs)
| isCompat (typeOid f) = cvt bs
| otherwise = returnError Incompatible f "types incompatible"
doFromField f _ _ _ = returnError UnexpectedNull f ""
returnError :: forall a err . (Typeable a, Exception err)
=> (String -> Maybe PQ.Oid -> String -> String -> String -> err)
-> Field -> String -> Conversion a
returnError mkErr f msg = do
typnam <- typename f
left $ mkErr (B.unpack typnam)
(tableOid f)
(maybe "" B.unpack (name f))
(show (typeOf (undefined :: a)))
msg
atto :: forall a. (Typeable a)
=> Compat -> Parser a -> Field -> Maybe ByteString
-> Conversion a
atto types p0 f dat = doFromField f types (go p0) dat
where
go :: Parser a -> ByteString -> Conversion a
go p s =
case parseOnly p s of
Left err -> returnError ConversionFailed f err
Right v -> pure v