{-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -Wno-orphans #-} module TestSepList (properties) where import Lawless import Textual import Test.Framework import Test.Framework.TH import Test.Framework.Providers.QuickCheck2 (testProperty) import Test.QuickCheck import qualified Data.ByteString.Lazy as L import Data.Binary instance Arbitrary (SepList Char) where arbitrary = foldl1Of folded (<>) . over traversed sepList <$> listOf1 arbitrary prop_Semigroup :: SepList Char -> SepList Char -> Property prop_Semigroup (a :: SepList Char) (b :: SepList Char) = (a <> b) ^. slItems === (a ^. slItems) <> (b ^. slItems) prop_Serialize :: SepList Char -> Property prop_Serialize (a :: SepList Char) = let sz = L.toStrict $ encode a de = decode $ L.fromStrict sz in (de ^. slItems) === (a ^. slItems) properties ∷ Test properties = $(testGroupGenerator)