[GHC] #14901: dsrun004 fails with most ways

#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

#14901: dsrun004 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by alpmestan): This test was apparently added for #1031. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14901#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14901: dsrun004 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by alpmestan): If I change one or more `seq`s into `pseq`, in order for this test to be a little more useful (because `pseq` might prevent some transformations that could make things go wrong with `seq`, so we can hope that the trace is reliably `one` then `two`), ghc isn't happy: {{{#!hs ... import GHC.Conc ... {-# NOINLINE f #-} f :: a -> b -> (# a,b #) f x y = x `pseq` y `pseq` (# x,y #) -- similar with x `pseq` y `seq` (# x,y #) }}} {{{ dsrun014.hs:10:9: error: • Couldn't match a lifted type with an unlifted type When matching types b0 :: * (# a, b #) :: TYPE ('GHC.Types.TupleRep '['GHC.Types.LiftedRep, 'GHC.Types.LiftedRep]) • In the expression: x `pseq` y `pseq` (# x, y #) In an equation for ‘f’: f x y = x `pseq` y `pseq` (# x, y #) • Relevant bindings include y :: b (bound at dsrun014.hs:10:5) x :: a (bound at dsrun014.hs:10:3) f :: a -> b -> (# a, b #) (bound at dsrun014.hs:10:1) dsrun014.hs:10:27: error: • Couldn't match a lifted type with an unlifted type When matching types b0 :: * (# a, b #) :: TYPE ('GHC.Types.TupleRep '['GHC.Types.LiftedRep, 'GHC.Types.LiftedRep]) • In the second argument of ‘pseq’, namely ‘(# x, y #)’ In the second argument of ‘pseq’, namely ‘y `pseq` (# x, y #)’ In the expression: x `pseq` y `pseq` (# x, y #) • Relevant bindings include y :: b (bound at dsrun014.hs:10:5) x :: a (bound at dsrun014.hs:10:3) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14901#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14901: dsrun014 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: dsrun014 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * testcase: dsrun004 => dsrun014 Old description:
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?
New description: The `dsrun014` 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#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14901: dsrun014 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: dsrun014 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): alpmestan, this is a consequence of the fact that `seq` has special typing rules. See `Note [Typing rule for seq]` in http://git.haskell.org/ghc.git/blob/efc844f5b955385d69d8e20b80d38311083a6665... how this is implemented (and why it's special). `pseq` does not have corresponding special typing rules, which is why it fails when given an unlifted argument. Should `pseq` be given similar magic? I'm not sure. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14901#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14901: dsrun014 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: dsrun014 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): I tried to extend that code to do the same thing for `pseq` but it looks like that did not quite work (see [https://gist.github.com/alpmestan/2ed121470f5ed3b4e27b79a22111ab27 this gist]). I'm probably missing something obvious here though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14901#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14901: dsrun014 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: dsrun014 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): Oh, well I can't just expect GHC to magically use that "id" can I... I'll look at how the mapping is done for seq and then do the same thing for `pseq`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14901#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC