Make Connection parameter go last in query functions

This commit is contained in:
Paul Brinkmeier 2024-07-03 10:09:38 +02:00
parent ef52bd9235
commit 2b2a048197
4 changed files with 32 additions and 29 deletions

View File

@ -33,8 +33,8 @@ data User = User
instance Opium.FromRow User where instance Opium.FromRow User where
getUsers :: Connection -> IO (Either Opium.Error [Users]) getUsers :: Connection -> IO (Either Opium.Error [User])
getUsers conn = Opium.fetch_ conn "SELECT * FROM user" getUsers conn = Opium.fetch_ "SELECT * FROM user" conn
``` ```
The `Opium.FromRow` instance is implemented generically for all product types ("records"). It looks up the field name in the query result and decodes the column value using `Opium.FromField`. The `Opium.FromRow` instance is implemented generically for all product types ("records"). It looks up the field name in the query result and decodes the column value using `Opium.FromField`.
@ -51,7 +51,7 @@ instance Opium.FromRow ScoreByAge where
getScoreByAge :: Connection -> IO ScoreByAge getScoreByAge :: Connection -> IO ScoreByAge
getScoreByAge conn = do getScoreByAge conn = do
let query = "SELECT regr_intercept(score, age) AS t, regr_slope(score, age) AS m FROM user" let query = "SELECT regr_intercept(score, age) AS t, regr_slope(score, age) AS m FROM user"
Right [x] <- Opium.fetch_ conn query Right [x] <- Opium.fetch_ query conn
pure x pure x
``` ```

View File

