Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

[#50] Add decode.encode = id tests #173

Merged
merged 4 commits into from
Jan 12, 2019
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
178 changes: 178 additions & 0 deletions test/Test/Toml/BiCode/Property.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,178 @@
module Test.Toml.BiCode.Property where

import Control.Applicative ((<|>))
import Control.Category ((>>>))
import Data.ByteString (ByteString)
import Data.HashSet (HashSet)
import Data.IntSet (IntSet)
import Data.List.NonEmpty (NonEmpty)
import Data.Set (Set)
import Data.Text (Text)
import Data.Time (Day, LocalTime, TimeOfDay, ZonedTime, zonedTimeToUTC)
import GHC.Exts (fromList)
import Hedgehog (Gen, forAll, tripping)
import Numeric.Natural (Natural)

import Toml (TomlBiMap, TomlCodec, (.=))
import Toml.Bi.Code (decode, encode)

import Test.Toml.Gen (PropertyTest, genBool, genByteString, genDay, genDouble, genFloat, genHashSet,
genHours, genInt, genIntSet, genInteger, genLByteString, genLocal, genNatural,
genNonEmpty, genString, genText, genWord, genZoned, prop)

import qualified Data.ByteString.Lazy as L
import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range
import qualified Toml

test_encodeDecodeProp :: PropertyTest
test_encodeDecodeProp = prop "decode . encode == id" $ do
bigType <- forAll genBigType
tripping bigType (encode bigTypeCodec) (decode bigTypeCodec)

data BigType = BigType
{ btBool :: Bool
, btInteger :: Integer
, btNatural :: Natural
, btInt :: Int
, btWord :: Word
, btDouble :: Batman Double
, btFloat :: Batman Float
, btText :: Text
, btString :: String
, btBS :: ByteString
, btLazyBS :: L.ByteString
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Lol, I just noticed that in tomland we have Text, ByteString, LByteString and String but not LText. Heh, that's awkward. Probably need to add LText to tomland as well. I've created issue for this:

, btLocalTime :: LocalTime
, btDay :: Day
, btTimeOfDay :: TimeOfDay
, btArray :: [Int]
, btArraySet :: Set Word
, btArrayIntSet :: IntSet
, btArrayHashSet :: HashSet Natural
, btArrayNonEmpty :: NonEmpty Text
, btNonEmpty :: NonEmpty ByteString
, btList :: [Bool]
, btNewtype :: BigTypeNewtype
, btSum :: BigTypeSum
, btRecord :: BigTypeRecord
} deriving (Show, Eq)

-- | Wrapper over 'Double' and 'Float' to be equal on @NaN@ values.
newtype Batman a = Batman a
deriving (Show)

instance RealFloat a => Eq (Batman a) where
Batman a == Batman b =
if isNaN a
then isNaN b
else a == b

newtype BigTypeNewtype = BigTypeNewtype ZonedTime
deriving (Show)

instance Eq BigTypeNewtype where
(BigTypeNewtype a) == (BigTypeNewtype b) = zonedTimeToUTC a == zonedTimeToUTC b
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Very nice idea to move ZonedTime inside newtype! With this trick you can minimize the size of Eq instance and test both diwrap and zonedTime!


data BigTypeSum = BigTypeSumA Integer | BigTypeSumB Text
deriving (Show, Eq)

data BigTypeRecord = BigTypeRecord
{ btrBoolSet :: Set Bool
, btrNewtypeList :: [BigTypeSum]
} deriving (Show, Eq)

bigTypeCodec :: TomlCodec BigType
bigTypeCodec = BigType
<$> Toml.bool "bool" .= btBool
<*> Toml.integer "integer" .= btInteger
<*> Toml.natural "natural" .= btNatural
<*> Toml.int "int" .= btInt
<*> Toml.word "word" .= btWord
<*> Toml.diwrap (Toml.double "double") .= btDouble
<*> Toml.diwrap (Toml.float "float") .= btFloat
<*> Toml.text "text" .= btText
<*> Toml.string "string" .= btString
<*> Toml.byteString "bs" .= btBS
<*> Toml.lazyByteString "lbs" .= btLazyBS
<*> Toml.localTime "localTime" .= btLocalTime
<*> Toml.day "day" .= btDay
<*> Toml.timeOfDay "timeOfDay" .= btTimeOfDay
<*> Toml.arrayOf Toml._Int "arrayOfInt" .= btArray
<*> Toml.arraySetOf Toml._Word "arraySetOfWord" .= btArraySet
<*> Toml.arrayIntSet "arrayIntSet" .= btArrayIntSet
<*> Toml.arrayHashSetOf Toml._Natural "arrayHashSetDouble" .= btArrayHashSet
<*> Toml.arrayNonEmptyOf Toml._Text "arrayNonEmptyOfText" .= btArrayNonEmpty
<*> Toml.nonEmpty (Toml.byteString "bs") "nonEmptyBS" .= btNonEmpty
<*> Toml.list (Toml.bool "bool") "listBool" .= btList
<*> Toml.diwrap (Toml.zonedTime "nt.zonedTime") .= btNewtype
<*> bigTypeSumCodec .= btSum
<*> Toml.table bigTypeRecordCodec "table-record" .= btRecord

_BigTypeSumA :: TomlBiMap BigTypeSum Integer
_BigTypeSumA = Toml.prism BigTypeSumA $ \case
BigTypeSumA i -> Right i
other -> Toml.wrongConstructor "BigTypeSumA" other

_BigTypeSumB :: TomlBiMap BigTypeSum Text
_BigTypeSumB = Toml.prism BigTypeSumB $ \case
BigTypeSumB n -> Right n
other -> Toml.wrongConstructor "BigTypeSumB" other

bigTypeSumCodec :: TomlCodec BigTypeSum
bigTypeSumCodec =
Toml.match (_BigTypeSumA >>> Toml._Integer) "sum.integer"
<|> Toml.match (_BigTypeSumB >>> Toml._Text) "sum.text"

bigTypeRecordCodec :: TomlCodec BigTypeRecord
bigTypeRecordCodec = BigTypeRecord
<$> Toml.arraySetOf Toml._Bool "rboolSet" .= btrBoolSet
<*> Toml.list bigTypeSumCodec "rnewtype" .= btrNewtypeList

----------------------------------------------------------------------------
-- Generator
----------------------------------------------------------------------------

genBigType :: Gen BigType
genBigType = do
btBool <- genBool
btInteger <- genInteger
btNatural <- genNatural
btInt <- genInt
btWord <- genWord
btDouble <- Batman <$> genDouble
btFloat <- Batman <$> genFloat
btText <- genText
btString <- genString
btBS <- genByteString
btLazyBS <- genLByteString
btLocalTime <- genLocal
btDay <- genDay
btTimeOfDay <- genHours
btArray <- Gen.list (Range.constant 0 5) genInt
btArraySet <- Gen.set (Range.constant 0 5) genWord
btArrayIntSet <- genIntSet
btArrayHashSet <- genHashSet genNatural
btArrayNonEmpty <- genNonEmpty genText
btNonEmpty <- genNonEmpty genByteString
btList <- Gen.list (Range.constant 0 5) genBool
btNewtype <- genNewType
btSum <- genSum
btRecord <- genRec
pure BigType {..}

-- Custom generators

genNewType :: Gen BigTypeNewtype
genNewType = BigTypeNewtype <$> genZoned

genSum :: Gen BigTypeSum
genSum = Gen.choice
[ BigTypeSumA <$> genInteger
, BigTypeSumB <$> genText
]

genRec :: Gen BigTypeRecord
genRec = do
btrBoolSet <- fromList <$> Gen.list (Range.constant 0 5) genBool
btrNewtypeList <- Gen.list (Range.constant 0 5) genSum
pure BigTypeRecord{..}
68 changes: 15 additions & 53 deletions test/Test/Toml/BiMap/Property.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,51 +2,17 @@

module Test.Toml.BiMap.Property where

import Hedgehog (Gen, PropertyT, Range, assert, forAll, tripping, (===))
import Hedgehog (Gen, PropertyT, assert, forAll, tripping, (===))

import Data.Time (Day, ZonedTime (..))
import GHC.Natural (Natural)
import Data.Time (ZonedTime (..))
import Test.Tasty (testGroup)
import Test.Toml.Gen (PropertyTest, prop)
import Toml.Bi.Map (BiMap (..), TomlBiMap)

import qualified Data.ByteString.Builder as BB
import qualified Data.ByteString.Lazy as BL
import qualified Data.HashSet as HS
import qualified Data.IntSet as IS
import qualified Data.List.NonEmpty as NE
import qualified Data.Text.Lazy as L
import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range
import qualified Test.Toml.Gen as G
import qualified Toml.Bi.Map as B

-- Custom generators

range100 :: Range Int
range100 = Range.constant 0 100

genNatural :: Gen Natural
genNatural = fromIntegral <$> Gen.word Range.constantBounded

genInSet :: Gen IS.IntSet
genInSet = IS.fromList <$> Gen.list range100 (Gen.int Range.constantBounded)

genHashSet :: Gen (HS.HashSet Integer)
genHashSet = HS.fromList <$> Gen.list range100 G.genInteger

genNEDays :: Gen (NE.NonEmpty Day)
genNEDays = Gen.nonEmpty (Range.constant 1 100) G.genDay

genLByteString :: Gen BL.ByteString
genLByteString =
BB.toLazyByteString . BB.byteString <$>
Gen.utf8 range100 Gen.unicodeAll

genLText :: Gen L.Text
genLText = L.fromStrict <$> G.genText

-- Tests

testBiMap
:: (Monad m, Show a, Show b, Eq a)
Expand All @@ -70,30 +36,26 @@ test_BiMaps :: PropertyTest
test_BiMaps = pure $ testGroup "BiMap roundtrip tests" $ concat
[ prop "Bool" (testBiMap B._Bool G.genBool)
, prop "Integer" (testBiMap B._Integer G.genInteger)
, prop "Natural" (testBiMap B._Natural genNatural)
, prop "Int" (testBiMap B._Int (Gen.int Range.constantBounded))
, prop "Word" (testBiMap B._Word (Gen.word Range.constantBounded))
, prop "Natural" (testBiMap B._Natural G.genNatural)
, prop "Int" (testBiMap B._Int G.genInt)
, prop "Word" (testBiMap B._Word G.genWord)
, prop "Double" testDouble
, prop "Float"
(testBiMap B._Float (Gen.float $ Range.constant (-10000.0) 10000.0))
, prop "Float" (testBiMap B._Float G.genFloat)
, prop "Text" (testBiMap B._Text G.genText)
, prop "LazyText" (testBiMap B._LText genLText)
, prop "String"
(testBiMap B._String (Gen.string range100 Gen.unicode))
, prop "LazyText" (testBiMap B._LText G.genLText)
, prop "String" (testBiMap B._String G.genString)
, prop "Read (Integer)" (testBiMap B._Read G.genInteger)
, prop "ByteString"
(testBiMap B._ByteString (Gen.utf8 range100 Gen.unicodeAll))
, prop "Lazy ByteString" (testBiMap B._LByteString genLByteString)
, prop "ByteString" (testBiMap B._ByteString G.genByteString)
, prop "Lazy ByteString" (testBiMap B._LByteString G.genLByteString)
, prop "ZonedTime" (testBiMap B._ZonedTime G.genZoned)
, prop "LocalTime" (testBiMap B._LocalTime G.genLocal)
, prop "TimeOfDay" (testBiMap B._TimeOfDay G.genHours)
, prop "Day" (testBiMap B._Day G.genDay)
, prop "IntSet" (testBiMap B._IntSet genInSet)
, prop "Array (Day)"
(testBiMap (B._Array B._Day) (Gen.list range100 G.genDay))
, prop "Set (Day)" (testBiMap (B._Set B._Day) (Gen.set range100 G.genDay))
, prop "NonEmpty (Day)" (testBiMap (B._NonEmpty B._Day) genNEDays)
, prop "HashSet (Integer)" (testBiMap (B._HashSet B._Integer) genHashSet)
, prop "IntSet" (testBiMap B._IntSet G.genIntSet)
, prop "Array (Day)" (testBiMap (B._Array B._Day) (G.genList G.genDay))
, prop "Set (Day)" (testBiMap (B._Set B._Day) (Gen.set G.range100 G.genDay))
, prop "NonEmpty (Day)" (testBiMap (B._NonEmpty B._Day) (G.genNonEmpty G.genDay))
, prop "HashSet (Integer)" (testBiMap (B._HashSet B._Integer) (G.genHashSet G.genInteger))
]

-- Orphan instances
Expand Down
Loading