#7555: SpecConstr pass hangs
------------------------------+---------------------------------------------
Reporter: daniel.is.fischer | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.6.1 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Blockedby:
Blocking: | Related:
------------------------------+---------------------------------------------
From [http://stackoverflow.com/questions/14187413/small-code-snippet-
causes-ghc-to-not-terminate Stack Overflow]:
The code
{{{
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -O2 #-}
import qualified Data.Vector.Unboxed.Mutable as MV
import Data.Vector.Unboxed ((!))
import qualified Data.Vector.Unboxed as V
import Control.Monad (forM_)
similar :: V.Vector Char -> Int
similar v = l + sum (map (similar' 1 1) checks)
where
(l,checks) = let h = V.head v in V.foldl'
(\(i,is) c -> if c == h then (i+1,i:is) else (i+1,is)) (1,[])
(V.tail v)
similar' !r !n !i = if i < l-1 && v!(n) == v!(i+1) then similar' (r+1)
(n+1) (i+1)
else r
main :: IO ()
main = do
n <- getLine
v <- MV.replicate (read n) 0
forM_ [1..read n] $ \n' -> do
v' <- getLine
MV.unsafeWrite v (n'-1) (similar . V.fromList $ v')
V.unsafeFreeze v >>= V.mapM_ print
}}}
causes GHC to hang in the !SpecConstr pass.
Versions 7.0.* compiled it just fine, 7.2.* to 7.6.1 hang.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7555>
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