postgres-wire/tests/Driver.hs

203 lines
6.9 KiB
Haskell
Raw Normal View History

2017-01-29 03:48:14 +03:00
module Driver where
import Data.Monoid ((<>))
import Data.Foldable
import Control.Monad
2017-01-29 04:22:55 +03:00
import Data.Either
2017-01-29 03:48:14 +03:00
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BS
2017-01-29 05:21:46 +03:00
import qualified Data.Vector as V
2017-01-29 03:48:14 +03:00
import Test.Tasty
import Test.Tasty.HUnit
import Database.PostgreSQL.Driver.Connection
2017-02-01 06:53:56 +03:00
import Database.PostgreSQL.Driver.Query
2017-01-29 03:48:14 +03:00
import Database.PostgreSQL.Protocol.Types
import Connection
2017-01-29 04:22:55 +03:00
testDriver :: TestTree
testDriver = testGroup "Driver"
[ testCase "Single batch" testBatch
, testCase "Two batches" testTwoBatches
, testCase "Multiple batches" testMultipleBatches
2017-01-29 04:22:55 +03:00
, testCase "Empty query" testEmptyQuery
, testCase "Query without result" testQueryWithoutResult
, testCase "Invalid queries" testInvalidBatch
2017-01-29 05:21:46 +03:00
, testCase "Describe statement" testDescribeStatement
, testCase "Describe statement with no data" testDescribeStatementNoData
, testCase "Describe empty statement" testDescribeStatementEmpty
, testCase "SimpleQuery" testSimpleQuery
, testCase "SimpleAndExtendedQuery" testSimpleAndExtendedQuery
2017-01-29 04:22:55 +03:00
]
2017-01-29 03:48:14 +03:00
makeQuery1 :: B.ByteString -> Query
2017-02-02 00:18:06 +03:00
makeQuery1 n = Query "SELECT $1" (V.fromList [Oid 23]) (V.fromList [n])
Text Text
2017-01-29 03:48:14 +03:00
makeQuery2 :: B.ByteString -> B.ByteString -> Query
2017-02-02 00:18:06 +03:00
makeQuery2 n1 n2 = Query "SELECT $1 + $2" (V.fromList [Oid 23, Oid 23])
(V.fromList [n1, n2]) Text Text
2017-01-29 03:48:14 +03:00
2017-01-29 04:22:55 +03:00
fromRight :: Either e a -> a
2017-01-29 03:48:14 +03:00
fromRight (Right v) = v
fromRight _ = error "fromRight"
2017-02-02 00:18:06 +03:00
fromMessage :: Either e DataMessage -> B.ByteString
fromMessage (Right (DataMessage [v])) = V.head v
fromMessage _ = error "from message"
2017-01-29 04:22:55 +03:00
2017-01-29 05:45:44 +03:00
-- | Single batch.
2017-01-29 03:48:14 +03:00
testBatch :: IO ()
testBatch = withConnection $ \c -> do
let a = "5"
b = "3"
sendBatchAndSync c [makeQuery1 a, makeQuery1 b]
readReadyForQuery c
r1 <- readNextData c
r2 <- readNextData c
2017-02-02 00:18:06 +03:00
a @=? fromMessage r1
b @=? fromMessage r2
2017-01-29 03:48:14 +03:00
2017-01-29 05:45:44 +03:00
-- | Two batches in single transaction.
2017-01-29 03:48:14 +03:00
testTwoBatches :: IO ()
testTwoBatches = withConnection $ \c -> do
let a = 7
b = 2
sendBatchAndFlush c [ makeQuery1 (BS.pack (show a))
, makeQuery1 (BS.pack (show b))]
2017-02-02 00:18:06 +03:00
r1 <- fromMessage <$> readNextData c
r2 <- fromMessage <$> readNextData c
2017-01-29 03:48:14 +03:00
sendBatchAndSync c [makeQuery2 r1 r2]
r <- readNextData c
readReadyForQuery c
2017-02-02 00:18:06 +03:00
BS.pack (show $ a + b) @=? fromMessage r
2017-01-29 05:45:44 +03:00
-- | Multiple batches with individual transactions in single connection.
testMultipleBatches :: IO ()
testMultipleBatches = withConnection $ replicateM_ 10 . assertSingleBatch
2017-01-29 03:48:14 +03:00
where
assertSingleBatch c = do
let a = "5"
b = "6"
sendBatchAndSync c [ makeQuery1 a, makeQuery1 b]
r1 <- readNextData c
2017-02-02 00:18:06 +03:00
a @=? fromMessage r1
2017-01-29 05:45:44 +03:00
r2 <- readNextData c
2017-02-02 00:18:06 +03:00
b @=? fromMessage r2
2017-01-29 05:45:44 +03:00
readReadyForQuery c
2017-01-29 03:48:14 +03:00
2017-01-29 05:45:44 +03:00
-- | Query is empty string.
2017-01-29 04:22:55 +03:00
testEmptyQuery :: IO ()
testEmptyQuery = assertQueryNoData $
2017-02-02 00:18:06 +03:00
Query "" V.empty V.empty Text Text
2017-01-29 04:22:55 +03:00
2017-01-29 05:45:44 +03:00
-- | Query than returns no datarows.
2017-01-29 04:22:55 +03:00
testQueryWithoutResult :: IO ()
testQueryWithoutResult = assertQueryNoData $
2017-02-02 00:18:06 +03:00
Query "SET client_encoding TO UTF8" V.empty V.empty Text Text
2017-01-29 04:22:55 +03:00
2017-01-29 05:45:44 +03:00
-- | Asserts that query returns no data rows.
2017-01-29 04:22:55 +03:00
assertQueryNoData :: Query -> IO ()
assertQueryNoData q = withConnection $ \c -> do
sendBatchAndSync c [q]
r <- fromRight <$> readNextData c
readReadyForQuery c
DataMessage [] @=? r
-- | Asserts that all the received data rows are in form (Right _)
checkRightResult :: Connection -> Int -> Assertion
checkRightResult conn 0 = pure ()
checkRightResult conn n = readNextData conn >>=
either (const $ assertFailure "Result is invalid")
(const $ checkRightResult conn (n - 1))
-- | Asserts that (Left _) as result exists in the received data rows.
checkInvalidResult :: Connection -> Int -> Assertion
checkInvalidResult conn 0 = assertFailure "Result is right"
checkInvalidResult conn n = readNextData conn >>=
either (const $ pure ())
(const $ checkInvalidResult conn (n -1))
2017-01-29 05:45:44 +03:00
-- | Diffirent invalid queries in batches.
2017-01-29 04:22:55 +03:00
testInvalidBatch :: IO ()
testInvalidBatch = do
let rightQuery = makeQuery1 "5"
2017-02-02 00:18:06 +03:00
q1 = Query "SEL $1" (V.fromList [Oid 23]) (V.fromList ["5"]) Text Text
q2 = Query "SELECT $1" (V.fromList [Oid 23]) (V.fromList ["a"]) Text Text
q3 = Query "SELECT $1" (V.fromList [Oid 23]) (V.fromList []) Text Text
q4 = Query "SELECT $1" (V.fromList []) (V.fromList ["5"]) Text Text
2017-01-29 04:22:55 +03:00
assertInvalidBatch "Parse error" [q1]
assertInvalidBatch "Invalid param" [ q2]
assertInvalidBatch "Missed param" [ q3]
assertInvalidBatch "Missed oid of param" [ q4]
assertInvalidBatch "Parse error" [rightQuery, q1]
assertInvalidBatch "Invalid param" [rightQuery, q2]
assertInvalidBatch "Missed param" [rightQuery, q3]
assertInvalidBatch "Missed oid of param" [rightQuery, q4]
where
assertInvalidBatch desc qs = withConnection $ \c -> do
sendBatchAndSync c qs
readReadyForQuery c
checkInvalidResult c $ length qs
2017-01-29 05:45:44 +03:00
-- | Describes usual statement.
2017-01-29 05:21:46 +03:00
testDescribeStatement :: IO ()
testDescribeStatement = withConnection $ \c -> do
r <- describeStatement c $
"select typname, typnamespace, typowner, typlen, typbyval,"
<> "typcategory, typispreferred, typisdefined, typdelim, typrelid,"
<> "typelem, typarray from pg_type where typtypmod = $1 "
<> "and typisdefined = $2"
assertBool "Should be Right" $ isRight r
2017-01-29 05:45:44 +03:00
-- | Describes statement that returns no data.
2017-01-29 05:21:46 +03:00
testDescribeStatementNoData :: IO ()
testDescribeStatementNoData = withConnection $ \c -> do
r <- fromRight <$> describeStatement c "SET client_encoding TO UTF8"
assertBool "Should be empty" $ V.null (fst r)
assertBool "Should be empty" $ V.null (snd r)
2017-01-29 05:45:44 +03:00
-- | Describes statement that is empty string.
2017-01-29 05:21:46 +03:00
testDescribeStatementEmpty :: IO ()
testDescribeStatementEmpty = withConnection $ \c -> do
r <- fromRight <$> describeStatement c ""
assertBool "Should be empty" $ V.null (fst r)
assertBool "Should be empty" $ V.null (snd r)
2017-01-29 05:45:44 +03:00
-- | Query using simple query protocol.
testSimpleQuery :: IO ()
testSimpleQuery = withConnection $ \c -> do
r <- sendSimpleQuery c $
"DROP TABLE IF EXISTS a;"
<> "CREATE TABLE a(v int);"
<> "INSERT INTO a VALUES (1), (2), (3);"
<> "SELECT * FROM a;"
<> "DROP TABLE a;"
assertBool "Should be Right" $ isRight r
-- | Simple and extended queries in a sinle connection.
testSimpleAndExtendedQuery :: IO ()
testSimpleAndExtendedQuery = withConnection $ \c -> do
let a = "7"
b = "2"
d = "5"
sendBatchAndSync c [ makeQuery1 a , makeQuery1 b]
readReadyForQuery c
checkRightResult c 2
rs <- sendSimpleQuery c "SELECT * FROM generate_series(1, 10)"
assertBool "Should be Right" $ isRight rs
sendBatchAndSync c [makeQuery1 d]
fr <- readReadyForQuery c
assertBool "Should be Right" $ isRight fr
2017-02-02 00:18:06 +03:00
r <- fromMessage <$> readNextData c
r @=? d