Dear GHC developers,

I think I have found an optimisation problem in GHC
pre-4.07-20000613. I ran across that problem when compiling nhc98
(version 1.0pre19) without and then with -O. 

The follwoing program is a cut down version of a code excerpt from
nhc98 (taken from nhc98-1.0pre19/src/compiler98/EmitState.hs).

I tried this on
 - i386/Linux (Debian 2.2) with GHC 4.06 and pre-4.07-20000613, gcc 2.95.2 
 - sparc/Solaris with GHC 4.06, gcc 2.7.2.3
The results were the same in all three configurations.


module Main where

data Label = Define String | Use String  deriving Show

testfun :: [Label] -> String
testfun labs =
  let isUse (Use _) = True
      isUse  _ = False
      isDefine (Define _) = True
      isDefine  _ = False
      defines = filter isDefine labs
      uses    = filter isUse labs
      externs = filter (\use-> notElemBy useAfterDef use defines) uses
      notElemBy :: (a->b->Bool) -> a -> [b] -> Bool
      notElemBy ok x = all (not . ok x)
      useAfterDef (Use sym) (Define sym') = (sym==sym')
      useAfterDef u d = error ("useAfterDef (" ++ show u ++ ") (" ++
                               show d ++ ")\n")
  in
       concat (map show externs)

lablist1 = [Define "a"]

lablist2 = [Use "a",
            Define "b",
            Define "a"]

lablist3 = [Use "b",
            Define "c",
            Define "a",
            Use "c",
            Define "b",
            Use "a"]

main :: IO ()
main = print (testfun lablist1)



The function `useAfterDef' is always called (due to the filters) as
"useAfterDef (Use _) (Define _)", so the `error ...' clause should
never be reached, right?

When I compile without -O, the program runs correctly, but with -O (or
-O2), the `... = error ...' clause is reached:


$ ghc -o main Main.hs && ./main
""

$ ghc -O -o main Main.hs && ./main

Fail: useAfterDef (Define "a") (Define "a")



With `lablist2' instead of `lablist1' the result is

Fail: useAfterDef (Define "b") (Define "b")

and with `lablist3' the program produces

Fail: useAfterDef (Define "c") (Define "c")



When I try to show the value of `uses' in the call to error, i.e.
... = error (show uses)
the problem disappers and the program runs correctly with -O.


Armin



Reply via email to