[commit: ghc] master: Comments only (related to #12789) (3aa9368)

git at git.haskell.org git at git.haskell.org
Mon Nov 28 17:44:06 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/3aa936893cac8d7c3b242c882731e9a38a4ae425/ghc

>---------------------------------------------------------------

commit 3aa936893cac8d7c3b242c882731e9a38a4ae425
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Nov 28 17:41:27 2016 +0000

    Comments only (related to #12789)
    
    It took me some time to find the right Note for the
    fix to #12789.  This comment patch tries to add pointers
    from relevant places.


>---------------------------------------------------------------

3aa936893cac8d7c3b242c882731e9a38a4ae425
 compiler/coreSyn/CoreSyn.hs     |  4 +--
 compiler/iface/MkIface.hs       | 72 -----------------------------------------
 compiler/iface/ToIface.hs       | 71 ++++++++++++++++++++++++++++++++++++++++
 compiler/simplCore/OccurAnal.hs |  3 ++
 4 files changed, 76 insertions(+), 74 deletions(-)

diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs
index 6a70f2c..01a864b 100644
--- a/compiler/coreSyn/CoreSyn.hs
+++ b/compiler/coreSyn/CoreSyn.hs
@@ -980,8 +980,8 @@ data Unfolding
 
   | BootUnfolding      -- ^ We have no information about the unfolding, because
                        -- this 'Id' came from an @hi-boot@ file.
-                       -- See Note [Inlining and hs-boot files] for what
-                       -- this is used for.
+                       -- See Note [Inlining and hs-boot files] in ToIface
+                       -- for what this is used for.
 
   | OtherCon [AltCon]  -- ^ It ain't one of these constructors.
                        -- @OtherCon xs@ also indicates that something has been evaluated
diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs
index 9e6fa62..4d45efd 100644
--- a/compiler/iface/MkIface.hs
+++ b/compiler/iface/MkIface.hs
@@ -1769,75 +1769,3 @@ bogusIfaceRule id_name
         ifRuleBndrs = [], ifRuleHead = id_name, ifRuleArgs = [],
         ifRuleRhs = IfaceExt id_name, ifRuleOrph = IsOrphan,
         ifRuleAuto = True }
-
----------------------
-{-
-Note [Inlining and hs-boot files]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Consider this example (Trac #10083):
-
-    ---------- RSR.hs-boot ------------
-    module RSR where
-      data RSR
-      eqRSR :: RSR -> RSR -> Bool
-
-    ---------- SR.hs ------------
-    module SR where
-      import {-# SOURCE #-} RSR
-      data SR = MkSR RSR
-      eqSR (MkSR r1) (MkSR r2) = eqRSR r1 r2
-
-    ---------- RSR.hs ------------
-    module RSR where
-      import SR
-      data RSR = MkRSR SR -- deriving( Eq )
-      eqRSR (MkRSR s1) (MkRSR s2) = (eqSR s1 s2)
-      foo x y = not (eqRSR x y)
-
-When compiling RSR we get this code
-
-    RSR.eqRSR :: RSR -> RSR -> Bool
-    RSR.eqRSR = \ (ds1 :: RSR.RSR) (ds2 :: RSR.RSR) ->
-                case ds1 of _ { RSR.MkRSR s1 ->
-                case ds2 of _ { RSR.MkRSR s2 ->
-                SR.eqSR s1 s2 }}
-
-    RSR.foo :: RSR -> RSR -> Bool
-    RSR.foo = \ (x :: RSR) (y :: RSR) -> not (RSR.eqRSR x y)
-
-Now, when optimising foo:
-    Inline eqRSR (small, non-rec)
-    Inline eqSR  (small, non-rec)
-but the result of inlining eqSR from SR is another call to eqRSR, so
-everything repeats.  Neither eqSR nor eqRSR are (apparently) loop
-breakers.
-
-Solution: in the unfolding of eqSR in SR.hi, replace `eqRSR` in SR
-with `noinline eqRSR`, so that eqRSR doesn't get inlined.  This means
-that when GHC inlines `eqSR`, it will not also inline `eqRSR`, exactly
-as would have been the case if `foo` had been defined in SR.hs (and
-marked as a loop-breaker).
-
-But how do we arrange for this to happen?  There are two ingredients:
-
-    1. When we serialize out unfoldings to IfaceExprs (toIfaceVar),
-    for every variable reference we see if we are referring to an
-    'Id' that came from an hs-boot file.  If so, we add a `noinline`
-    to the reference.
-
-    2. But how do we know if a reference came from an hs-boot file
-    or not?  We could record this directly in the 'IdInfo', but
-    actually we deduce this by looking at the unfolding: 'Id's
-    that come from boot files are given a special unfolding
-    (upon typechecking) 'BootUnfolding' which say that there is
-    no unfolding, and the reason is because the 'Id' came from
-    a boot file.
-
-Here is a solution that doesn't work: when compiling RSR,
-add a NOINLINE pragma to every function exported by the boot-file
-for RSR (if it exists).  Doing so makes the bootstrapped GHC itself
-slower by 8% overall (on Trac #9872a-d, and T1969: the reason
-is that these NOINLINE'd functions now can't be profitably inlined
-outside of the hs-boot loop.
-
--}
diff --git a/compiler/iface/ToIface.hs b/compiler/iface/ToIface.hs
index 8de3e3e..8e80bb3 100644
--- a/compiler/iface/ToIface.hs
+++ b/compiler/iface/ToIface.hs
@@ -497,3 +497,74 @@ toIfaceVar v
     | isExternalName name                        = IfaceExt name
     | otherwise                                  = IfaceLcl (getOccFS name)
   where name = idName v
+
+
+{- Note [Inlining and hs-boot files]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Consider this example (Trac #10083, #12789):
+
+    ---------- RSR.hs-boot ------------
+    module RSR where
+      data RSR
+      eqRSR :: RSR -> RSR -> Bool
+
+    ---------- SR.hs ------------
+    module SR where
+      import {-# SOURCE #-} RSR
+      data SR = MkSR RSR
+      eqSR (MkSR r1) (MkSR r2) = eqRSR r1 r2
+
+    ---------- RSR.hs ------------
+    module RSR where
+      import SR
+      data RSR = MkRSR SR -- deriving( Eq )
+      eqRSR (MkRSR s1) (MkRSR s2) = (eqSR s1 s2)
+      foo x y = not (eqRSR x y)
+
+When compiling RSR we get this code
+
+    RSR.eqRSR :: RSR -> RSR -> Bool
+    RSR.eqRSR = \ (ds1 :: RSR.RSR) (ds2 :: RSR.RSR) ->
+                case ds1 of _ { RSR.MkRSR s1 ->
+                case ds2 of _ { RSR.MkRSR s2 ->
+                SR.eqSR s1 s2 }}
+
+    RSR.foo :: RSR -> RSR -> Bool
+    RSR.foo = \ (x :: RSR) (y :: RSR) -> not (RSR.eqRSR x y)
+
+Now, when optimising foo:
+    Inline eqRSR (small, non-rec)
+    Inline eqSR  (small, non-rec)
+but the result of inlining eqSR from SR is another call to eqRSR, so
+everything repeats.  Neither eqSR nor eqRSR are (apparently) loop
+breakers.
+
+Solution: in the unfolding of eqSR in SR.hi, replace `eqRSR` in SR
+with `noinline eqRSR`, so that eqRSR doesn't get inlined.  This means
+that when GHC inlines `eqSR`, it will not also inline `eqRSR`, exactly
+as would have been the case if `foo` had been defined in SR.hs (and
+marked as a loop-breaker).
+
+But how do we arrange for this to happen?  There are two ingredients:
+
+    1. When we serialize out unfoldings to IfaceExprs (toIfaceVar),
+    for every variable reference we see if we are referring to an
+    'Id' that came from an hs-boot file.  If so, we add a `noinline`
+    to the reference.
+
+    2. But how do we know if a reference came from an hs-boot file
+    or not?  We could record this directly in the 'IdInfo', but
+    actually we deduce this by looking at the unfolding: 'Id's
+    that come from boot files are given a special unfolding
+    (upon typechecking) 'BootUnfolding' which say that there is
+    no unfolding, and the reason is because the 'Id' came from
+    a boot file.
+
+Here is a solution that doesn't work: when compiling RSR,
+add a NOINLINE pragma to every function exported by the boot-file
+for RSR (if it exists).  Doing so makes the bootstrapped GHC itself
+slower by 8% overall (on Trac #9872a-d, and T1969: the reason
+is that these NOINLINE'd functions now can't be profitably inlined
+outside of the hs-boot loop.
+
+-}
diff --git a/compiler/simplCore/OccurAnal.hs b/compiler/simplCore/OccurAnal.hs
index 7e62eee..6950e56 100644
--- a/compiler/simplCore/OccurAnal.hs
+++ b/compiler/simplCore/OccurAnal.hs
@@ -276,6 +276,9 @@ Loop breaking is surprisingly subtle.  First read the section 4 of
 We avoid infinite inlinings by choosing loop breakers, and
 ensuring that a loop breaker cuts each loop.
 
+See also Note [Inlining and hs-boot files] in ToIface, which deals
+with a closely related source of infinite loops.
+
 Fundamentally, we do SCC analysis on a graph.  For each recursive
 group we choose a loop breaker, delete all edges to that node,
 re-analyse the SCC, and iterate.



More information about the ghc-commits mailing list