#5626: Miscompilation, exception omitted with -O
---------------------------------+------------------------------------------
Reporter: michal.palka | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.3 | Keywords: strictness strict exception
miscompilation
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Incorrect result at runtime
---------------------------------+------------------------------------------
Following program is miscompiled when compiled with `-O`.
{{{
module Main where
wrap x = [x]!!0
f :: [Int] -> a
f a = foldr (\b -> \c -> c) (undefined ()) (a ++ a) 0
main = do
print $ (f [] :: String)
print $ wrap $ (f [] :: Int)
print $ wrap $ (f [] :: (Int, Int, Int, Int))
}}}
The result of running it on my machine (Linux x86-64) is following:
{{{
"
1099511628032
zsh: segmentation fault ./test7
}}}
Looking at the Core it seems that instead of the expected `undefined` a
partially-applied function is returned. GHC 7.3.20111022 was used for
testing.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5626>
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