
Sorry, could you explain further? I don't understand what the implementation of any of those proposed instances is supposed to be.
Sure. {-# LANGUAGE ConstraintKinds #-} type BoundedEnum a = (Bounded a, Enum a) instance (BoundedEnum b) => Enum (Either a b) where fromEnum (Left _) = 0 fromEnum (Right x) = 1 + fromEnum x toEnum 0 = error "toEnum: zero" -- could also add a Monoid constraint instead toEnum n = Right . toEnum $ n-1 instance (Bounded b) => Bounded (Either a b) where minBound = Right minBound maxBound = Right maxBound Rationale: these two implement the use case of working on something from a finite selection of elements inside a monad stack. In other words it's a special case of instance (Applicative f, Bounded a) => Bounded (f a) where minBound = pure minBound maxBound = pure maxBound Is it a good idea to implement this? Probably not, but it serves as an illustration. On the other hand, many error types are bounded and enumerable, so why not enhance the error handling instead? instance (BoundedEnum a, Monoid b) => Enum (Either a b) where -- okay, I cheated by adding the Monoid constraint this time fromEnum (Right _) = 0 fromEnum (Left e) = 1 + fromEnum e toEnum 0 = Right mempty toEnum n = Left . toEnum $ n-1 instance (Bounded a) => Bounded (Either a b) where minBound = Left minBound maxBound = Left maxBound Which is better? That depends. Now for product types: instance (Enum a, Monoid b) => Enum (a, b) where toEnum = (,mempty) . toEnum fromEnum = fromEnum . fst instance (Enum b, Monoid a) => Enum (a, b) where toEnum = (mempty,) . toEnum fromEnum = fromEnum . snd And to be thorough enumAll :: (BoundedEnum a) => [a] enumAll = enumFromTo minBound maxBound Hope it's clearer now what I meant.