[GHC] #14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2

#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2 --------------------------------------+--------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- Steps to reproduce: {{{ git clone https://gitlab.imn.htwk-leipzig.de/waldmann/pure-matchbox git checkout a2005d246cb7bd77a33bf4c09419534bc7ecd435 stack build .stack-work/install/x86_64-linux/nightly-2017-09-26/8.2.1/bin/pure- matchbox -i -w Count data/z001.srs }}} Output: {{{ pure-matchbox: Oops! Entered absent arg ww Map k (Set k1) }}} Error goes away when compiling with -O0, or when removing this pragma in src/Matchbox/Pairs.hs {{{ 52 {-# INLINEABLE pre_images #-} 53 pre_images x rel = images x $ mirrorRel rel }}} (normal output starts with YES on a single line) Error also goes away when building with 8.0.2 {{{ PATH=/where/you/have/installed/ghc-8.0.2/bin:$PATH stack build --resolver=lts-9.6 }}} I tried to isolate a shorter test case but gave up after some hours. Is there some automation for this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14285 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2 ---------------------------------+-------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by mpickering): Does `-dcore-lint` report an error? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14285#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2 ---------------------------------+-------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by j.waldmann): No. - After a clean checkout, I did {{{ stack build --dependencies-only stack exec -- ghc -isrc -fforce-recomp -O1 -dcore-lint pure-matchbox.hs ./pure-matchbox -i -w Count data/z001.srs pure-matchbox: Oops! Entered absent arg ww Map k (Set k1) }}} If I leave out the "-O1", or if I put "-O0", the error does not happen. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14285#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2 ---------------------------------+-------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by bgamari): This may or may not be the same root cause as #11126. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14285#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2 ---------------------------------+-------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by RyanGlScott): By sheer dumb luck, I managed to reduce this down to the following two files: {{{#!hs module Foo where import qualified Data.Foldable as F import qualified Data.IntMap as IM import qualified Data.IntSet as IS import Prelude hiding (null) import System.Environment data Set k = Set IS.IntSet null (Set a) = IS.null a empty = Set IS.empty sfromList :: (Enum a, Foldable c) => c a -> Set a sfromList xs = Set $ IS.fromList $ Prelude.map fromEnum $ F.toList xs newtype Map k v = Map { unMap :: (IM.IntMap v) } deriving (Eq, Ord) {-# inlineable fromList #-} fromList :: Enum k => [(k,v)] -> Map k v fromList kvs = Map $ IM.fromList $ Prelude.map (\(k,v) -> (fromEnum k, v)) kvs {-# inlineable findWithDefault #-} findWithDefault d k (Map m) = IM.findWithDefault d (fromEnum k) m data Rel a b = Rel !(Map a (Set b)) !(Map b (Set a)) {-# INLINEABLE images #-} images x (Rel f b) = findWithDefault empty x f {-# INLINEABLE pre_images #-} pre_images x rel = images x $ mirrorRel rel {-# INLINEABLE mirrorRel #-} mirrorRel :: Rel a b -> Rel b a mirrorRel (Rel f g) = Rel g f }}} {{{#!hs module Main where import Foo import Prelude hiding (null) main :: IO () main = do let args = "hw" print $ null $ pre_images 'a' (Rel (fromList [('a',sfromList args)]) (fromList [('b',sfromList ar gs)])) }}} This works on GHC 8.0.2: {{{ $ /opt/ghc/8.0.2/bin/ghc -O2 -fforce-recomp Main.hs [1 of 2] Compiling Foo ( Foo.hs, Foo.o ) [2 of 2] Compiling Main ( Main.hs, Main.o ) Linking Main ... $ ./Main True }}} But not on GHC 8.2.1: {{{ $ /opt/ghc/8.0.2/bin/ghc -O2 -fforce-recomp Main.hs [1 of 2] Compiling Foo ( Foo.hs, Foo.o ) [2 of 2] Compiling Main ( Main.hs, Main.o ) Linking Main ... $ ./Main True }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14285#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2 ---------------------------------+-------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by RyanGlScott): * cc: simonpj (added) Comment: I managed to bisect this down to 2effe18ab51d66474724d38b20e49cc1b8738f60 (`The Early Inline Patch`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14285#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2
---------------------------------+--------------------------------------
Reporter: j.waldmann | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64 (amd64)
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
---------------------------------+--------------------------------------
Comment (by simonpj):
I know what is going on. It's extremely annoying. In module `Foo` we get
this after demand analysis:
{{{
pre_images [InlPrag=INLINABLE] :: forall a k k. Enum a => a -> Rel k k ->
Set k
[Str=
, <----------- NB
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 0 20] 120 0
Tmpl= \ (@ a_a52c) (@ k_a52e) (@ k_a52d)
($dEnum_a52n [Occ=Once] :: Enum a_a52c)
(x_a2k0 [Occ=Once] :: a_a52c)
(rel_a2k1 [Occ=Once!] :: Rel k_a52e k_a52d) ->
case rel_a2k1 of { Rel f_a2k2 [Occ=Once] g_a2k3
[Occ=Once] ->
NB -------> case T14285a.$WRel @ k_a52d @ k_a52e g_a2k3 f_a2k2 of
{ Rel f_a2jY [Occ=Once] _ [Occ=Dead] ->
IM.findWithDefault
@ (Set k_a52e)
(empty @ k_a52e)
(fromEnum @ a_a52c $dEnum_a52n x_a2k0)
(f_a2jY
`cast` (T14285a.N:Map[0] ]
:: Enum a_a52c)
(x_a2k0 :: a_a52c)
(rel_a2k1 [Dmd=] :: Rel k_a52e k_a52d) ->
case rel_a2k1 of { Rel f_a2k2 [Dmd=] ->
case fromEnum @ a_a52c $dEnum_a52n x_a2k0 of
{ GHC.Types.I# ww1_a57r [Dmd=] ->
Data.IntMap.Internal.$wfindWithDefault
@ (Set k_a52e)
(empty @ k_a52e)
ww1_a57r
(g_a2k3
`cast` (T14285a.N:Map[0] `, and so is strict, but its
first component is unused.
* And indeed `f_a2k2` is unsed in the body of `pre_images`
* But alas, in the stable-unfolding, `f_a2k2` '''is''' used. It is passed
to `$WRel`, the wrapper for the strict data contructor `Rel`; it evaluates
both arguments.
* So if we w/w this function, we won't pass the first component; instead
we'll make up `absentError "blah"` to fill the hole, expecting it not to
be used.
* Alas, when we do the same thing to the stable unfolding (see `Note
[Worker-wrapper for INLINABLE functions]` in `WorkWrap.hs`) we ''do''
evaluate that `absentError` call. Sigh.
I'm not at all clear what to do about this, but at least we can see what
is going on. It's very much a corner case, so I don't want to harm
mainstream cases for the sake of this one.
--
Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14285#comment:6
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2
---------------------------------+--------------------------------------
Reporter: j.waldmann | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64 (amd64)
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
---------------------------------+--------------------------------------
Comment (by Simon Peyton Jones

#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2 -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | stranal/should_run/T14285 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => stranal/should_run/T14285 * milestone: => 8.2.2 Comment: I can't say I'm proud of this fix, but it certainly fixes it. Which is important. Could merge to future 8.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14285#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2 -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | stranal/should_run/T14285 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.2` in 35f85046d7f639b8aa741069f19add754b546fdc. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14285#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC