The new GHC lexer contains some small bugs:
-- Foo.hs ------------------------------------------------------------
module Foo where
forall :: Int
forall = 1
-- Main.hs -----------------------------------------------------------
import Foo
main :: IO ()
main = print forall
----------------------------------------------------------------------
panne@liesl:~ > ghc -Wall -c Foo.hs
ghc: module version changed to 1; reason: no old .hi file
panne@liesl:~ > ghc -Wall -c Main.hs
ParseIface.hs:6496: Non-exhaustive patterns in case
----------------------------------------------------------------------
Similar games can be played with the identifiers foreign, export,
label, dynamic, unsafe, ...
And a small quiz: What's wrong with the following program? :-)
(no EOL after the 1)
-- Main.hs -----------------------------------------------------------
main = print 1
----------------------------------------------------------------------
panne@liesl:~ > ghc -c Main.hs
Main.hs:1:
Couldn't match `IO t' against `a -> IO ()'
Expected type: IO t
Inferred type: a -> IO ()
When checking that `main' has the required type
Compilation had errors
----------------------------------------------------------------------
Small hint:
-- Main.hs -----------------------------------------------------------
main = print True
----------------------------------------------------------------------
panne@liesl:~ > ghc -c Main.hs
Main.hs:1: Data constructor not in scope: `Tru'
Compilation had errors
----------------------------------------------------------------------
Cheers,
Sven
--
Sven Panne Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr. 67
mailto:[EMAIL PROTECTED] D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne