Hat bug report: Ambiguous occurrence `List'

I am trying to get Hat working on a reasonably large and complicated project. Unfortunately it doesn't work. I have cut down the code which triggers the problem to the following simple test case: | bash$ cat Foo/List.hs | module Foo.List where | | class List a b where | foo :: a -> b | | main :: IO () | main = return () | | bash$ hmake -hat Foo/List | hat-trans Foo/List.hs | Creating directories Hat Hat/Foo | Wrote Hat/Foo/List.hs | /usr/bin/haskell-compiler -c -package hat -o Hat/Foo/List.o Hat/Foo/List.hs | | Hat/Foo/List.hs:1: | Ambiguous occurrence `List' | It could refer to either `Hat.Hat.List', imported from Hat.Prelude at Hat/Foo/List.hs:30 | or `Hat.Foo.List.List', defined at Hat/Foo/List.hs:32 I am using hat-2.02.8 with ghc 6.2 on Debian Linux. -- Fergus J. Henderson | "I have always known that the pursuit Galois Connections, Inc. | of excellence is a lethal habit" Phone: +1 503 626 6616 | -- the last words of T. S. Garp.

Fergus Henderson
| Hat/Foo/List.hs:1: | Ambiguous occurrence `List' | It could refer to either `Hat.Hat.List', imported from Hat.Prelude at | Hat/Foo/List.hs:30 | or `Hat.Foo.List.List', defined at | Hat/Foo/List.hs:32
Unfortunately, ghc-6 seems to be rather over-eager to report ambiguous use of identifiers, where in fact the usage is not ambiguous (the Hat.Hat versions are only visible qualified, whereas your Foo.List is visible unqualified). In this regard, Hat does steal a couple of identifiers from the user when you are using ghc-6. 'List' is one of these. 'Fun' is another. Ideally we will try to find a fix for this. In the meantime, you can work around the bug either by renaming your own versions of the overlapping identifiers, or always using them qualified (including in export lists). Regards, Malcolm

On 22-Jun-2004, Malcolm Wallace
Fergus Henderson
writes: | Hat/Foo/List.hs:1: | Ambiguous occurrence `List' | It could refer to either `Hat.Hat.List', imported from Hat.Prelude at | Hat/Foo/List.hs:30 | or `Hat.Foo.List.List', defined at | Hat/Foo/List.hs:32
Unfortunately, ghc-6 seems to be rather over-eager to report ambiguous use of identifiers, where in fact the usage is not ambiguous (the Hat.Hat versions are only visible qualified, whereas your Foo.List is visible unqualified).
The Hat.Hat versions are imported unqualified in line 30 of Hat/Foo/List.hs, which is "import Hat.Prelude". So I think this is a Hat bug, not a ghc bug.
Ideally we will try to find a fix for this. In the meantime, you can work around the bug either by renaming your own versions of the overlapping identifiers, or always using them qualified (including in export lists).
And including in _implicit_ export lists? Well, I tried that, but the result was another Hat bug: a pattern match failure for the following function in src/hattrans/TraceId.hs: tyClsInfo :: TraceId -> TyCls tyClsInfo (TI _ (Just (TyCls tyCls))) = tyCls | bash$ hmake -hat Main.hs | hat-trans Foo/List.hs | Creating directories Hat Hat/Foo | | Fail: TraceId.hs:152: Non-exhaustive patterns in function tyClsInfo | | bash$ cat Main.hs | import Foo.List | main = Foo.List.main | | bash$ cat Foo/List.hs | module Foo.List(Foo.List,main) where | | class List a b where | foo :: a -> b | | main :: IO () | main = return () -- Fergus J. Henderson | "I have always known that the pursuit Galois Connections, Inc. | of excellence is a lethal habit" Phone: +1 503 626 6616 | -- the last words of T. S. Garp.

Fergus Henderson
Unfortunately, ghc-6 seems to be rather over-eager to report ambiguous use of identifiers, ...
The Hat.Hat versions are imported unqualified in line 30 of Hat/Foo/List.hs, which is "import Hat.Prelude". So I think this is a Hat bug, not a ghc bug.
Yes, I realised this shortly after posting, when I discovered the indirect import route via Hat.Prelude. I am cooking up a relatively simple hack to fix this. Patch attached. (Hoping you can re-build the hat-lib from sources.)
Ideally we will try to find a fix for this. In the meantime, you can work around the bug either by renaming your own versions of the overlapping identifiers, or always using them qualified (including in export lists).
And including in _implicit_ export lists?
Well, in that case, global renaming might be the better workaround than identifier qualification.
Well, I tried that, but the result was another Hat bug: a pattern match failure for the following function in src/hattrans/TraceId.hs:
tyClsInfo :: TraceId -> TyCls tyClsInfo (TI _ (Just (TyCls tyCls))) = tyCls
Fail: TraceId.hs:152: Non-exhaustive patterns in function tyClsInfo
I couldn't reproduce this bug with the current CVS sources. In any case, if the other patch works, you shouldn't need to alter your own sources after all, so hopefully this issue will go away. Regards, Malcolm

Fail: TraceId.hs:152: Non-exhaustive patterns in function tyClsInfo
I couldn't reproduce this bug with the current CVS sources.
Further to this, I have found some existing patches to Hat-2.02 that enable qualified use of class names, so perhaps these are missing from your version. Regards, Malcolm

On 22-Jun-2004, Malcolm Wallace
Hoping you can re-build the hat-lib from sources.
I did indeed eventually succeed in building it from the CVS sources. And the patch that you made solved the ambiguity problem. However, unfortunately I then ran into another problem. The symptom is $ make hat HATFLAGS=-I. hmake -hat -i. -i/usr/include/hat -i/home/users/fjh007/install/hat-cvs/include/hat -i./ghc -i./unix -package concurrent -package net -package posix -package hat -O -Wall -package-name galois -Iunix/include -Iinclude -c Codec/Base64.hs -o Hat/Codec/Base64.o hat-trans -I. Codec/Base64.hs Fail: /usr/local/include/hat/Data/Word.hx: openFile: does not exist (No such file or directory) /usr/bin/haskell-compiler -package concurrent -package net -package posix -package hat -O -Wall -package-name galois -c -o -Iunix/include -Iinclude -i. -i/usr/include/hat -i/home/users/fjh007/install/hat-cvs/include/hat -i./ghc -i./unix -iunix/include -iinclude -c -package hat -o Hat/Codec/Base64.o Hat/Codec/Base64.hs ghc-6.2: file `Hat/Codec/Base64.hs' does not exist make: *** [Hat/Codec/Base64.o] Error 1 I'm not quite sure why it goes on and invokes /usr/bin/haskell-compiler after the openFile failure. But that's a side issue. The main problem here seems to be that Hat doesn't support the "Data.Word" module. Is there any simple work-around? I'm not particularly interested in tracing that module. -- Fergus J. Henderson | "I have always known that the pursuit Galois Connections, Inc. | of excellence is a lethal habit" Phone: +1 503 626 6616 | -- the last words of T. S. Garp.

