-- ~\~ language=Haskell filename=test/less/LessArbitrary.hs -- ~\~ begin <>[0] -- ~\~ begin <>[0] {-# language FlexibleInstances #-} {-# language Rank2Types #-} {-# language MultiParamTypeClasses #-} {-# language ScopedTypeVariables #-} {-# language TypeOperators #-} {-# language UndecidableInstances #-} {-# language AllowAmbiguousTypes #-} {-# language DeriveGeneric #-} module Main where import Data.Proxy import Test.QuickCheck import qualified GHC.Generics as Generic import Test.QuickCheck.Classes import Test.LessArbitrary import Test.Arbitrary.Laws import Test.LessArbitrary.Laws -- ~\~ begin <>[0] data Tree a = Leaf a | Branch [Tree a] deriving (Eq,Show,Generic.Generic) -- ~\~ end -- ~\~ end -- ~\~ begin <>[0] instance LessArbitrary a => LessArbitrary (Tree a) where instance LessArbitrary a => Arbitrary (Tree a) where arbitrary = fasterArbitrary -- ~\~ end -- ~\~ begin <>[0] main :: IO () main = do lawsCheckMany [("Tree", [arbitraryLaws (Proxy :: Proxy (Tree Int)) ,eqLaws (Proxy :: Proxy (Tree Int)) ] <> otherLaws)] -- ~\~ end -- ~\~ begin <>[0] otherLaws :: [Laws] otherLaws = [lessArbitraryLaws isLeaf] where isLeaf :: Tree Int -> Bool isLeaf (Leaf _) = True isLeaf (Branch _) = False -- ~\~ end -- ~\~ end