114 lines
4.2 KiB
Haskell
114 lines
4.2 KiB
Haskell
{-# LANGUAGE DeriveGeneric #-}
|
|
{-# LANGUAGE DuplicateRecordFields #-}
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
{-# LANGUAGE TypeApplications #-}
|
|
|
|
module Database.PostgreSQL.OpiumSpec (spec) where
|
|
|
|
import Data.Proxy (Proxy (..))
|
|
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
|
|
|
|
data ManyFields = ManyFields
|
|
{ a :: Text
|
|
, b :: Int
|
|
, c :: Double
|
|
, d :: String
|
|
, e :: Bool
|
|
} deriving (Eq, Generic, Show)
|
|
|
|
instance Opium.FromRow ManyFields where
|
|
|
|
isLeft :: Either a b -> Bool
|
|
isLeft (Left _) = True
|
|
isLeft _ = False
|
|
|
|
spec :: SpecWith Connection
|
|
spec = do
|
|
describe "getColumnTable" $ do
|
|
it "Gets the column table for a result" $ \conn -> do
|
|
Just result <- LibPQ.execParams conn "SELECT name, age FROM person" [] LibPQ.Text
|
|
columnTable <- Opium.getColumnTable @Person Proxy result
|
|
columnTable `shouldBe` Right [0, 1]
|
|
|
|
it "Gets the numbers right for funky configurations" $ \conn -> do
|
|
Just result0 <- LibPQ.execParams conn "SELECT age, name FROM person" [] LibPQ.Text
|
|
columnTable0 <- Opium.getColumnTable @Person Proxy result0
|
|
columnTable0 `shouldBe` Right [1, 0]
|
|
|
|
Just result1 <- LibPQ.execParams conn "SELECT 0 AS a, 1 AS b, 2 AS c, age, 4 AS d, name FROM person" [] LibPQ.Text
|
|
columnTable1 <- Opium.getColumnTable @Person Proxy result1
|
|
columnTable1 `shouldBe` Right [5, 3]
|
|
|
|
it "Fails for missing columns" $ \conn -> do
|
|
Just result <- LibPQ.execParams conn "SELECT 0 AS a FROM person" [] LibPQ.Text
|
|
columnTable <- Opium.getColumnTable @Person Proxy result
|
|
columnTable `shouldBe` Left (Opium.ErrorMissingColumn "name")
|
|
|
|
describe "fromRow" $ do
|
|
it "Decodes rows in a Result" $ \conn -> do
|
|
Just result <- LibPQ.execParams conn "SELECT * FROM person" [] LibPQ.Text
|
|
Right columnTable <- Opium.getColumnTable @Person Proxy result
|
|
|
|
row0 <- Opium.fromRow @Person result columnTable (LibPQ.Row 0)
|
|
row0 `shouldBe` Right (Person "paul" 25)
|
|
|
|
row1 <- Opium.fromRow @Person result columnTable (LibPQ.Row 1)
|
|
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
|
|
Right columnTable <- Opium.getColumnTable @MaybeTest Proxy result
|
|
|
|
row <- Opium.fromRow result columnTable (LibPQ.Row 0)
|
|
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
|
|
Right columnTable <- Opium.getColumnTable @MaybeTest Proxy result
|
|
|
|
row <- Opium.fromRow result columnTable (LibPQ.Row 0)
|
|
row `shouldBe` Right (MaybeTest $ Just "abc")
|
|
|
|
it "Works for many fields" $ \conn -> do
|
|
Just result <- LibPQ.execParams conn "SELECT 'abc' AS a, 42 AS b, 1.0::double precision AS c, 'test' AS d, true AS e" [] LibPQ.Text
|
|
Right columnTable <- Opium.getColumnTable @ManyFields Proxy result
|
|
|
|
row <- Opium.fromRow result columnTable (LibPQ.Row 0)
|
|
row `shouldBe` Right (ManyFields "abc" 42 1.0 "test" True)
|
|
|
|
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 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.ErrorInvalidOid "age" $ LibPQ.Oid 25)
|