Fergus Henderson
The main problem here seems to be that Hat doesn't support the "Data.Word" module. Is there any simple work-around? I'm not particularly interested in tracing that module.
The range of hierarchical libraries supported by Hat is still rather limited at the moment I'm afraid. There is a full list of supported and unsupported modules from -package base in docs/libraries.html. Apart from Data.Word, I notice your command-line also mentions the concurrent, net, and posix packages, none of which are yet supported either. In principle, it shouldn't be too difficult to plug some of these things in. There are two issues: * Translate the library sources with hat-trans. Provided you want to 'trust' the library module, and it deals only in standard datatypes, this is just a question of copying the sources into the hatlib build tree and updating the Makefile. * Dealing with primitive types, e.g. Int8, Word16, Socket, etc. Each primitive type needs a wrapper type and a couple of wrapper functions to be written by hand, to<Type> and from<Type>. You will see examples of these in, for instance, Hat/PreludeBuiltinTypes.hs and Hat/Foreign/BuiltinTypes.hs. All primitive functions that manipulate primitive types then also need to be wrapped by hand. The mechanism is illustrated by this: import qualified TraceOrigChar foreign import haskell "Char.isAscii" isAscii :: Char -> Bool import qualified TraceOrigForeign.ForeignPtr foreign import haskell "Prelude.==" eqForeignPtr :: ForeignPtr a -> ForeignPtr a -> Bool and you can see numerous more examples in PreludeBuiltin.hs, Directory.hs, IO.hs, Foreign/ForeignPtr.hs and so on I'm sure a lot of this boilerplate could be automated, given a fairly simple specification of the complete module signature, and it is on our to-do list for when we manage to persuade a funding agency to support the next stage of research on Hat. But in the meantime, it is just another tedious job to be done by hand. A word of warning about concurrency. We don't yet know in detail what it would mean to trace a concurrent program. There are probably locking issues when writing to the (shared) trace file. There may be graph-connectedness issues for the separate threads. And we have no support for examining faults related to concurrency itself, such as the successive values acquired by an MVar. (But see [1].)
I'm not quite sure why it goes on and invokes /usr/bin/haskell-compiler after the openFile failure. But that's a side issue.
Yes, this is a bug in hmake. Regards, Malcolm [1] Concurrent Haskell Debugger, Frank Huch, http://www.informatik.uni-kiel.de/~fhu/chd/

