GHC does not like modules starting with Z?

1999-05-06 Thread Mark Utting


I am a long-time Hugs user, but am relatively new to ghc.
I've been trying to get a Makefile working, with little success.
After much investigation, the problem seems to be not with my Makefile, 
but that ghc does not like modules whose names start with 'Z'.  

Seems that a module called Zabc (in file Zabc.lhs) generates a 
Zabc.hi file whose first line is:

__interface ZZabc 1 402 where
^^ Note the repeated Z.
   This repetition does not seem to happen for other module names!

Is this a bug?  


Detailed Example:  Given the following two files
--- Zabc.lhs -
> module Zabc(a)
> where

> a :: Int
> a = 3
--


--- Main.hs --
module Main where

import qualified Zabc

main :: IO ()
main
  = do putStrLn ("set1: " ++ show Zabc.a)
   putStrLn "Done."
--

with no pre-existing *.hi *.o or *.hc files around,
the following command (using ghc version 4.02, patchlevel 0) gives
this output:

$  ghc -o test Zabc.lhs Main.hs
ghc: module version changed to 1; reason: no old .hi file

Main.hs:3: Could not find valid interface file `Zabc'

   [But there is a file called Zabc.hi there]

Compilation had errors
$


Mark.

Dr Mark Utting, Senior Lecturer
Department of Computer Science
School of Computing and Mathematical Sciences
The University of Waikato   Tel:   +64 7 838 4791
Private Bag 3105Fax:   +64 7 838 4155
HamiltonEmail: [EMAIL PROTECTED]
New Zealand Web:   http://www.cs.waikato.ac.nz/~marku

The highest bandwidth output from a human is the notes pouring
from a concert pianist's fingers.



GHC dies with no error message

1999-05-06 Thread Keith Wansbrough

Probably not repeatable, but in case someone recognises it:

In the latest GHC 4.03 from CVS, compiling using ghc-4.02, and with 
GhcLibHcOpts=-DDEBUG -fno-prune-tydecls -O -fno-specialise, when it 
gets to lib/exts/Word.lhs it dies with no error message:



==fptools== make all --no-print-directory -r;
 in /local/scratch/kw217/Builds/i386-unknown-linux/fptools-4.xx-cvs-w402
/ghc/lib/exts

../../../ghc/driver/ghc -recomp -cpp -fglasgow-exts -fvia-C 
-Rghc-timing -DDEBUG -fno-prune-tydecls -O -fno-specialise -static  
-H12m -monly-3-regs  -c Word.lhs -o Word.o -osuf o
make[3]: *** [Word.o] Error 1
make[2]: *** [all] Error 1
make[1]: *** [all] Error 1
make: *** [all] Error 1
Make all failed; aborting...


When I change into the appropriate directory and apply the above 
command with a -v added on the end to find out where it's dying, it 
works fine.  A classic case of `it doesn't crash when I'm in the 
debugger' (s/debugger/verbose mode/ of course).

Ideas?

Thanks.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) :
: PhD Student, Computer Laboratory, University of Cambridge, England. :
:  (and recently of the University of Glasgow, Scotland. [><] )   :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S.:
: http://www.cl.cam.ac.uk/users/kw217/  mailto:[EMAIL PROTECTED] :
:-: