|
| 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"] |
0 commit comments