The main problem here seems to be that Hat doesn't support the "Data.Word" module. Is there any simple work-around? I'm not particularly interested in tracing that module.
I have just checked into CVS a tracing version of Data.Word. It compiles, but I haven't tested it. Currently it provides instances of Eq, Ord, Bounded, Num, Enum, Read, Show but omits instances of Real, Integral, Ix because of tedious errors I haven't tracked down. If you need those instances, I'll look into it further. Regards, Malcolm

On 23-Jun-2004, Malcolm Wallace
The main problem here seems to be that Hat doesn't support the "Data.Word" module. Is there any simple work-around? I'm not particularly interested in tracing that module.
I have just checked into CVS a tracing version of Data.Word.
Thanks!
It compiles, but I haven't tested it. Currently it provides instances of Eq, Ord, Bounded, Num, Enum, Read, Show but omits instances of Real, Integral, Ix because of tedious errors I haven't tracked down. If you need those instances, I'll look into it further.
It turns out that I do need at least the Integral instances. I tried uncommenting those, and got an error about "fromRational" being undeclared. I then tried adding "import Prelude(fromRational)" to src/hatlib/Data/Word.hs, but that didn't work. I ran into the following problem: | bash$ make | cd src/hatlib; make HC=ghc6 all | make[1]: Entering directory `/home/fjh007/hat/cvs/hat/src/hatlib' | /home/fjh007/hat/cvs/hat/script/hat-trans -P. -I. -trusted -prelude -D__GLASGOW_HASKELL__=620 Data/Word.hs | | Fail: AuxLabelAST.letVar: == not let-bound in env The build continued a little longer, | ghc6 -package-name hat -fglasgow-exts -package lang -package base -fno-warn-overlapping-patterns -fno-warn-missing-methods -i/home/fjh007/hat/cvs/hat/targets/ix86-Linux/obj/hatlib/ghc6 -I. -I/home/fjh007/hat/cvs/hat/include '-#include "hat-c.h"' -c -o /home/fjh007/hat/cvs/hat/targets/ix86-Linux/obj/hatlib/ghc6/Hat/Data/Word.o Hat/Data/Word.hs | | Hat/Data/Word.hs:1: | The main function `main' is not defined in module `Main' | make[1]: *** [/home/fjh007/hat/cvs/hat/targets/ix86-Linux/obj/hatlib/ghc6/Hat/Data/Word.o] Error 1 but I think the first error message is the one that is really causing the problem. Cheers, Fergus. -- Fergus J. Henderson | "I have always known that the pursuit Galois Connections, Inc. | of excellence is a lethal habit" Phone: +1 503 626 6616 | -- the last words of T. S. Garp.

Fergus Henderson
I tried uncommenting those, and got an error about "fromRational" being undeclared. I then tried adding "import Prelude(fromRational)" to src/hatlib/Data/Word.hs, but that didn't work. I ran into the following problem:
Actually, the 'fromRational' that is needed is not the Prelude function of the same name. The following wrapper: foreign import haskell "Prelude.toRational" toRatWord8 :: Word8 -> Rational is the culprit. hat-trans interprets Rational to be a primitive type, and expects primitively-defined tracing operations that lift a real Rational into a traced Rational and drop it again. (cf. the similar operations toWord8 and fromWord8 defined in Hat.Data.WordBuiltin) Unfortunately, these lifting and dropping operations are automatically given the names 'fromRational' and 'toRational' respectively, which not only clash with the Prelude names, but have completely different types.
| /home/fjh007/hat/cvs/hat/script/hat-trans -P. -I. -trusted -prelude | -D__GLASGOW_HASKELL__=620 Data/Word.hs | | Fail: AuxLabelAST.letVar: == not let-bound in env
Oops. That's rather nasty.
The build continued a little longer,
But should not have done. For some reason, hat-trans is exiting with a successful status even in the presence of an error. Regards, Malcolm

