Circular Instance Declarations
Brandon Michael Moore
brandon at its.caltech.edu
Sun Sep 14 01:40:05 EDT 2003
On Thu, 11 Sep 2003, Simon Peyton-Jones wrote:
> OK, I yield!
>
> The HEAD now runs this program. It turned out to be a case of
> interchanging two lines of code, which is the kind of fix I like.
>
> Simon
Cool! Yet another domain where haskell handles infinities quite happily.
Thanks.
Hopefully I'll have some code to contribute soon.
Brandon
>
>
> | -----Original Message-----
> | From: haskell-admin at haskell.org [mailto:haskell-admin at haskell.org] On
> Behalf Of Ashley Yakeley
> | Sent: 07 September 2003 06:57
> | To: haskell at haskell.org
> | Subject: Circular Instance Declarations
> |
> | When -fallow-undecidable-instances is switched on, is there any reason
> | why circular instances are forbidden? For instance:
> |
> | module CircularInsts where
> | {
> | data D r = ZeroD | SuccD (r (D r));
> |
> | instance (Eq (r (D r))) => Eq (D r) where
> | {
> | ZeroD == ZeroD = True;
> | (SuccD a) == (SuccD b) = a == b;
> | _ == _ = False;
> | };
> |
> | newtype C a = MkC a deriving Eq;
> |
> | equalDC :: D C -> D C -> Bool;
> | equalDC = (==);
> | }
> |
> | When I compile this, I get this:
> |
> | $ ghc -fglasgow-exts -fallow-undecidable-instances -c
> CircularInsts.hs
> | CircularInsts.hs:2:
> | Context reduction stack overflow; size = 21
> | Use -fcontext-stack20 to increase stack size to (e.g.) 20
> | `Eq (C (D C))' arising from use of `==' at CircularInsts.hs:16
> | `Eq (D C)' arising from use of `==' at CircularInsts.hs:16
> | `Eq (C (D C))' arising from use of `==' at CircularInsts.hs:16
> | `Eq (D C)' arising from use of `==' at CircularInsts.hs:16
> |
> | Would it be reasonable for the compiler to check back through the
> stack
> | and allow the circularity? It will just create an ordinary recursive
> | function.
> |
> | --
> | Ashley Yakeley, Seattle WA
> |
> | _______________________________________________
> | Haskell mailing list
> | Haskell at haskell.org
> | http://www.haskell.org/mailman/listinfo/haskell
>
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
>
>
More information about the Haskell
mailing list