{-# LANGUAGE DeriveDataTypeable #-} -- | Types with invariants. Currently these are mostly examples of how to -- define such types, suggestions on useful types are appreciated. -- -- To use the invariant types you can use the record label. For instance: -- -- @ -- data C a = C [a] [a] deriving Typeable -- instance Enumerable a => Enumerable (C a) where -- enumerate = unary $ funcurry $ -- \xs ys -> C (nonEmpty xs) (nonEmpty ys) -- @ -- -- Alternatively you can put everything in pattern postition: -- -- @ -- instance Enumerable a => Enumerable (C a) where -- enumerate = unary $ funcurry $ -- \(Free (NonEmpty xs,NonEmpty ys)) -> C xs ys) -- @ -- -- The first approach has the advantage of being usable with a -- point free style: @ \xs -> C (nonEmpty xs) . nonEmpty @. module Test.Feat.Modifiers( NonEmpty(..), mkNonEmpty, Nat(..), ) where -- testing-feat import Test.Feat.Enumerate import Test.Feat.Class -- quickcheck -- Should be made compatible at some point. -- import Test.QuickCheck.Modifiers -- | A type of non empty lists. newtype NonEmpty a = NonEmpty {nonEmpty :: [a]} deriving (Typeable, Show) mkNonEmpty x xs = x:xs instance Enumerable a => Enumerable (NonEmpty a) where enumerate = unary NonEmpty -- Copy paste from Enumerate.hs -- | A type of natural numbers. newtype Nat = Nat {nat :: Integer} deriving (Typeable, Show) instance Enumerable Nat where enumerate = let e = Enumerate{ card = crd, select = sel, optimal = return e} in e where crd p | p <= 0 = 0 | p == 1 = 1 | otherwise = 2^(p-2) sel 1 0 = Nat 0 sel p i = Nat $ 2^(p-2) + i