[Haskell-cafe] Re: Type Families: infinite compile process?

Hugo Pacheco hpacheco at gmail.com
Mon Apr 7 17:46:40 EDT 2008


The problem is that the representation probably does not reduce to a normal
form.
Say, for the case

type instance F (Nest a) x = Either() (a,F a x)

fnn :: F (Nest a) (Nest a)
fnn = Left ()

it compiles ok.

But why can't the representation be infinite, like any other infinite data
type?
Cheers,
hugo


On Mon, Apr 7, 2008 at 10:30 PM, Hugo Pacheco <hpacheco at gmail.com> wrote:

> Hi guys,
> I have been experimenting some weird stuff (risky, yes I know) but the
> behaviour was certainly not the one I expected:
>
> {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}
>
> module Nest where
>
> data Nest a = Nil | Cons a (Nest (a,a))
>
> type family F a x :: *
> type instance F (Nest a) x = Either () (a,F (Nest (a,a)) x)
>
> fnn :: F (Nest Int) (Nest Int)
> fnn = Left ()
>
> The following module fails to compile (or better, compilation never ends).
>
> Maybe there is something very bad going on due to the
> undecidable-instances extension?
>
> Any clue?
> hugo
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080407/d692d401/attachment.htm


More information about the Haskell-Cafe mailing list