[GHC] #9418: Warnings about "INLINE binder is (non-rule) loop breaker"

#9418: Warnings about "INLINE binder is (non-rule) loop breaker" -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Gabor rightly complains: I see literally ''thousands'' of these warnings (in yesterday's and) today's bootstraps: {{{ HC [stage 1] libraries/base/dist-install/build/GHC/Base.o *** Core Lint warnings : in result of Desugar (after optimization) *** {-# LINE 261 "libraries/base/GHC/Base.lhs #-}: Warning: [RHS of $c>>_arr :: forall r_agf a_adQ b_adR. (r_agf -> a_adQ) -> (r_agf -> b_adR) -> r_agf -> b_adR] INLINE binder is (non-rule) loop breaker: $c>>_arr {-# LINE 632 "libraries/base/GHC/Base.lhs #-}: Warning: [RHS of $c>>_apH :: forall a_adQ b_adR. GHC.Types.IO a_adQ -> GHC.Types.IO b_adR -> GHC.Types.IO b_adR] INLINE binder is (non-rule) loop breaker: $c>>_apH }}} }}} This is clearly unsatisfactory, because it is unsettling, and perhaps conceals more important warnings. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9418 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9418: Warnings about "INLINE binder is (non-rule) loop breaker" -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): What is happening is this. Consider {{{ class C a where op1 :: a -> a -> (a,a) op2 :: a -> a -> (a,a) {-# INLINE op2 #-} op2 x y = op1 y x instance C Int where op1 x y = (x,y) }}} The intent of the INLINE pragma is obviously to ensure that in every instance declaration we get an INLINEd definition for op2. These declarations desugar to something like this: {{{ op1 :: forall a. C a => a -> a -> (a,a,) op1 c = case c of MkC op1 op2 -> op1 Rec { $dCInt :: C Int = MkC $cop1 $cop2 $cop1 :: Int->Int->(Int,Int) = \xy. (x,y) $cop2 :: Int->Int->(Int,Int) {-# INLINE #-} = \xy -> op1 $dCInt y x } }}} Here * `op1` is the method selector, which picks the `op1` field out of a `C` dictionary. * `$dCInt` is the dictionary for `C Int`. * `$cop1` and `$cop2` are the implementations of `op1` and `op2` at type `Int`. Notice that `$dCInt` and `$cop2` are apparently mutually recursive; each uses the other. We break the mutual recursion by inlining the `op1` selector and `$dCInt` (in the rhs of `$cop2`) so that now we can do the record selection. But do to this, we must inline `$dCInt`, so it can't be a loop breaker. So `$cop2` must be picked as the loop breaker, ''even though it has an INLINE pragma''. That's fine, and it's what GHC does. But Lint is just warning that, as a result, the INLINE pragma isn't going to do anything. This might be useful to the programmer. If you wrote {{{ f x = ....(f y).... {-# INLINE f #-} }}} then `f` won't be inlnined (despite the pragma) because it's recursive. So you might want to re-think your definitions. The Lint warning is just that: a warning. The unravelling of the mutual recursion happens early, otherwise the warning would be repeated after in every subsequent run of the simplifier. So one possible fix would be to have a flag for Core Lint to control whether the warning was enabled, and only switch it on later in the pipeline. But that doesn't seem very satisfactory. Well then. That's why it is the way it is. I'd like it to be better! Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9418#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9418: Warnings about "INLINE binder is (non-rule) loop breaker" -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: I don't see those warnings in the build logs, and also the example from comment:1 compiles without warnings. I guess this is fixed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9418#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9418: Warnings about "INLINE binder is (non-rule) loop breaker" -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #12137 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * failure: None/Unknown => Incorrect warning at compile-time * resolution: fixed => * related: => #12137 Comment: I closed this prematurely. The example from comment:1 requires `-dcore- lint`. Also reported as #12137. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9418#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9418: Warnings about "INLINE binder is (non-rule) loop breaker" -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #12137, #3073 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * related: #12137 => #12137, #3073 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9418#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9418: Warnings about "INLINE binder is (non-rule) loop breaker" -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #12137, #3073 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: => Inlining -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9418#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9418: Warnings about "INLINE binder is (non-rule) loop breaker" -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #12137, #3073 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): See [https://mail.haskell.org/pipermail/ghc-devs/2017-March/013993.html this thread], where Mikolaj wants the inline-loop-breaker warning to happen when not in a debug build. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9418#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC