deriving instances of Enum for tuples of bounded, enumerable types (useful for generating QuickCheck.Arbitrary instances for collection of collection types)

I have some code for creating instances of Enum for a tuple of bounded enumerable types. The main win with this was that it makes it easier for me to generate Test.QuickCheck.Arbitrary instances for types that are based on collections of enumerable collections -- like you might get when modeling poker for instance. In fact, I was trying to answer the question about using QuickCheck with poker, that Vincent Foley asked a few days ago at http://groups.google.com/group/fa.haskell/browse_thread/thread/8298c4d838c95... when I came up with this. (And I am posting a reply to Vincent right after I finish writing this message.) Basically I noticed that coming up with the Arbitrary instances seemed to be tricker than I would have expected. However, it was pretty straightforward to write an instance of arbitrary for instance (Enum a, Bounded a) => Arbitrary a where arbitrary = do n <- choose (fromEnum (minBound :: a), fromEnum (maxBound :: a) ) return $ toEnum n So all I needed to do was get my type into instances of Enum and Bounded, and I got my Arbitrary instance for free. Most of the work was just writing the instances for various tuples of Bounded Enumerable types. Maybe I've been spoiled by how easy many types are gotten using the magic of the deriving clause, but this seemed like a lot of work to me. I was wondering if there was an easier way? Or if not, if it would make sense for something like this to be added to the prelude? Or is there some sizeable collection of nice Arbitrary instances for QuickCheck somewheres that I can leverage off of, that hasn't made it into the standard libraries? A minor issue: I had a question if I could make the type signatures for Enum instances less verbose by doing something like type BoundedEnum = (Bounded a, Enum a) => a... I tried, and commented out my attempt as it wouldn't type check. Guidance appreciated. Thanks, Thomas. Code follows: {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-} module EnumInstances where -- instances of Enum for tuples of types that are both Bounded and Enum -- typechecks, and does the right thing, though this signature seems messy, specially when I -- want to do this kind of thing for longer tuples instance (Enum a, Enum b,Bounded a, Bounded b) => Enum (a,b) where fromEnum (primero,segundo) = ( divFactor * (fromEnum primero) ) + (fromEnum segundo) where divFactor = fromEnum (maxBound :: b) + 1 toEnum i | (i > (fromEnum (maxBound :: (a,b)))) || (i < (fromEnum (minBound :: (a,b)))) = error "Enum (a,b) bounds error" | otherwise = (a,b) where a = toEnum baseline b = toEnum $ i - (baseline * divFactor ) baseline = i `div` divFactor divFactor = (fromEnum (maxBound :: b)) + 1 -- I tried to use a type synonym to write a cleaner type syg but... type BoundedEnumerable = (Enum a, Bounded a) => a -- does not typecheck. oh well, the verbose signatures aren't all that bad. {- instance Enum (BoundedEnumerable,BoundedEnumerable) where fromEnum (primero,segundo) = ( divFactor * (fromEnum primero) ) + (fromEnum segundo) where divFactor = fromEnum (maxBound :: b) + 1 toEnum i | (i > (fromEnum (maxBound :: (a,b)))) || (i < (fromEnum (minBound :: (a,b)))) = error "Enum (a,b) bounds error" | otherwise = (a,b) where a = toEnum baseline b = toEnum $ i - (baseline * divFactor ) baseline = i `div` divFactor divFactor = (fromEnum (maxBound :: b)) + 1 -} instance (Enum t, Enum t1, Enum t2, Bounded t, Bounded t1, Bounded t2) => Enum (t,t1,t2) where fromEnum (a,b,c) = fromEnum ((a,b),c) toEnum i = (a,b,c) where ((a,b),c) = toEnum i instance (Enum t, Enum t1, Enum t2, Enum t3, Bounded t, Bounded t1, Bounded t2, Bounded t3) => Enum (t,t1,t2,t3) where fromEnum (a,b,c,d) = fromEnum ((a,b,c),d) toEnum i = (a,b,c,d) where ((a,b,c),d) = toEnum i instance (Enum t, Enum t1, Enum t2, Enum t3, Enum t4, Bounded t, Bounded t1, Bounded t2, Bounded t3, Bounded t4) => Enum (t,t1,t2,t3,t4) where fromEnum (a,b,c,d,e) = fromEnum ((a,b,c,d),e) toEnum i = (a,b,c,d,e) where ((a,b,c,d),e) = toEnum i

On Mar 8, 2008, at 22:06 , Thomas Hartman wrote:
A minor issue: I had a question if I could make the type signatures for Enum instances less verbose by doing something like type BoundedEnum = (Bounded a, Enum a) => a... I tried, and commented out my attempt as it wouldn't type check. Guidance appreciated.
Nope. Uses of "type" declarations are self-contained; if you do type BoundedEnum = (Bounded a, Enum a) => a myFunc :: BoundedEnum -> BoundedEnum -> BoundedEnum each instance of BoundedEnum in the declaration of BoundedEnum refers to a distinct a. More technically, the declaration expands to: myFunc :: (forall a. (Bounded a, Enum a) => a) -> (forall a. (Bounded a, Enum a) => a) -> (forall a. (Bounded a, Enum a) => a) which is a rather useless declaration (I think the only inhabitant of that type is _|_). And yes, this is annoying. I think you might be able to do this as a typeclass instead, at the expense of having to insert an instance declaration for each type. (You will have to use an extension if you want to declare instances for types such as Int. I think.) class (Bounded a, Enum a) => BoundedEnum a where -- empty instance BoundedEnum MyType a where instance BoundedEnum Int where -- requires FlexibleInstances? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Sun, Mar 9, 2008 at 3:23 AM, Brandon S. Allbery KF8NH
myFunc :: (forall a. (Bounded a, Enum a) => a) -> (forall a. (Bounded a, Enum a) => a) -> (forall a. (Bounded a, Enum a) => a)
which is a rather useless declaration (I think the only inhabitant of that type is _|_).
Just to nitpick: this function type is quite specific, and there are many non _|_ implementations. myFunc a b = a myFunc a b = b myFunc a b = toEnum (f a b) where f :: Int -> Int -> Int ... Luke

On Sat, Mar 8, 2008 at 9:23 PM, Brandon S. Allbery KF8NH
I think you might be able to do this as a typeclass instead, at the expense of having to insert an instance declaration for each type. (You will have to use an extension if you want to declare instances for types such as Int. I think.)
class (Bounded a, Enum a) => BoundedEnum a where -- empty
instance BoundedEnum MyType a where instance BoundedEnum Int where -- requires FlexibleInstances?
I've had good luck with things like: class (Bounded a, Enum a) => BoundedEnum a instance (Bounded a, Enum a) => BoundedEnum a which picks up everything that can inhabit the new class. -Antoine
participants (4)
-
Antoine Latter
-
Brandon S. Allbery KF8NH
-
Luke Palmer
-
Thomas Hartman