[GHC] #14901: dsrun004 fails with most ways
GHC
ghc-devs at haskell.org
Thu Mar 8 17:12:31 UTC 2018
#14901: dsrun004 fails with most ways
-------------------------------------+-------------------------------------
Reporter: alpmestan | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.5
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Incorrect result
Unknown/Multiple | at runtime
Test Case: dsrun004 | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The `dsrun004` test doesn't seem to pass for a whole bunch of ways, as a
recent `./validate --slow` (against yesterday's master) revealed.
{{{#!py
# the test options
test('dsrun014', normal, compile_and_run, ['-fobject-code'])
}}}
{{{#!hs
-- the haskell program we build & run
{-# LANGUAGE UnboxedTuples #-}
module Main where
import Debug.Trace
{-# NOINLINE f #-}
f :: a -> b -> (# a,b #)
f x y = x `seq` y `seq` (# x,y #)
g :: Int -> Int -> Int
g v w = case f v w of
(# a,b #) -> a+b
main = print (g (trace "one" 1) (trace "two" 2))
-- The args should be evaluated in the right order!
}}}
{{{
# the failing ways
/tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run
dsrun014 [bad stderr] (hpc)
/tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run
dsrun014 [bad stderr] (optasm)
/tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run
dsrun014 [bad stderr] (threaded2)
/tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run
dsrun014 [bad stderr] (dyn)
/tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run
dsrun014 [bad stderr] (optllvm)
}}}
With those 5 ways, the program's trace is `two` then `one` while with some
other ways (like ghci or normal) we get (as expected by the testsuite)
`one` first and `two` afterwards.
I'm not sure whether the expectation is too strong or whether there's
something fishy going on with those 5 ways.
Simon, could you perhaps comment on this? Is this a "proper" bug?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14901>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list