[Haskell-cafe] Type Families: infinite compile process?
Hugo Pacheco
hpacheco at gmail.com
Mon Apr 7 17:30:33 EDT 2008
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/6d2430db/attachment.htm
More information about the Haskell-Cafe
mailing list