GHC-4.02 and yesterday's GHC-4.03 don't like the following (rather
senseless) module:

-- Foo.hs -----------------------------------------
module Foo where

import IOExts(unsafePerformIO)

bar :: [Int] -> IO (Bool,[Int])
bar tns = do
   baz_ <- barAux 8
   let baz = baz_ == false
   res <- if baz then return tns else return []
   return (baz, res)

false :: Char
false = unsafePerformIO (_casm_ ``%r = 0;'')

barAux :: Int -> IO Char
barAux _ = _casm_ ``%r = (char)%0;'' (0::Int)
---------------------------------------------------

panne@fangatau:~ > ghc -fglasgow-exts -O -c Foo.hs
NOTE: Simplifier still going after 4 iterations; bailing out.

panic! (the `impossible' happened):
        lookupBindC:no info!
 for: wild{-c1T0-}
                      (probably: data dependencies broken by an optimisation pass)
                      static binds for:
                      Foo.false{-r3,x-}
                      Foo.barAux{-r5,x-}
                      Foo.lvl{-s1Sg,l-}
                      local binds for:
                      tns{-c1T2-}
                      wild1{-c1T4-}
                      ds2{-s1RS-}
                      ds1{-s1RT-}
                      b1{-s1RX-}

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

As usual, this is part of a bigger program and the -O is important for
the reproduction of this panic.

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