[GHC] #9418: Warnings about "INLINE binder is (non-rule) loop breaker"
GHC
ghc-devs at haskell.org
Thu Aug 7 08:53:39 UTC 2014
#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
More information about the ghc-tickets
mailing list