summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/GHC/Core/Lint.hs60
-rw-r--r--libraries/base/GHC/Enum.hs58
-rw-r--r--libraries/base/GHC/Real.hs20
3 files changed, 122 insertions, 16 deletions
diff --git a/compiler/GHC/Core/Lint.hs b/compiler/GHC/Core/Lint.hs
index 8ee39cbe88..037940eac2 100644
--- a/compiler/GHC/Core/Lint.hs
+++ b/compiler/GHC/Core/Lint.hs
@@ -767,7 +767,65 @@ It's very suspicious if a strong loop breaker is marked INLINE.
However, the desugarer generates instance methods with INLINE pragmas
that form a mutually recursive group. Only after a round of
simplification are they unravelled. So we suppress the test for
-the desugarer.
+the desugarer. Here is an example:
+ instance Eq T where
+ t1 == t2 = blah
+ t1 /= t2 = not (t1 == t2)
+ {-# INLINE (/=) #-}
+
+This will generate something like
+ -- From the class decl for Eq
+ data Eq a = EqDict (a->a->Bool) (a->a->Bool)
+ eq_sel :: Eq a -> (a->a->Bool)
+ eq_sel (EqDict eq _) = eq
+
+ -- From the instance Eq T
+ $ceq :: T -> T -> Bool
+ $ceq = blah
+
+ Rec { $dfEqT :: Eq T {-# DFunId #-}
+ $dfEqT = EqDict $ceq $cnoteq
+
+ $cnoteq :: T -> T -> Bool {-# INLINE #-}
+ $cnoteq x y = not (eq_sel $dfEqT x y) }
+
+Notice that
+
+* `$dfEqT` and `$cnotEq` are mutually recursive.
+
+* We do not want `$dfEqT` to be the loop breaker: it's a DFunId, and
+ we want to let it "cancel" with "eq_sel" (see Note [ClassOp/DFun
+ selection] in GHC.Tc.TyCl.Instance, which it can't do if it's a loop
+ breaker.
+
+So we make `$cnoteq` into the loop breaker. That means it can't
+inline, despite the INLINE pragma. That's what gives rise to the
+warning, which is perfectly appropriate for, say
+ Rec { {-# INLINE f #-} f = \x -> ...f.... }
+We can't inline a recursive function -- it's a loop breaker.
+
+But now we can optimise `eq_sel $dfEqT` to `$ceq`, so we get
+ Rec {
+ $dfEqT :: Eq T {-# DFunId #-}
+ $dfEqT = EqDict $ceq $cnoteq
+
+ $cnoteq :: T -> T -> Bool {-# INLINE #-}
+ $cnoteq x y = not ($ceq x y) }
+
+and now the dependencies of the Rec have gone, and we can split it up to give
+ NonRec { $dfEqT :: Eq T {-# DFunId #-}
+ $dfEqT = EqDict $ceq $cnoteq }
+
+ NonRec { $cnoteq :: T -> T -> Bool {-# INLINE #-}
+ $cnoteq x y = not ($ceq x y) }
+
+Now $cnoteq is not a loop breaker any more, so the INLINE pragma can
+take effect -- the warning turned out to be temporary.
+
+To stop excessive warnings, this warning for INLINE loop breakers is
+switched off when linting the the result of the desugarer. See
+lf_check_inline_loop_breakers in GHC.Core.Lint.
+
Note [Checking for representation polymorphism]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/libraries/base/GHC/Enum.hs b/libraries/base/GHC/Enum.hs
index d80689423c..a050325f17 100644
--- a/libraries/base/GHC/Enum.hs
+++ b/libraries/base/GHC/Enum.hs
@@ -160,14 +160,14 @@ class Enum a where
{-# INLINABLE enumFromThenTo #-}
enumFromThenTo x1 x2 y = map toEnum [fromEnum x1, fromEnum x2 .. fromEnum y]
--- See Note [Stable Unfolding for list producers]
-{-# INLINABLE boundedEnumFrom #-}
+-- See Note [Inline Enum method helpers]
+{-# INLINE boundedEnumFrom #-}
-- Default methods for bounded enumerations
boundedEnumFrom :: (Enum a, Bounded a) => a -> [a]
boundedEnumFrom n = map toEnum [fromEnum n .. fromEnum (maxBound `asTypeOf` n)]
--- See Note [Stable Unfolding for list producers]
-{-# INLINABLE boundedEnumFromThen #-}
+-- See Note [Inline Enum method helpers]
+{-# INLINE boundedEnumFromThen #-}
boundedEnumFromThen :: (Enum a, Bounded a) => a -> a -> [a]
boundedEnumFromThen n1 n2
| i_n2 >= i_n1 = map toEnum [i_n1, i_n2 .. fromEnum (maxBound `asTypeOf` n1)]
@@ -176,11 +176,55 @@ boundedEnumFromThen n1 n2
i_n1 = fromEnum n1
i_n2 = fromEnum n2
-{-
-Note [Stable Unfolding for list producers]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+{- Note [Stable Unfolding for list producers]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The INLINABLE/INLINE pragmas ensure that we export stable (unoptimised)
unfoldings in the interface file so we can do list fusion at usage sites.
+
+Related tickets: #15185, #8763, #18178.
+
+Note [Inline Enum method helpers]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+The overloaded `numericEnumFrom` functions are used to abbreviate Enum
+instances. We call them "method helpers". For example, in GHC.Float:
+
+ numericEnumFromTo :: (Ord a, Fractional a) => a -> a -> [a]
+ mnumericEnumFromTo = ...blah...
+
+ instance Enum Double where
+ ...
+ enumFromTo = numericEnumFromTo
+
+Similarly with the overloaded `boundedEnumFrom` functions. E.g. in GHC.Word
+
+ boundedEnumFrom :: (Enum a, Bounded a) => a -> [a]
+ boundedEnumFrom n = map toEnum [fromEnum n .. fromEnum (maxBound `asTypeOf` n)]
+
+ instance Enum Word8 where
+ ...
+ enumFrom = boundedEnumFrom
+
+In both cases, it is super-important to specialise these overloaded
+helper function (`numericEnumFromTo`, `boundedEnumFrom` etc) to the
+particular type of the instance, else every use of that instance will
+be inefficient.
+
+Moreover (see Note [Stable Unfolding for list producers]) the helper
+function is a list producer, so we want it to have a stable unfolding
+to support fusion.
+
+So we attach an INLINE pragma to them.
+
+Alternatives might be
+* An `INLINABLE` pragma on `numericEnumFromTo`, relying on the
+ specialiser to create a specialised version. But (a) if the
+ instance method is marked INLINE we may get spurious INLINE
+ loop-breaker warnings (#21343), and (b) specialision gains no extra
+ sharing, because there is just one call at each type.
+
+* Using `inline` at the call site
+ enumFromTo = inline numericEnumFromTo
+ But that means remembering to do this in multiple places.
-}
------------------------------------------------------------------------
diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs
index e8cfbfbc57..e6943b0d86 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -275,6 +275,7 @@ class (Real a, Fractional a) => RealFrac a where
-- These 'numeric' enumerations come straight from the Report
numericEnumFrom :: (Fractional a) => a -> [a]
+{-# INLINE numericEnumFrom #-} -- See Note [Inline Enum method helpers] in GHC.Enum
numericEnumFrom n = go 0
where
-- See Note [Numeric Stability of Enumerating Floating Numbers]
@@ -282,6 +283,7 @@ numericEnumFrom n = go 0
in n' : go (k + 1)
numericEnumFromThen :: (Fractional a) => a -> a -> [a]
+{-# INLINE numericEnumFromThen #-} -- See Note [Inline Enum method helpers] in GHC.Enum
numericEnumFromThen n m = go 0
where
step = m - n
@@ -290,9 +292,11 @@ numericEnumFromThen n m = go 0
in n' : go (k + 1)
numericEnumFromTo :: (Ord a, Fractional a) => a -> a -> [a]
+{-# INLINE numericEnumFromTo #-} -- See Note [Inline Enum method helpers] in GHC.Enum
numericEnumFromTo n m = takeWhile (<= m + 1/2) (numericEnumFrom n)
numericEnumFromThenTo :: (Ord a, Fractional a) => a -> a -> a -> [a]
+{-# INLINE numericEnumFromThenTo #-} -- See Note [Inline Enum method helpers] in GHC.Enum
numericEnumFromThenTo e1 e2 e3
= takeWhile predicate (numericEnumFromThen e1 e2)
where
@@ -829,13 +833,13 @@ lcm x y = abs ((x `quot` (gcd x y)) * y)
"gcd/Word->Word->Word" gcd = gcdWord
#-}
--- See Note [Stable Unfolding for list producers] in GHC.Enum
-{-# INLINABLE integralEnumFrom #-}
+-- INLINE pragma: see Note [Inline Enum method helpers] in GHC.Enum
+{-# INLINE integralEnumFrom #-}
integralEnumFrom :: (Integral a, Bounded a) => a -> [a]
integralEnumFrom n = map fromInteger [toInteger n .. toInteger (maxBound `asTypeOf` n)]
--- See Note [Stable Unfolding for list producers] in GHC.Enum
-{-# INLINABLE integralEnumFromThen #-}
+-- INLINE pragma: see Note [Inline Enum method helpers] in GHC.Enum
+{-# INLINE integralEnumFromThen #-}
integralEnumFromThen :: (Integral a, Bounded a) => a -> a -> [a]
integralEnumFromThen n1 n2
| i_n2 >= i_n1 = map fromInteger [i_n1, i_n2 .. toInteger (maxBound `asTypeOf` n1)]
@@ -844,13 +848,13 @@ integralEnumFromThen n1 n2
i_n1 = toInteger n1
i_n2 = toInteger n2
--- See Note [Stable Unfolding for list producers] in GHC.Enum
-{-# INLINABLE integralEnumFromTo #-}
+-- INLINE pragma: see Note [Inline Enum method helpers] in GHC.Enum
+{-# INLINE integralEnumFromTo #-}
integralEnumFromTo :: Integral a => a -> a -> [a]
integralEnumFromTo n m = map fromInteger [toInteger n .. toInteger m]
--- See Note [Stable Unfolding for list producers] in GHC.Enum
-{-# INLINABLE integralEnumFromThenTo #-}
+-- INLINE pragma: see Note [Inline Enum method helpers] in GHC.Enum
+{-# INLINE integralEnumFromThenTo #-}
integralEnumFromThenTo :: Integral a => a -> a -> a -> [a]
integralEnumFromThenTo n1 n2 m
= map fromInteger [toInteger n1, toInteger n2 .. toInteger m]