<div dir="ltr"><div dir="ltr"><div dir="ltr">Try this:<br>{-#LANGUAGE GADTs#-}<br><br>data Enumerator a b where<br>  Enumerator :: a -> a -> Enumerator a a<br><br>instance Enum a => Foldable (Enumerator a) where<br>  foldMap f (Enumerator x y)<br>    | fromEnum x > fromEnum y = mempty<br>    | otherwise                           = f x <> foldMap f (Enumerator (succ x) y)<br><br></div><div>Here we're using a GADT to express that our two-parameter Enumerator type in practice always has a == b (at the type level).<br></div><div>Which lets us constrain the values inside our new Foldable structure, while still having a type of kind (* -> *) like the the<br></div><div>typeclass requires.<br></div></div></div><br><div class="gmail_quote"><div dir="ltr">On Wed, Sep 5, 2018 at 6:56 AM Johannes Waldmann <<a href="mailto:johannes.waldmann@htwk-leipzig.de">johannes.waldmann@htwk-leipzig.de</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Hi David,<br>
<br>
Thanks for responding.<br>
Let me re-phrase the technical question: in some hypothetical<br>
<br>
>       instance Foldable Enumerator where ...<br>
<br>
the methods (e.g., foldMap) would be overconstrained.<br>
Is there a way to still write something like it?<br>
<br>
It seems not, as shown by these examples:<br>
<br>
Data.EnumSet cannot implement Foldable because of  Enum k.<br>
<a href="http://hackage.haskell.org/package/enummapset/docs/Data-EnumSet.html" rel="noreferrer" target="_blank">http://hackage.haskell.org/package/enummapset/docs/Data-EnumSet.html</a><br>
<br>
Data.IntSet cannot implement Foldable because of   k ~ Int.<br>
<br>
- J.<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
Only members subscribed via the mailman list are allowed to post.</blockquote></div>