Qualified variable in pattern: T.mkRoot

The following short program: module Main where Just foo = undefined Causes an error message: hmake -hat hatd.hs hat-trans hatd.hs Wrote Hat/hatd.hs /usr/bin/haskell-compiler -c -package hat -o Hat/hatd.o Hat/hatd.hs Hat/hatd.hs:10:10: Qualified variable in pattern: T.mkRoot with hat 2.0.4 and ghc 6.4-2 (debian) --ken

The following short program:
module Main where Just foo = undefined
Causes an error message: hmake -hat hatd.hs hat-trans hatd.hs Wrote Hat/hatd.hs /usr/bin/haskell-compiler -c -package hat -o Hat/hatd.o Hat/hatd.hs
Hat/hatd.hs:10:10: Qualified variable in pattern: T.mkRoot
with hat 2.0.4 and ghc 6.4-2 (debian) To be honest, I'm not sure if this is your problem, because I'm not sure what the above program is supposed to do, but it gives a compile error when not using hat too.
ghc -c -o foo.o foo.hs foo.hs:1: The main function `main' is not defined in module `Main' In general, if you give hat a program that produces a compile error, then compiling with hat on will give you a more cryptic one. I wonder if this is a place we can improve error messages by compiling without hat and spewing out that error automatically. Bob

On 28 Jun 2005, at 21:03, Ken T Takusagawa wrote:
The following short program:
module Main where Just foo = undefined
Causes an error message: hmake -hat hatd.hs hat-trans hatd.hs Wrote Hat/hatd.hs /usr/bin/haskell-compiler -c -package hat -o Hat/hatd.o Hat/hatd.hs
Hat/hatd.hs:10:10: Qualified variable in pattern: T.mkRoot
with hat 2.0.4 and ghc 6.4-2 (debian)
My last reply I realise was somewhat useless - in that the addition of a main function still gives the error. However, I think that this is actually hat catching a syntactic error that the normal compilers don't catch... The haskell syntax states: decl -> gendecl | (funlhs | pat0) rhs where, gendecl covers type definitions, funlhs covers functions (and must start with a lower case character), and pat0 covers 0 arity paterns. Correct me if I'm wrong, bit if I'm reading the syntax correctly (a big if), then this program is not correct Haskell 98. Bob

On Wed, Jun 29, 2005 at 12:11:22PM +0100, Thomas Davie wrote:
On 28 Jun 2005, at 21:03, Ken T Takusagawa wrote:
The following short program:
module Main where Just foo = undefined
Causes an error message: hmake -hat hatd.hs hat-trans hatd.hs Wrote Hat/hatd.hs /usr/bin/haskell-compiler -c -package hat -o Hat/hatd.o Hat/hatd.hs
Hat/hatd.hs:10:10: Qualified variable in pattern: T.mkRoot
with hat 2.0.4 and ghc 6.4-2 (debian)
My last reply I realise was somewhat useless - in that the addition of a main function still gives the error. However, I think that this is actually hat catching a syntactic error that the normal compilers don't catch... The haskell syntax states:
decl -> gendecl | (funlhs | pat0) rhs
where, gendecl covers type definitions, funlhs covers functions (and must start with a lower case character), and pat0 covers 0 arity paterns.
The 0 is the tightness of binding, not the arity. pat^0 -> pat^1 -> ... -> pat^10 -> gcon apat_1 Such contructs look a bit odd at the top level, but I think foo x = f y where Just y = x is more common. Even more so is [ x | Just x <- xs] Thanks Ian

The 0 is the tightness of binding, not the arity.
pat^0 -> pat^1 -> ... -> pat^10 -> gcon apat_1
Such contructs look a bit odd at the top level, but I think
foo x = f y where Just y = x
is more common. Even more so is
[ x | Just x <- xs]
Okay, I see that, now I'm slightly intrigued -- if, as before, we have Just foo = undefined Doesn't that have 2 effects: foo = undefined undefined :: Maybe a and thus cause a type error (i.e. undefined has become too specific)? Bob

Thomas Davie
Okay, I see that, now I'm slightly intrigued -- if, as before, we have
Just foo = undefined
Doesn't that have 2 effects: foo = undefined undefined :: Maybe a
and thus cause a type error (i.e. undefined has become too specific)?
No, 'foo' does not literally gain the value of 'undefined'. In fact, foo gets no value at all, because the computation diverges before the pattern can be matched. /Semantically/ divergence is equivalent to 'undefined', but syntactically, 'foo' and 'undefined' are separate bindings, and their types are therefore not constrained to be equal. Regards, Malcolm

On 29 Jun 2005, at 16:47, Malcolm Wallace wrote:
Thomas Davie
writes: Okay, I see that, now I'm slightly intrigued -- if, as before, we have
Just foo = undefined
Doesn't that have 2 effects: foo = undefined undefined :: Maybe a
and thus cause a type error (i.e. undefined has become too specific)?
No, 'foo' does not literally gain the value of 'undefined'. In fact, foo gets no value at all, because the computation diverges before the pattern can be matched. /Semantically/ divergence is equivalent to 'undefined', but syntactically, 'foo' and 'undefined' are separate bindings, and their types are therefore not constrained to be equal.
Okay, but does this not force undefined to have the type Maybe a? i.e. Just x = undefined File y = undefined would cause a type error? Bob

Thomas Davie
No, 'foo' does not literally gain the value of 'undefined'. In fact, foo gets no value at all, because the computation diverges before the pattern can be matched. /Semantically/ divergence is equivalent to 'undefined', but syntactically, 'foo' and 'undefined' are separate bindings, and their types are therefore not constrained to be equal.
Okay, but does this not force undefined to have the type Maybe a?
i.e. Just x = undefined File y = undefined
would cause a type error?
'undefined :: forall a . a' is a truly polymorphic value, in fact the only possible value of such an unconstrained type. In your example, it is instantiated twice, at different actual types, just as for instance the polymorphic function 'map' can be instantiated at several different actual types: map toUpper "hello" map (+1) [1,2,3] The only place where instantiating a polymorphic value at different types might cause a problem is in a recursive definition where the usage occurrence is at a different type to the defining occurrence, e.g. f x = f [x] Most functional languages do not permit this because it makes type inference undecidable. However Haskell allows it, provided that you give an explicit type signature so full inference is not required. Regards, Malcolm

On Wed, 2005-06-29 at 16:47 +0100, Malcolm Wallace wrote:
Thomas Davie
writes: Okay, I see that, now I'm slightly intrigued -- if, as before, we have
Just foo = undefined
Sorry to jump in the middle of this discussion. In Hat do you desugar the above code to: v = undefined foo = (\Just x -> x) v Cheers, Bernie.

Thomas Davie
Just foo = undefined
The haskell syntax states:
decl -> gendecl | (funlhs | pat0) rhs
where, gendecl covers type definitions, funlhs covers functions (and must start with a lower case character), and pat0 covers 0 arity patterns.
The notation pat_0 does not mean zero-arity, but zero-fixity. Thus, since any pat_i can be a pat_i+1, and pat_10 -> apat | gcon apat_1 ... apat_k the given declaration is syntactically valid, even though it is certainly unusual. hat-trans is generating bad code for this, because the pattern binding is at the toplevel. If the pattern binding were in a let or where clause, the generated code is different. When not at the toplevel, the parent, p, of the binding is always a variable passed in. But at the toplevel, there is no static parent, so hat-trans has wrongly substituted T.mkRoot (which explicitly represents no parent), in both the generated pattern and the generated expression: gx px T.mkRoot = T.constUse px T.mkRoot sx -- incorrect vs. gx px p = T.constUse px p sx -- correct I think the attached patch for hat-trans should fix the problem (but would like someone to confirm this is not going to break anything else, before I will commit it to CVS). Regards, Malcolm

hat-trans is generating bad code for this, because the pattern binding is at the toplevel. If the pattern binding were in a let or where clause, the generated code is different. When not at the toplevel, the parent, p, of the binding is always a variable passed in. But at the toplevel, there is no static parent, so hat-trans has wrongly substituted T.mkRoot (which explicitly represents no parent), in both the generated pattern and the generated expression:
gx px T.mkRoot = T.constUse px T.mkRoot sx -- incorrect vs. gx px p = T.constUse px p sx -- correct
I think the attached patch for hat-trans should fix the problem (but would like someone to confirm this is not going to break anything else, before I will commit it to CVS).
You are absolutely right. I just committed it to CVS. Ciao, Olaf
participants (7)
-
Bernard Pope
-
Ian Lynagh
-
Ken T Takusagawa
-
Malcolm Wallace
-
Olaf Chitil
-
Thomas Davie
-
Thomas Davie