[GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <<loop>>)
GHC
ghc-devs at haskell.org
Wed Jul 1 02:02:08 UTC 2015
#10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into
<<loop>>)
-------------------------------------+-------------------------------------
Reporter: exio4 | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by michaelt):
And a bit more compressed, for what it may be worth:
{{{#!hs
{-# LANGUAGE MagicHash, UnboxedTuples #-}
import GHC.Exts
newtype Eval a = Eval {runEval :: State# RealWorld -> (# State# RealWorld,
a #)}
-- inline sequence :: [Eval a] -> Eval [a]
well_sequenced :: [Eval a] -> Eval [a]
well_sequenced = foldr op (Eval $ \s -> (# s, [] #)) where
op e es = Eval $ \s -> case runEval e s of
(# s', a #) -> case runEval es s' of
(# s'', as #) -> (# s'', a : as #)
-- seemingly demonic use of spark#
ill_sequenced :: [Eval a] -> Eval [a]
ill_sequenced as = Eval $ spark# (case well_sequenced as of
Eval f -> case f realWorld# of (# _, a' #) -> a')
main :: IO ()
main = print ((layer . layer . layer . layer . layer) show 'y')
where
layer :: (Char -> String) -> (Char -> String)
layer f = (\(Eval x) -> case x realWorld# of (# _, as #) -> concat as)
. well_sequenced
. map ill_sequenced
. map (map (\x -> Eval $ \s -> (# s, x #)))
. chunk'
. concatMap f
. show
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10414#comment:15>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list