Dear type wizards,

what's wrong with the following program?

> module Test where
> data Empty q                  =  Empty (Ord a => q a)
> q                             :: (Ord a) => [a]
> q                             =  []
> e0, e1, e2                    :: Empty []
> e0                            =  Empty []
> e1                            =  Empty ([] :: (Ord a) => [a])
> e2                            =  Empty q


ghc-2.08 tells me ...


> ghc -c -fglasgow-exts Test.lhs
 
Test.lhs:11: Context `{Ord taDr}'
                 required by inferred type, but missing on a type signature
                 `Ord taDr' arising from use of `q' at Test.lhs:11
    In a polymorphic function argument `q'
    In the first argument of `Empty', namely `q'
    In a pattern binding: `e2 = Empty q'

Compilation had errors


If I remove the definition of `e2' everything works fine. But look:
`q' is just a name for `[]'. Maybe it's a bug ssssssszzzzzzzzzzzzd?

Ralf

Reply via email to