Try this:
{-#LANGUAGE GADTs#-}

data Enumerator a b where
  Enumerator :: a -> a -> Enumerator a a

instance Enum a => Foldable (Enumerator a) where
  foldMap f (Enumerator x y)
    | fromEnum x > fromEnum y = mempty
    | otherwise                           = f x <> foldMap f (Enumerator (succ x) y)

Here we're using a GADT to express that our two-parameter Enumerator type in practice always has a == b (at the type level).
Which lets us constrain the values inside our new Foldable structure, while still having a type of kind (* -> *) like the the
typeclass requires.

On Wed, Sep 5, 2018 at 6:56 AM Johannes Waldmann <johannes.waldmann@htwk-leipzig.de> wrote:
Hi David,

Thanks for responding.
Let me re-phrase the technical question: in some hypothetical

>       instance Foldable Enumerator where ...

the methods (e.g., foldMap) would be overconstrained.
Is there a way to still write something like it?

It seems not, as shown by these examples:

Data.EnumSet cannot implement Foldable because of  Enum k.
http://hackage.haskell.org/package/enummapset/docs/Data-EnumSet.html

Data.IntSet cannot implement Foldable because of   k ~ Int.

- J.
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.