[Yhc] Incomprehensible error messages
Stefan O'Rear
stefanor at cox.net
Mon Jun 4 18:30:51 EDT 2007
On Mon, Jun 04, 2007 at 12:05:56PM -0700, David Fox wrote:
> I created this file by simplifying an error I was getting from a
> program that uses the Javascript types. If you remove the type
> signatures for f1 and f2 it compiles, but how do I fix the error I get
> when I compile with the signatures?
>
> module Main where
>
> type CPS c a = (a -> c) -> c
>
> class CNode a
> data TNode = TNode
> instance CNode TNode
>
> m :: TNode -> TNode -> Bool
> m a b = f1 b a $ \_ -> True
>
> f1 :: (CNode a, CNode b) => a -> b -> CPS c a
> f1 a b f = f2 a b $ \_ -> f a
>
> f2 :: (CNode a, CNode b) => a -> b -> CPS c a
> f2 a b f = f1 a b $ \_ -> f a
>
> This gives these messages:
>
> yhc -linkcore Browser3.hs
> Compiling Main ( Browser3.hs )
> -- during after type inference/checking
> Error: No default for Main.CNode at 16:1-16:29.(Id 215,[(Id 200,Id 250)])
> Error: No default for Main.CNode at 16:1-16:29.(Id 214,[(Id 200,Id 251)])
> Error: No default for Main.CNode at 13:1-13:29.(Id 220,[(Id 200,Id 248)])
> Error: No default for Main.CNode at 13:1-13:29.(Id 219,[(Id 200,Id 249)])
>
> You can replace the CNode/TNode and CPS declarations with this:
>
> import DOM.Level1.Html
> import DOM.Level1.Dom
> import CPS
>
> same result.
Works fine in both GHC and Hugs. I don't think this bug will be fixed,
because the current typechecker is already on the chopping block (see
Matthieu's SoC project). So just wait a few months, or help.
Stefan
More information about the Yhc
mailing list