{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeApplications #-} module Database.PostgreSQL.OpiumSpec (ManyFields (..), MaybeTest (..), Person (..), Only (..), spec) where import Data.Either (isLeft) import Data.Functor.Identity (Identity (..)) import Data.Text (Text) import GHC.Generics (Generic) import Test.Hspec (SpecWith, describe, it, shouldBe, shouldSatisfy) import qualified Database.PostgreSQL.LibPQ as LibPQ import qualified Database.PostgreSQL.Opium as Opium data Person = Person { name :: Text , age :: Int } deriving (Eq, Generic, Show) instance Opium.FromRow Person where newtype MaybeTest = MaybeTest { a :: Maybe String } deriving (Eq, Generic, Show) instance Opium.FromRow MaybeTest where data ManyFields = ManyFields { a :: Text , b :: Int , c :: Double , d :: String , e :: Bool } deriving (Eq, Generic, Show) instance Opium.FromRow ManyFields where data ScoreByAge = ScoreByAge { m :: Double , t :: Double } deriving (Eq, Generic, Show) instance Opium.FromRow ScoreByAge where newtype Only a = Only { only :: a } deriving (Eq, Generic, Show) instance Opium.FromField a => Opium.FromRow (Only a) where spec :: SpecWith Opium.Connection spec = do describe "fetch" $ do it "Passes numbered parameters and retrieves a list of rows" $ \conn -> do rows <- Opium.fetch "SELECT ($1 + $2) AS only" (17 :: Int, 25 :: Int) conn rows `shouldBe` Right [Only (42 :: Int)] it "Uses Identity to pass single parameters" $ \conn -> do rows <- Opium.fetch "SELECT count(*) AS only FROM person WHERE name = $1" (Identity ("paul" :: Text)) conn rows `shouldBe` Right [Only (1 :: Int)] describe "fetch_" $ do it "Retrieves a list of rows" $ \conn -> do rows <- Opium.fetch_ "SELECT * FROM person" conn rows `shouldBe` Right [Person "paul" 25, Person "albus" 103] it "Fails for invalid queries" $ \conn -> do rows <- Opium.fetch_ @Person @[] "MRTLBRNFT" conn rows `shouldSatisfy` isLeft it "Fails for unexpected NULLs" $ \conn -> do rows <- Opium.fetch_ @Person @[] "SELECT NULL AS name, 0 AS age" conn rows `shouldBe` Left (Opium.ErrorUnexpectedNull (Opium.ErrorPosition 0 "name")) it "Fails for the wrong column type" $ \conn -> do rows <- Opium.fetch_ @Person @[] "SELECT 'quby' AS name, 'indeterminate' AS age" conn rows `shouldBe` Left (Opium.ErrorInvalidOid "age" $ LibPQ.Oid 25) it "Works for the readme regression example" $ \conn -> do 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 } it "Accepts exactly one row when Identity is the row container type" $ \conn -> do row <- Opium.fetch_ "SELECT 42 AS only" conn row `shouldBe` Right (Identity (Only (42 :: Int))) it "Does not accept zero rows when Identity is the row container type" $ \conn -> do row <- Opium.fetch_ @(Only Int) @Identity "SELECT 42 AS only WHERE false" conn row `shouldSatisfy` isLeft it "Does not accept two rows when Identity is the row container type" $ \conn -> do row <- Opium.fetch_ @(Only Int) @Identity "SELECT 17 AS only UNION ALL SELECT 25 AS only" conn row `shouldSatisfy` isLeft it "Accepts zero rows when Maybe is the row container type" $ \conn -> do row <- Opium.fetch_ @(Only Int) @Maybe "SELECT 17 AS only WHERE false" conn row `shouldBe` Right Nothing it "Accepts one row when Maybe is the row container type" $ \conn -> do row <- Opium.fetch_ @(Only Int) @Maybe "SELECT 42 AS only" conn row `shouldBe` Right (Just (Only 42)) it "Does not accept two rows when Maybe is the row container type" $ \conn -> do row <- Opium.fetch_ @(Only Int) @Maybe "SELECT 17 AS only UNION ALL SELECT 25 AS only" conn row `shouldSatisfy` isLeft describe "close" $ do it "Does not crash when called twice on the same connection" $ \conn -> do Opium.close conn Opium.close conn