-- | Test encoding and decoding options. {-# LANGUAGE TemplateHaskell, ExtendedDefaultRules #-} {-# OPTIONS_GHC -Wno-orphans #-} module TestAeson where import Test.Framework import Test.Framework.TH import Test.Framework.Providers.QuickCheck2 (testProperty) import Test.QuickCheck import Data.String (String) import Lawless import Aeson import Text import Generics import Data.Text (pack) default (Text) data TestData = TestData { _tdName ∷ Text, _tdCount ∷ Integer } deriving (Show, Eq, Ord, Generic) makeLenses ''TestData instance ToJSON TestData where toEncoding = lawlessToJSONEncoding instance FromJSON TestData where parseJSON = lawlessParseJSON instance Arbitrary Text where arbitrary = pack <$> arbitrary instance Arbitrary TestData where arbitrary = TestData <$> arbitrary <*> arbitrary prop_TestEncodingSimple :: TestData -> Property prop_TestEncodingSimple (td :: TestData) = let enc = encode td dec ∷ Either String TestData dec = eitherDecode enc in collect "dec ∘ enc ≍ id" $ isn't _Left dec data Cluster = Cluster { _clName ∷ Text, _clRegion ∷ Text } deriving (Show, Eq, Ord, Generic) instance ToJSON Cluster where toEncoding = lawlessToJSONEncoding instance FromJSON Cluster where parseJSON = lawlessParseJSON data Schema1 = Schema1 { _sc1Name ∷ Text, _sc1Cluster ∷ Cluster } deriving (Show, Eq, Ord, Generic) instance ToJSON Schema1 where toEncoding = lawlessToJSONEncoding instance FromJSON Schema1 where parseJSON = lawlessParseJSON properties ∷ Test properties = $(testGroupGenerator)