Add RawField utility type
This commit is contained in:
parent
126b8ee6e9
commit
9628a4b57f
@ -15,6 +15,7 @@ module Database.PostgreSQL.Opium
|
||||
, ErrorPosition (..)
|
||||
, FromField (..)
|
||||
, FromRow (..)
|
||||
, RawField (..)
|
||||
, fetch_
|
||||
, toListColumnTable
|
||||
)
|
||||
@ -43,11 +44,12 @@ import qualified Data.Vector as Vector
|
||||
import qualified Database.PostgreSQL.LibPQ as LibPQ
|
||||
|
||||
import Database.PostgreSQL.Opium.Error (Error (..), ErrorPosition (..))
|
||||
import Database.PostgreSQL.Opium.FromField (FromField (..), fromField)
|
||||
import Database.PostgreSQL.Opium.FromField (FromField (..), fromField, RawField (..))
|
||||
|
||||
execParams :: Connection -> ByteString -> ExceptT Error IO Result
|
||||
execParams :: Connection -> Text -> ExceptT Error IO Result
|
||||
execParams conn query = do
|
||||
liftIO (LibPQ.execParams conn query [] LibPQ.Binary) >>= \case
|
||||
let queryBytes = Encoding.encodeUtf8 query
|
||||
liftIO (LibPQ.execParams conn queryBytes [] LibPQ.Binary) >>= \case
|
||||
Nothing ->
|
||||
except $ Left ErrorNoResult
|
||||
Just result -> do
|
||||
@ -58,7 +60,7 @@ execParams conn query = do
|
||||
Nothing -> pure result
|
||||
Just message -> except $ Left $ ErrorInvalidResult status $ Encoding.decodeUtf8 message
|
||||
|
||||
fetch_ :: forall a. FromRow a => Connection -> ByteString -> IO (Either Error [a])
|
||||
fetch_ :: forall a. FromRow a => Connection -> Text -> IO (Either Error [a])
|
||||
fetch_ conn query = runExceptT $ do
|
||||
result <- execParams conn query
|
||||
columnTable <- ExceptT $ getColumnTable @a Proxy result
|
||||
|
@ -3,8 +3,11 @@
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
|
||||
module Database.PostgreSQL.Opium.FromField
|
||||
( FromField (..)
|
||||
( -- * Decoding data from @libpq@
|
||||
FromField (..)
|
||||
, fromField
|
||||
-- * Utility types
|
||||
, RawField (..)
|
||||
) where
|
||||
|
||||
import Data.Attoparsec.ByteString (Parser)
|
||||
@ -37,15 +40,19 @@ class FromField a where
|
||||
validOid :: Proxy a -> Oid -> Bool
|
||||
parseField :: Parser a
|
||||
|
||||
-- | See https://www.postgresql.org/docs/current/datatype-binary.html.
|
||||
-- Accepts @bytea@.
|
||||
instance FromField ByteString where
|
||||
validOid Proxy = Oid.bytea
|
||||
parseField = AP.takeByteString
|
||||
|
||||
-- | See https://www.postgresql.org/docs/current/datatype-character.html.
|
||||
-- Accepts @text@, @character@ and @character varying@.
|
||||
instance FromField Text where
|
||||
validOid Proxy = Oid.text \/ Oid.character \/ Oid.characterVarying
|
||||
parseField = Encoding.decodeUtf8 <$> AP.takeByteString
|
||||
|
||||
-- Accepts @text@, @character@ and @character varying@.
|
||||
-- | See https://www.postgresql.org/docs/current/datatype-character.html.
|
||||
instance FromField String where
|
||||
validOid Proxy = validOid @Text Proxy
|
||||
@ -117,3 +124,10 @@ instance FromField Day where
|
||||
parseField = fromJulianDay . fromIntegral <$> intParser @Int32
|
||||
where
|
||||
fromJulianDay x = ModifiedJulianDay $ x + 51544
|
||||
|
||||
newtype RawField = RawField ByteString
|
||||
deriving (Eq, Show)
|
||||
|
||||
instance FromField RawField where
|
||||
validOid Proxy = const True
|
||||
parseField = RawField <$> AP.takeByteString
|
||||
|
@ -60,12 +60,12 @@ library
|
||||
|
||||
-- Modules exported by the library.
|
||||
exposed-modules:
|
||||
Database.PostgreSQL.Opium
|
||||
Database.PostgreSQL.Opium,
|
||||
Database.PostgreSQL.Opium.FromField,
|
||||
|
||||
-- Modules included in this library but not exported.
|
||||
other-modules:
|
||||
Database.PostgreSQL.Opium.Error,
|
||||
Database.PostgreSQL.Opium.FromField,
|
||||
Database.PostgreSQL.Opium.Oid
|
||||
|
||||
-- LANGUAGE extensions used by modules in this package.
|
||||
|
@ -11,6 +11,8 @@ import Database.PostgreSQL.Opium (FromRow)
|
||||
import GHC.Generics (Generic)
|
||||
import Test.Hspec (SpecWith, describe, it, shouldBe, shouldSatisfy)
|
||||
|
||||
import qualified Data.ByteString as BS
|
||||
|
||||
import qualified Database.PostgreSQL.Opium as Opium
|
||||
|
||||
newtype AnInt = AnInt
|
||||
@ -79,7 +81,13 @@ newtype ADay = ADay
|
||||
|
||||
instance FromRow ADay where
|
||||
|
||||
shouldFetch :: (Eq a, FromRow a, Show a) => Connection -> ByteString -> [a] -> IO ()
|
||||
newtype ARawField = ARawField
|
||||
{ raw :: Opium.RawField
|
||||
} deriving (Eq, Generic, Show)
|
||||
|
||||
instance FromRow ARawField where
|
||||
|
||||
shouldFetch :: (Eq a, FromRow a, Show a) => Connection -> Text -> [a] -> IO ()
|
||||
shouldFetch conn query expectedRows = do
|
||||
actualRows <- Opium.fetch_ conn query
|
||||
actualRows `shouldBe` Right expectedRows
|
||||
@ -214,3 +222,12 @@ spec = do
|
||||
shouldFetch conn "SELECT date '2023-09-23' AS day" [ADay $ fromGregorian 2023 9 23]
|
||||
-- Example from postgres doc page
|
||||
shouldFetch conn "SELECT date 'J2451187' AS day" [ADay $ fromGregorian 1999 1 8]
|
||||
|
||||
describe "FromField RawField" $ do
|
||||
it "Simply returns the bytestring without decoding it" $ \conn -> do
|
||||
shouldFetch conn "SELECT 'Hello, World!'::bytea AS raw" [ARawField $ Opium.RawField "Hello, World!"]
|
||||
shouldFetch conn "SELECT 42::int AS raw" [ARawField $ Opium.RawField "\0\0\0\42"]
|
||||
shouldFetch conn "SELECT 42::bigint AS raw" [ARawField $ Opium.RawField "\0\0\0\0\0\0\0\42"]
|
||||
-- Opium assumes that the connection always uses UTF-8.
|
||||
-- The query string is encoded using UTF-8 before passing it to @libpq@.
|
||||
shouldFetch conn "SELECT 'Ära'::text AS raw" [ARawField $ Opium.RawField $ BS.pack [0xC3, 0x84, 0x72, 0x61]]
|
||||
|
Loading…
x
Reference in New Issue
Block a user