#2916: Adding "-auto-all" when using "-O2 -prof" causes "<<loop>>"
--------------------------+-------------------------------------------------
Reporter:  BenMoseley     |          Owner:           
    Type:  bug            |         Status:  new      
Priority:  normal         |      Component:  Profiling
 Version:  6.10.1         |       Severity:  normal   
Keywords:  loop auto-all  |       Testcase:           
      Os:  Windows        |   Architecture:  x86      
--------------------------+-------------------------------------------------
 The program below works fine (and outputs "ZeroPmt") when compiled with
 "-O2 -prof -fno-cse", but when you add in "-auto-all" it causes
 "<<loop>>".

 There are many ways to workaround the problem, uncommenting pretty much
 any of the commented-out lines avoids the issue, but my impression is that
 adding "-auto-all" shouldn't cause this.

 This is with stock 6.10.1.  "-dcore-lint" has no effect.

 {{{
 --
 -- Compile with : ghc -O2 -prof -auto-all -fno-cse --make ~/loop.hs
 --
 -- ...and it breaks, outputting <<loop>>
 -- ...compile without "-auto-all" and you get ZeroPmt
 --
 import Data.IORef
 import qualified Data.Map as Map
 import System.IO
 import System.IO.Unsafe
 import System.Mem.StableName

 main :: IO ()
 main = do

  -- putStrLn $ show $ unHC $ mkHC ZeroPmt -- Works OK
  putStrLn $ show $ unHC $ mkHC $ unHC $ mkHC ZeroPmt

 data Expr = Add | ZeroPmt deriving (Ord, Eq, Show)
 data ExprHC = ExprHC { unStableName :: !(StableName Expr), unHC ::
 !Expr} deriving (Eq)

 -- {-# NOINLINE mkHC #-} -- Works OK
 -- mkHC e = hashConser e -- Works OK
 mkHC = hashConser

 {-# NOINLINE hashConser #-}
 hashConser :: Expr -> ExprHC
 hashConser e = deepSeq e (unsafePerformIO $ mkHC' e)
 -- hashConser e = seq (e == e) (unsafePerformIO $ mkHC' e)
  where
    refTbl = unsafePerformIO $ newIORef Map.empty

    mkHC' e = do
      tbl <- readIORef refTbl
      case Map.lookup e tbl of
        Just ehc -> return ehc
        Nothing -> do
                      sn <- makeStableName e
                      let ehc = ExprHC sn e
                      writeIORef refTbl $ Map.insert e ehc tbl
                      return ehc

 deepSeq :: Eq e => e -> x -> x
 deepSeq e x = seq (e == e) x
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2916>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to