On Mon, Jul 17, 2000 at 03:40:29 +0200, Michael Weber wrote:

> Marcin reported a fault with AClass before, it looked like this:
> ------------------------------------------------------------------------
> module Test where
> 
> class Lookup c k a where
>     lookupAll :: Sequence seq a => c -> k -> seq a
> 
> class Lookup (s a) Int a => Sequence s a where
>     foo :: s a
> ------------------------------------------------------------------------

I tested the above piece with my 4.08.0 package and it *really* emits
just `AClass' (as Martin reported before).

IMHO, this comes from ghc/compiler/typecheck/TcTyClsDecls.lhs:203

[...]
getTyBinding1 (ClassDecl _ name tyvars _ _ _ _ _ _ _ _ _)
 = mapNF_Tc kcHsTyVar tyvars            `thenNF_Tc` \ arg_kinds ->
   returnNF_Tc (name, (foldr mkArrowKind boxedTypeKind arg_kinds,
                       Just (length tyvars),
                       AClass (error "AClass")))
[...]                  

In the HEAD, it's a bit more descriptive: 

                AClass (pprPanic "AClass" (ppr name)) (length tyvars)))

                
Cheers,
Michael
-- 
() ASCII ribbon campaign |  Chair for Computer Science  II  | GPG: F65C68CD
/\ against HTML mail     |       RWTH Aachen, Germany       | PGP: 1D0DD0B9
   When someone says "I want a programming language in which I need only
                say what I wish done," give him a lollipop.

Reply via email to