The typo in the following module causes ghc to crash:

--------------------------------------------------------------
module Foo where

data Bar = Bar { flag :: Bool }

data State = State { bar :: Bar, baz :: Float }

display :: State -> IO ()
display (State{ bar = Bar { flag = f, baz = b }}) = print (f,b)

-- Typo! The line above should better be:
-- display (State{ bar = Bar { flag = f }, baz = b }) = print (f,b)
--------------------------------------------------------------

   panne@jeanluc:~ > ghc -Wall -O -c Foo.hs

   panic! (the `impossible' happened):
           tcLookupValue: b{-r4n-}

   Please report it as a compiler bug to [EMAIL PROTECTED]

Done!   :o)

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.pms.informatik.uni-muenchen.de/mitarbeiter/panne

Reply via email to