Circular Instance Declarations
Brandon Michael Moore
brandon@its.caltech.edu
Sun, 7 Sep 2003 21:07:59 -0700 (PDT)
Hi Ashley
See the thread "Type Class Problem". In his post on Aug 22 Simon
Peyton-Jones said that it shouldn't be hard to implement, and mentioned
that it would ruin the property that dictionaries can be evaluated by
call-by-value. I couldn't puzzle out enough of the type class system to
make the change on my first try, and since then I've been looking for a
more general solution
Actually, I'm surprised someone else has a use for this. I wanted
circular instances for playing with the paper "Recursion Schemes from
Comonads". What are you trying to do?
Detecting circularity in a derivation is equivalent to accepting a regular
infinite derivation for instances. Would you have a use for irregular
derivations?
Brandon
On Sat, 6 Sep 2003, Ashley Yakeley wrote:
> 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@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
>