opium/test/Database/PostgreSQL/OpiumSpec.hs

76 lines
2.5 KiB
Haskell

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Database.PostgreSQL.OpiumSpec (spec) where
import Data.Text (Text)
import Database.PostgreSQL.LibPQ (Connection)
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
isLeft :: Either a b -> Bool
isLeft (Left _) = True
isLeft _ = False
spec :: SpecWith Connection
spec = do
describe "fromRow" $ do
it "decodes rows in a Result" $ \conn -> do
Just result <- LibPQ.execParams conn "SELECT * FROM person" [] LibPQ.Text
row0 <- Opium.fromRow @Person (LibPQ.Row 0) result
row0 `shouldBe` Right (Person "paul" 25)
row1 <- Opium.fromRow @Person (LibPQ.Row 1) result
row1 `shouldBe` Right (Person "albus" 103)
it "decodes NULL into Nothing for Maybes" $ \conn -> do
Just result <- LibPQ.execParams conn "SELECT NULL AS a" [] LibPQ.Text
row <- Opium.fromRow (LibPQ.Row 0) result
row `shouldBe` Right (MaybeTest Nothing)
it "decodes values into Just for Maybes" $ \conn -> do
Just result <- LibPQ.execParams conn "SELECT 'abc' AS a" [] LibPQ.Text
row <- Opium.fromRow (LibPQ.Row 0) result
row `shouldBe` Right (MaybeTest $ Just "abc")
describe "fetch_" $ do
it "retrieves a list of rows" $ \conn -> do
rows <- Opium.fetch_ conn "SELECT * FROM person"
rows `shouldBe` Right [Person "paul" 25, Person "albus" 103]
it "fails for invalid queries" $ \conn -> do
rows <- Opium.fetch_ @Person conn "MRTLBRNFT"
rows `shouldSatisfy` isLeft
it "fails for missing columns" $ \conn -> do
rows <- Opium.fetch_ @Person conn "SELECT name FROM person"
rows `shouldBe` Left (Opium.ErrorMissingColumn "age")
it "fails for unexpected NULLs" $ \conn -> do
rows <- Opium.fetch_ @Person conn "SELECT NULL AS name, 0 AS age"
rows `shouldBe` Left (Opium.ErrorUnexpectedNull (LibPQ.Row 0) "name")
it "fails for the wrong column type" $ \conn -> do
rows <- Opium.fetch_ @Person conn "SELECT 'quby' AS name, 'indeterminate' AS age"
rows `shouldBe` Left (Opium.ErrorDecode (LibPQ.Row 0) "age" $ Opium.FieldErrorInvalidOid $ LibPQ.Oid 25)