Skip to content

Commit 8b7741f

Browse files
QuickCheck tests for existing codecs
1 parent b1d58b5 commit 8b7741f

File tree

5 files changed

+117
-0
lines changed

5 files changed

+117
-0
lines changed

postgres-wire.cabal

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -87,6 +87,8 @@ test-suite postgres-wire-test
8787
, Fault
8888
, Protocol
8989
, Misc
90+
, Codecs.Runner
91+
, Codecs.QuickCheck
9092
build-depends: base
9193
, postgres-wire
9294
, bytestring
@@ -95,6 +97,9 @@ test-suite postgres-wire-test
9597
, socket
9698
, async
9799
, tasty-hunit
100+
, tasty-quickcheck
101+
, QuickCheck >= 2.9
102+
, tagged
98103
ghc-options: -threaded -rtsopts -with-rtsopts=-N
99104
default-language: Haskell2010
100105
default-extensions:

stack.yaml

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,11 @@ packages:
99
extra-deps:
1010
- socket-0.8.0.0
1111
- socket-unix-0.2.0.0
12+
# <<<<<<< HEAD
13+
# =======
14+
# - store-core-0.3
15+
# - QuickCheck-2.9.2
16+
# >>>>>>> QuickCheck tests for existing codecs
1217

1318
# Override default flag values for local packages and extra-deps
1419
flags: {}

tests/Codecs/QuickCheck.hs

Lines changed: 80 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,80 @@
1+
module Codecs.QuickCheck where
2+
3+
import Test.Tasty
4+
import Test.QuickCheck
5+
import Test.QuickCheck.Arbitrary
6+
import Test.QuickCheck.Monadic
7+
8+
import qualified Data.ByteString as B
9+
import qualified Data.Vector as V
10+
11+
import Database.PostgreSQL.Driver
12+
import Database.PostgreSQL.Protocol.DataRows
13+
import Database.PostgreSQL.Protocol.Types
14+
import Database.PostgreSQL.Protocol.Store.Encode
15+
import Database.PostgreSQL.Protocol.Store.Decode
16+
import qualified Database.PostgreSQL.Protocol.Codecs.Decoders as PD
17+
import qualified Database.PostgreSQL.Protocol.Codecs.Encoders as PE
18+
import qualified Database.PostgreSQL.Protocol.Codecs.PgTypes as PGT
19+
import Connection
20+
import Codecs.Runner
21+
22+
23+
-- | Makes property that if here is a value then encoding and sending it
24+
-- to PostgreSQL, and receiving back returns the same value.
25+
makeCodecProperty
26+
:: (Eq a, Arbitrary a )
27+
=> Connection
28+
-> Oid -> (a -> Encode) -> PD.FieldDecoder a
29+
-> a -> Property
30+
makeCodecProperty c oid encoder fd v = monadicIO $ do
31+
let bs = runEncode $ encoder v
32+
q = Query "SELECT $1" (V.fromList [(oid, Just bs)])
33+
Binary Binary AlwaysCache
34+
decoder = PD.dataRowHeader *> PD.getNonNullable fd
35+
r <- run $ do
36+
sendBatchAndSync c [q]
37+
dr <- readNextData c
38+
waitReadyForQuery c
39+
either (error . show) (pure . decodeOneRow decoder) dr
40+
41+
assert $ v == r
42+
43+
-- | Makes Tasty test tree.
44+
mkCodecTest
45+
:: (Eq a, Arbitrary a, Show a)
46+
=> TestName -> PGT.Oids -> (a -> Encode) -> PD.FieldDecoder a
47+
-> TestTree
48+
mkCodecTest name oids encoder decoder = testPropertyConn name $ \c ->
49+
makeCodecProperty c (PGT.oidType oids) encoder decoder
50+
51+
testCodecsEncodeDecode :: TestTree
52+
testCodecsEncodeDecode = testGroup "Codecs property 'encode . decode = id'"
53+
[ mkCodecTest "bool" PGT.bool PE.bool PD.bool
54+
, mkCodecTest "bytea" PGT.bytea PE.bytea PD.bytea
55+
, mkCodecTest "char" PGT.char PE.char PD.char
56+
-- TODO instance
57+
-- , mkCodecTest "date" PGT.date PE.date PD.date
58+
, mkCodecTest "float4" PGT.float4 PE.float4 PD.float4
59+
, mkCodecTest "float8" PGT.float8 PE.float8 PD.float8
60+
, mkCodecTest "int2" PGT.int2 PE.int2 PD.int2
61+
, mkCodecTest "int4" PGT.int4 PE.int4 PD.int4
62+
, mkCodecTest "int8" PGT.int8 PE.int8 PD.int8
63+
-- TODO intstance
64+
-- , mkCodecTest "interval" PGT.interval PE.interval PD.interval
65+
, mkCodecTest "json" PGT.json PE.bsJsonText PD.bsJsonText
66+
, mkCodecTest "jsonb" PGT.jsonb PE.bsJsonBytes PD.bsJsonBytes
67+
-- TODO
68+
-- , mkCodecTest "numeric" PGT.numeric PE.numeric PD.numeric
69+
, mkCodecTest "text" PGT.text PE.bsText PD.bsText
70+
-- TODO make instance
71+
-- , mkCodecTest "timestamp" PGT.timestamp PE.timestamp PD.timestamp
72+
-- TODO make instance
73+
-- , mkCodecTest "timestamptz" PGT.timestamptz PE.timestamptz PD.timestamptz
74+
-- TODO make instance
75+
-- , mkCodecTest "uuid" PGT.uuid PE.uuid PD.uuid
76+
]
77+
78+
-- TODO right instance
79+
instance Arbitrary B.ByteString where
80+
arbitrary = oneof [pure "1", pure "2"]

tests/Codecs/Runner.hs

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,24 @@
1+
module Codecs.Runner where
2+
3+
import Data.Typeable
4+
import Data.Tagged
5+
import Test.Tasty.QuickCheck
6+
import Test.Tasty.Providers
7+
import Test.Tasty.Options
8+
import qualified Test.QuickCheck as QC
9+
10+
import Database.PostgreSQL.Driver
11+
import Connection
12+
13+
newtype ConnQC = ConnQC (Connection -> QC.Property)
14+
deriving Typeable
15+
16+
-- | Create a 'Test' for a QuickCheck 'QC.Testable' property
17+
testPropertyConn :: QC.Testable a => TestName -> (Connection -> a) -> TestTree
18+
testPropertyConn name fprop = singleTest name . ConnQC $ QC.property . fprop
19+
20+
instance IsTest ConnQC where
21+
testOptions = retag (testOptions :: Tagged QC [OptionDescription])
22+
23+
run opts (ConnQC f) yieldProgress = withConnection $ \c ->
24+
run opts (QC $ f c) yieldProgress

tests/test.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,11 +5,14 @@ import Driver
55
import Fault
66
import Misc
77

8+
import Codecs.QuickCheck
9+
810
main :: IO ()
911
main = defaultMain $ testGroup "Postgres-wire"
1012
[ testProtocolMessages
1113
, testDriver
1214
, testFaults
1315
, testMisc
16+
, testCodecsEncodeDecode
1417
]
1518

0 commit comments

Comments
 (0)