@ -6,6 +6,9 @@
module Database.PostgreSQL.Opium module Database.PostgreSQL.Opium
-- * Queries -- * Queries
-- --
-- Functions for performing queries. @fetch@ retrieves rows, @execute@ doesn't.
-- The 'Connection' parameter comes last to facilitate currying for implicitly passing in the connection, e.g. from some framework's connection pool.
--
-- | TODO: Add @newtype Query = Query Text@ with @IsString@ instance to make constructing query strings at run time harder. -- | TODO: Add @newtype Query = Query Text@ with @IsString@ instance to make constructing query strings at run time harder.
( fetch ( fetch
, fetch_ , fetch_
@ -45,29 +48,29 @@ import Database.PostgreSQL.Opium.ToParamList (ToParamList (..))
-- The order of the type parameters is important, because it is more common to use type applications for providing the row type. -- The order of the type parameters is important, because it is more common to use type applications for providing the row type.
fetch fetch
:: forall a b. (ToParamList b, FromRow a) :: forall a b. (ToParamList b, FromRow a)
=> Connection => Text
-> Text
-> b -> b
-> Connection
-> IO (Either Error [a]) -> IO (Either Error [a])
fetch conn query params = runExceptT $ do fetch query params conn = runExceptT $ do
result <- execParams conn query params result <- execParams conn query params
columnTable <- ExceptT $ getColumnTable @a Proxy result columnTable <- ExceptT $ getColumnTable @a Proxy result
nRows <- liftIO $ LibPQ.ntuples result nRows <- liftIO $ LibPQ.ntuples result
mapM (ExceptT . fromRow result columnTable) [0..nRows - 1] mapM (ExceptT . fromRow result columnTable) [0..nRows - 1]
fetch_ :: forall a. FromRow a => Connection -> Text -> IO (Either Error [a]) fetch_ :: forall a. FromRow a => Text -> Connection -> IO (Either Error [a])
fetch_ conn query = fetch conn query () fetch_ query = fetch query ()
execute execute
:: forall a. ToParamList a :: forall a. ToParamList a
=> Connection => Text
-> Text
-> a -> a
-> Connection
-> IO (Either Error ()) -> IO (Either Error ())
execute conn query params = runExceptT $ void $ execParams conn query params execute query params conn = runExceptT $ void $ execParams conn query params
execute_ :: Connection -> Text -> IO (Either Error ()) execute_ :: Text -> Connection -> IO (Either Error ())
execute_ conn query = execute conn query () execute_ query = execute query ()
execParams execParams
:: ToParamList a :: ToParamList a

View File

@ -115,7 +115,7 @@ instance FromRow ARawField where
shouldFetch :: (Eq a, FromRow a, Show a) => Connection -> Text -> [a] -> IO () shouldFetch :: (Eq a, FromRow a, Show a) => Connection -> Text -> [a] -> IO ()
shouldFetch conn query expectedRows = do shouldFetch conn query expectedRows = do
actualRows <- Opium.fetch_ conn query actualRows <- Opium.fetch_ query conn
actualRows `shouldBe` Right expectedRows actualRows `shouldBe` Right expectedRows
(/\) :: (a -> Bool) -> (a -> Bool) -> a -> Bool (/\) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
@ -213,15 +213,15 @@ spec = do
shouldFetch conn "SELECT 4.2::real AS float" [AFloat 4.2] shouldFetch conn "SELECT 4.2::real AS float" [AFloat 4.2]
it "Decodes NaN::real" $ \conn -> do it "Decodes NaN::real" $ \conn -> do
Right [AFloat value] <- Opium.fetch_ conn "SELECT 'NaN'::real AS float" Right [AFloat value] <- Opium.fetch_ "SELECT 'NaN'::real AS float" conn
value `shouldSatisfy` isNaN value `shouldSatisfy` isNaN
it "Decodes Infinity::real" $ \conn -> do it "Decodes Infinity::real" $ \conn -> do
Right [AFloat value] <- Opium.fetch_ conn "SELECT 'Infinity'::real AS float" Right [AFloat value] <- Opium.fetch_ "SELECT 'Infinity'::real AS float" conn
value `shouldSatisfy` (isInfinite /\ (> 0)) value `shouldSatisfy` (isInfinite /\ (> 0))
it "Decodes -Infinity::real" $ \conn -> do it "Decodes -Infinity::real" $ \conn -> do
Right [AFloat value] <- Opium.fetch_ conn "SELECT '-Infinity'::real AS float" Right [AFloat value] <- Opium.fetch_ "SELECT '-Infinity'::real AS float" conn
value `shouldSatisfy` (isInfinite /\ (< 0)) value `shouldSatisfy` (isInfinite /\ (< 0))
describe "FromField Double" $ do describe "FromField Double" $ do
@ -229,22 +229,22 @@ spec = do
shouldFetch conn "SELECT 4.2::double precision AS double" [ADouble 4.2] shouldFetch conn "SELECT 4.2::double precision AS double" [ADouble 4.2]
it "Decodes NaN::double precision" $ \conn -> do it "Decodes NaN::double precision" $ \conn -> do
Right [ADouble value] <- Opium.fetch_ conn "SELECT 'NaN'::double precision AS double" Right [ADouble value] <- Opium.fetch_ "SELECT 'NaN'::double precision AS double" conn
value `shouldSatisfy` isNaN value `shouldSatisfy` isNaN
it "Decodes Infinity::double precision" $ \conn -> do it "Decodes Infinity::double precision" $ \conn -> do
Right [ADouble value] <- Opium.fetch_ conn "SELECT 'Infinity'::double precision AS double" Right [ADouble value] <- Opium.fetch_ "SELECT 'Infinity'::double precision AS double" conn
value `shouldSatisfy` (isInfinite /\ (> 0)) value `shouldSatisfy` (isInfinite /\ (> 0))
it "Decodes -Infinity::double precision" $ \conn -> do it "Decodes -Infinity::double precision" $ \conn -> do
Right [ADouble value] <- Opium.fetch_ conn "SELECT '-Infinity'::double precision AS double" Right [ADouble value] <- Opium.fetch_ "SELECT '-Infinity'::double precision AS double" conn
value `shouldSatisfy` (isInfinite /\ (< 0)) value `shouldSatisfy` (isInfinite /\ (< 0))
it "Decodes {inf,-inf}::double precision" $ \conn -> do it "Decodes {inf,-inf}::double precision" $ \conn -> do
Right [ADouble value0] <- Opium.fetch_ conn "SELECT 'inf'::double precision AS double" Right [ADouble value0] <- Opium.fetch_ "SELECT 'inf'::double precision AS double" conn
value0 `shouldSatisfy` (isInfinite /\ (> 0)) value0 `shouldSatisfy` (isInfinite /\ (> 0))
Right [ADouble value1] <- Opium.fetch_ conn "SELECT '-inf'::double precision AS double" Right [ADouble value1] <- Opium.fetch_ "SELECT '-inf'::double precision AS double" conn
value1 `shouldSatisfy` (isInfinite /\ (< 0)) value1 `shouldSatisfy` (isInfinite /\ (< 0))
describe "FromField Bool" $ do describe "FromField Bool" $ do

View File

@ -124,30 +124,30 @@ spec = do
describe "fetch" $ do describe "fetch" $ do
it "Passes numbered parameters and retrieves a list of rows" $ \conn -> do it "Passes numbered parameters and retrieves a list of rows" $ \conn -> do
rows <- Opium.fetch conn "SELECT ($1 + $2) AS only" (17 :: Int, 25 :: Int) rows <- Opium.fetch "SELECT ($1 + $2) AS only" (17 :: Int, 25 :: Int) conn
rows `shouldBe` Right [Only (42 :: Int)] rows `shouldBe` Right [Only (42 :: Int)]
it "Uses Identity to pass single parameters" $ \conn -> do it "Uses Identity to pass single parameters" $ \conn -> do
rows <- Opium.fetch conn "SELECT count(*) AS only FROM person WHERE name = $1" $ Identity ("paul" :: Text) rows <- Opium.fetch "SELECT count(*) AS only FROM person WHERE name = $1" (Identity ("paul" :: Text)) conn
rows `shouldBe` Right [Only (1 :: Int)] rows `shouldBe` Right [Only (1 :: Int)]
describe "fetch_" $ do describe "fetch_" $ do
it "Retrieves a list of rows" $ \conn -> do it "Retrieves a list of rows" $ \conn -> do
rows <- Opium.fetch_ conn "SELECT * FROM person" rows <- Opium.fetch_ "SELECT * FROM person" conn
rows `shouldBe` Right [Person "paul" 25, Person "albus" 103] rows `shouldBe` Right [Person "paul" 25, Person "albus" 103]
it "Fails for invalid queries" $ \conn -> do it "Fails for invalid queries" $ \conn -> do
rows <- Opium.fetch_ @Person conn "MRTLBRNFT" rows <- Opium.fetch_ @Person "MRTLBRNFT" conn
rows `shouldSatisfy` isLeft rows `shouldSatisfy` isLeft
it "Fails for unexpected NULLs" $ \conn -> do it "Fails for unexpected NULLs" $ \conn -> do
rows <- Opium.fetch_ @Person conn "SELECT NULL AS name, 0 AS age" rows <- Opium.fetch_ @Person "SELECT NULL AS name, 0 AS age" conn
rows `shouldBe` Left (Opium.ErrorUnexpectedNull (Opium.ErrorPosition 0 "name")) rows `shouldBe` Left (Opium.ErrorUnexpectedNull (Opium.ErrorPosition 0 "name"))
it "Fails for the wrong column type" $ \conn -> do it "Fails for the wrong column type" $ \conn -> do
rows <- Opium.fetch_ @Person conn "SELECT 'quby' AS name, 'indeterminate' AS age" rows <- Opium.fetch_ @Person "SELECT 'quby' AS name, 'indeterminate' AS age" conn
rows `shouldBe` Left (Opium.ErrorInvalidOid "age" $ LibPQ.Oid 25) rows `shouldBe` Left (Opium.ErrorInvalidOid "age" $ LibPQ.Oid 25)
it "Works for the readme regression example" $ \conn -> do it "Works for the readme regression example" $ \conn -> do
rows <- Opium.fetch_ @ScoreByAge conn "SELECT regr_intercept(score, age) AS t, regr_slope(score, age) AS m FROM person" rows <- Opium.fetch_ @ScoreByAge "SELECT regr_intercept(score, age) AS t, regr_slope(score, age) AS m FROM person" conn
rows `shouldSatisfy` \case { (Right [ScoreByAge _ _]) -> True; _ -> False } rows `shouldSatisfy` \case { (Right [ScoreByAge _ _]) -> True; _ -> False }