[commit: ghc] master: Comments about static forms (a4717f5)

git at git.haskell.org git at git.haskell.org
Tue May 10 13:22:02 UTC 2016


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

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

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

commit a4717f51433d16e948d102477564e257cdece475
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri May 6 09:49:46 2016 +0100

    Comments about static forms


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

a4717f51433d16e948d102477564e257cdece475
 compiler/coreSyn/CoreLint.hs    | 28 ++++++++++++++-----
 compiler/main/StaticPtrTable.hs |  2 ++
 compiler/main/TidyPgm.hs        |  7 +++--
 compiler/simplCore/SimplCore.hs | 62 +++++++++++++++++++++++++----------------
 4 files changed, 66 insertions(+), 33 deletions(-)

diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs
index b3cec5f..2a2284b 100644
--- a/compiler/coreSyn/CoreLint.hs
+++ b/compiler/coreSyn/CoreLint.hs
@@ -1636,18 +1636,32 @@ top-level ones. See Note [Exported LocalIds] and Trac #9857.
 
 Note [Checking StaticPtrs]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~
+See SimplCore Note [Grand plan for static forms] for an overview.
 
-Every occurrence of the data constructor @StaticPtr@ should be moved to the top
-level by the FloatOut pass. The linter is checking that no occurrence is left
-nested within an expression.
+Every occurrence of the data constructor @StaticPtr@ should be moved
+to the top level by the FloatOut pass.  It's vital that we don't have
+nested StaticPtr uses after CorePrep, because we populate the Static
+Pointer Table from the top-level bindings. See SimplCore Note [Grand
+plan for static forms].
 
-The check is enabled only if the module uses the StaticPointers language
-extension. This optimization arose from the need to compile "GHC.StaticPtr",
-which otherwise would be rejected because the following binding
+The linter checks that no occurrence is left behind, nested within an
+expression. The check is enabled only:
+
+* After the FloatOut, CorePrep, and CoreTidy passes.
+  We could check more often, but the condition doesn't hold until
+  after the first FloatOut pass.
+
+* When the module uses the StaticPointers language extension. This is
+  a little hack.  This optimization arose from the need to compile
+  GHC.StaticPtr, which otherwise would be rejected because of the
+  following binding for the StaticPtr data constructor itself:
 
     StaticPtr = \a b1 b2 b3 b4 -> StaticPtr a b1 b2 b3 b4
 
-contains an application of `StaticPtr` nested within the lambda abstractions.
+  which contains an application of `StaticPtr` nested within the
+  lambda abstractions.  This binding is injected by CorePrep.
+
+  Note that GHC.StaticPtr is itself compiled without -XStaticPointers.
 
 Note [Type substitution]
 ~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/main/StaticPtrTable.hs b/compiler/main/StaticPtrTable.hs
index c13bcd8..9ec970f 100644
--- a/compiler/main/StaticPtrTable.hs
+++ b/compiler/main/StaticPtrTable.hs
@@ -48,6 +48,8 @@
 {-# LANGUAGE ViewPatterns #-}
 module StaticPtrTable (sptModuleInitCode) where
 
+-- See SimplCore Note [Grand plan for static forms]
+
 import CLabel
 import CoreSyn
 import DataCon
diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs
index 945e3f8..401f939 100644
--- a/compiler/main/TidyPgm.hs
+++ b/compiler/main/TidyPgm.hs
@@ -375,7 +375,10 @@ tidyProgram hsc_env  (ModGuts { mg_module    = mod
               -- See Note [Injecting implicit bindings]
               ; all_tidy_binds = implicit_binds ++ tidy_binds
 
-              -- get the TyCons to generate code for.  Careful!  We must use
+              -- See SimplCore Note [Grand plan for static forms]
+              ; spt_init_code = sptModuleInitCode mod all_tidy_binds
+
+              -- Get the TyCons to generate code for.  Careful!  We must use
               -- the untidied TypeEnv here, because we need
               --  (a) implicit TyCons arising from types and classes defined
               --      in this module
@@ -409,7 +412,7 @@ tidyProgram hsc_env  (ModGuts { mg_module    = mod
                            cg_tycons   = alg_tycons,
                            cg_binds    = all_tidy_binds,
                            cg_foreign  = foreign_stubs `appendStubC`
-                                           sptModuleInitCode mod all_tidy_binds,
+                                         spt_init_code,
                            cg_dep_pkgs = map fst $ dep_pkgs deps,
                            cg_hpc_info = hpc_info,
                            cg_modBreaks = modBreaks },
diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs
index 654fd52..86eadc7 100644
--- a/compiler/simplCore/SimplCore.hs
+++ b/compiler/simplCore/SimplCore.hs
@@ -990,27 +990,41 @@ transferIdInfo exported_id local_id
         -- rules as we transfer them from one function to another
 
 
--- Note [Grand plan for static forms]
--- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
---
--- Static forms go through the compilation phases as follows:
---
--- The renamer looks for out-of-scope names in the body of the static form.
--- If all names are in scope, the free variables of the body are stored in AST
--- at the location of the static form.
---
--- The typechecker verifies that all free variables occurring in the static form
--- are closed (see Note [Bindings with closed types] in TcRnTypes).
---
--- The desugarer replaces the static form with an application of the data
--- constructor 'StaticPtr' (defined in module GHC.StaticPtr of base).
---
--- The simplifier runs the FloatOut pass which moves the applications of
--- 'StaticPtr' to the top level. Thus the FloatOut pass is always executed,
--- event when optimizations are disabled.
---
--- The CoreTidy pass produces a C function which inserts all the floated
--- 'StaticPtr' in the static pointer table (See StaticPtrTable.hs).
--- This pass also exports the Ids of floated 'StaticPtr's so they can be linked
--- with the C function.
---
+{- Note [Grand plan for static forms]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Static forms go through the compilation phases as follows.
+Here is a running example:
+
+   f x = let k = map toUpper
+         in ...(static k)...
+
+* The renamer looks for out-of-scope names in the body of the static
+  form, as always If all names are in scope, the free variables of the
+  body are stored in AST at the location of the static form.
+
+* The typechecker verifies that all free variables occurring in the
+  static form are closed (see Note [Bindings with closed types] in
+  TcRnTypes).  In our example, 'k' is closed, even though it is bound
+  in a nested let, we are fine.
+
+* The desugarer replaces the static form with an application of the
+  data constructor 'StaticPtr' (defined in module GHC.StaticPtr of
+  base).  So we get
+
+   f x = let k = map toUpper
+         in ...(StaticPtr <fingerprint> k)...
+
+* The simplifier runs the FloatOut pass which moves the applications
+  of 'StaticPtr' to the top level. Thus the FloatOut pass is always
+  executed, even when optimizations are disabled.  So we get
+
+   k = map toUpper
+   lvl = StaticPtr <fingerprint> k
+   f x = ...lvl...
+
+* The CoreTidy pass produces a C function which inserts all the
+  floated 'StaticPtr' in the static pointer table (see the call to
+  StaticPtrTable.sptModuleInitCode in TidyPgm). CoreTidy pass also
+  exports the Ids of floated 'StaticPtr's so they can be linked with
+  the C function.
+-}



More information about the ghc-commits mailing list