I wrote:
The following wrapper: foreign import haskell "Prelude.toRational" toRatWord8 :: Word8 -> Rational is the culprit.
I've now found a reasonable workaround and checked it into CVS. Happily, there is no need to attempt to construct a traced Rational primitively - we can do it in plain Haskell code instead: instance Real Word8 where { toRational x = toInteger x % 1 } Regards, Malcolm

On 29-Jun-2004, Malcolm Wallace
I wrote:
The following wrapper: foreign import haskell "Prelude.toRational" toRatWord8 :: Word8 -> Rational is the culprit.
I've now found a reasonable workaround and checked it into CVS.
Thanks! Now I get quite a way further before running into the next bug. This one can be reproduced with a simple one-liner, "(>>) = 42": bash$ cat Foo.hs (>>) = 42 bash$ hmake -hat Foo hat-trans Foo.hs Wrote Hat/Foo.hs /usr/bin/haskell-compiler -c -package hat -o Hat/Foo.o Hat/Foo.hs Hat/Foo.hs:10: Ambiguous occurrence `|>>' It could refer to either `Hat.PreludeBasic.|>>', imported from Hat.Prelude at Hat/Foo.hs:8 or `Main.|>>', defined at Hat/Foo.hs:12 While cutting this test case down, I also noticed another problem: bash$ cat Foo.hs import Prelude hiding (Prelude.head) fjh$ hmake -hat Foo hat-trans Foo.hs Fail: Variable or constructor not in scope: Prelude.head However, that one has an easy work-around (don't qualify the name in the hiding list). -- Fergus J. Henderson | "I have always known that the pursuit Galois Connections, Inc. | of excellence is a lethal habit" Phone: +1 503 626 6616 | -- the last words of T. S. Garp.

Fergus Henderson
This one can be reproduced with a simple one-liner, "(>>) = 42":
bash$ cat Foo.hs (>>) = 42
Hmm, but isn't (>>) indeed defined in the Prelude? So what is the expectation here? Is it something to do with lazy reporting of name clashes?
bash$ cat Foo.hs import Prelude hiding (Prelude.head)
fjh$ hmake -hat Foo hat-trans Foo.hs
Fail: Variable or constructor not in scope: Prelude.head
Probably easy to fix. I'll look into it tomorrow. Regards, Malcolm

On 29-Jun-2004, Malcolm Wallace
Fergus Henderson
writes: This one can be reproduced with a simple one-liner, "(>>) = 42":
bash$ cat Foo.hs (>>) = 42
Hmm, but isn't (>>) indeed defined in the Prelude?
Yes.
So what is the expectation here?
This example should be allowed. hat-trans should generate a type-correct translated Haskell program from it.
Is it something to do with lazy reporting of name clashes?
Yes. The name ">>" is defined in the Prelude, but this occurrence of ">>" in Foo.hs is a definition, so it unambiguously refers to Main.>>, not Prelude.>>. The Haskell 98 report gives a similar example in section 5.5.2 "Name clashes", using "sin" rather than ">>": | For example, the following module is legal: | | module F where | | sin :: Float -> Float | sin x = (x::Float) | | f x = Prelude.sin (F.sin x) | | The local declaration for sin is legal, even though the Prelude function sin is implicitly in scope. | The references to Prelude.sin and F.sin must both be qualified to make | it unambiguous which sin is meant. However, the unqualified name sin in | the type signature in the first line of F unambiguously refers to the | local declaration for sin. -- Fergus J. Henderson | "I have always known that the pursuit Galois Connections, Inc. | of excellence is a lethal habit" Phone: +1 503 626 6616 | -- the last words of T. S. Garp.

Fergus Henderson
(>>) = 42
The name ">>" is defined in the Prelude, but this occurrence of ">>" in Foo.hs is a definition, so it unambiguously refers to Main.>>, not Prelude.>>.
Yes, OK, accepted. The problem here is that the Hat transformation introduces three replacement definitions for the original function: a worker, a wrapper, and an atom. The worker is used on the RHS of the wrapper definition, and the atom is used on the RHS of the worker definition. These RHS usages should be qualified for disambiguation. Thus, hat-trans ought to check whether a top-level variable is already in scope at its point of definition, and if so, qualify those newly introduced uses. Unfortunately, it looks like a considerable amount of internal plumbing will need to be added to hat-trans to enable this check. In the meantime, a plausible workaround would be: import Prelude hiding ((>>)) import qualified Prelude (>>) = 42 but at the moment, this does not work either, because the transformed version only hides the imported wrapper function (!>>) but not the worker (|>>) or atom (+>>). I have attached a possible fix, but with it, the Hat prelude can no longer be transformed correctly, so you should not try to rebuild that. Olaf might like to comment on or refine the patch. Regards, Malcolm

Malcolm Wallace wrote:
I have attached a possible fix, but with it, the Hat prelude can no longer be transformed correctly, so you should not try to rebuild that. Olaf might like to comment on or refine the patch.
Gosh, the module system is really complicated; never thought of that. I believe it would be better if the AuxInfo pass, which knows about what is imported, would rename (>>) into its fully qualified form. Then the subsequent pass would work fine (?) However, I'm just about to leave for holidays. So don't expect anything from me before 26 July. Ciao, Olaf -- OLAF CHITIL, Computing Laboratory, University of Kent, Canterbury, Kent CT2 7NF, UK. URL: http://www.cs.kent.ac.uk/people/staff/oc/ Tel: +44 (0)1227 824320; Fax: +44 (0)1227 762811

I wrote:
I have attached a possible fix, but with it, the Hat prelude can no longer be transformed correctly, so you should not try to rebuild that.
Actually, the non-rebuildability of the Hat prelude turned out to be another bug, only made visible by the fix I suggested. Here is a patch to the Prelude which corrects that secondary fault. Since the combination of the two patches now seems to work, I'm committing them to CVS. Regards, Malcolm

On 30-Jun-2004, Malcolm Wallace
The problem here is that the Hat transformation introduces three replacement definitions for the original function: a worker, a wrapper, and an atom. The worker is used on the RHS of the wrapper definition, and the atom is used on the RHS of the worker definition. These RHS usages should be qualified for disambiguation. Thus, hat-trans ought to check whether a top-level variable is already in scope at its point of definition, and if so, qualify those newly introduced uses.
Another possible alternative would be _always_ qualify the newly introduced uses, regardless of whether the variable is already in scope or not. Perhaps that would require less new plumbing? Cheers, Fergus. -- Fergus J. Henderson | "I have always known that the pursuit Galois Connections, Inc. | of excellence is a lethal habit" Phone: +1 503 626 6616 | -- the last words of T. S. Garp.

On Mon, Jun 21, 2004 at 05:48:09PM -0700, Fergus Henderson wrote:
I am trying to get Hat working on a reasonably large and complicated project. Unfortunately it doesn't work. I have cut down the code which triggers the problem to the following simple test case:
| bash$ cat Foo/List.hs | module Foo.List where | | class List a b where | foo :: a -> b | | main :: IO () | main = return () | | bash$ hmake -hat Foo/List | hat-trans Foo/List.hs | Creating directories Hat Hat/Foo | Wrote Hat/Foo/List.hs | /usr/bin/haskell-compiler -c -package hat -o Hat/Foo/List.o Hat/Foo/List.hs | | Hat/Foo/List.hs:1: | Ambiguous occurrence `List' | It could refer to either `Hat.Hat.List', imported from Hat.Prelude at Hat/Foo/List.hs:30 | or `Hat.Foo.List.List', defined at Hat/Foo/List.hs:32
I am using hat-2.02.8 with ghc 6.2 on Debian Linux.
Hi Fergus, As a temporary fix, that _might_ get you past this bug, you can modify the file Hat/Foo/List.hs to say: import Hat.Prelude hiding (List) instead of import Hat.Prelude on about line 30. There might be cases where this fails to fix the problem though. Cheers, Bernie.
participants (4)
-
Bernard James POPE
-
Fergus Henderson
-
Malcolm Wallace
-
Olaf Chitil