[commit: ghc] master: Add flag -fno-it (41afbb3)

git at git.haskell.org git at git.haskell.org
Mon Jan 15 19:22:20 UTC 2018


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

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

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

commit 41afbb3f20f3d84abacb37afcc5aa64b24c22da8
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date:   Mon Jan 15 13:51:38 2018 -0500

    Add flag -fno-it
    
    This flag stops ghci creating the special variable `it`
    after evaluating an expression. This stops ghci leaking
    as much memory when evaluating expressions. See #14336
    
    Reviewers: bgamari
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, thomie, carter
    
    GHC Trac Issues: #14336
    
    Differential Revision: https://phabricator.haskell.org/D4299


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

41afbb3f20f3d84abacb37afcc5aa64b24c22da8
 compiler/main/DynFlags.hs        |  2 ++
 compiler/typecheck/TcRnDriver.hs | 68 +++++++++++++++++++++++++++++++++-------
 docs/users_guide/ghci.rst        | 14 +++++++++
 3 files changed, 73 insertions(+), 11 deletions(-)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 0c8222f..ef4e2f8 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -522,6 +522,7 @@ data GeneralFlag
    | Opt_GhciSandbox
    | Opt_GhciHistory
    | Opt_LocalGhciHistory
+   | Opt_NoIt
    | Opt_HelpfulErrors
    | Opt_DeferTypeErrors
    | Opt_DeferTypedHoles
@@ -3824,6 +3825,7 @@ fFlagsDeps = [
   flagSpec "gen-manifest"                     Opt_GenManifest,
   flagSpec "ghci-history"                     Opt_GhciHistory,
   flagGhciSpec "local-ghci-history"           Opt_LocalGhciHistory,
+  flagGhciSpec "no-it"                        Opt_NoIt,
   flagSpec "ghci-sandbox"                     Opt_GhciSandbox,
   flagSpec "helpful-errors"                   Opt_HelpfulErrors,
   flagSpec "hpc"                              Opt_Hpc,
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 9fbe053..85535e1 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -2010,17 +2010,23 @@ tcUserStmt (L loc (BodyStmt expr _ _ _))
                                            (mkRnSyntaxExpr thenIOName)
                                                   noSyntaxExpr placeHolderType
 
-        -- The plans are:
-        --   A. [it <- e; print it]     but not if it::()
-        --   B. [it <- e]
-        --   C. [let it = e; print it]
-        --
-        -- Ensure that type errors don't get deferred when type checking the
-        -- naked expression. Deferring type errors here is unhelpful because the
-        -- expression gets evaluated right away anyway. It also would potentially
-        -- emit two redundant type-error warnings, one from each plan.
-        ; plan <- unsetGOptM Opt_DeferTypeErrors $
-                  unsetGOptM Opt_DeferTypedHoles $ runPlans [
+              -- NewA
+              no_it_a = L loc $ BodyStmt (nlHsApps bindIOName
+                                       [rn_expr , nlHsVar interPrintName])
+                                       (mkRnSyntaxExpr thenIOName)
+                                       noSyntaxExpr placeHolderType
+
+              no_it_b = L loc $ BodyStmt (rn_expr)
+                                       (mkRnSyntaxExpr thenIOName)
+                                       noSyntaxExpr placeHolderType
+
+              no_it_c = L loc $ BodyStmt (nlHsApp (nlHsVar interPrintName) rn_expr)
+                                       (mkRnSyntaxExpr thenIOName)
+                                       noSyntaxExpr placeHolderType
+
+              -- See Note [GHCi Plans]
+
+              it_plans = [
                     -- Plan A
                     do { stuff@([it_id], _) <- tcGhciStmts [bind_stmt, print_it]
                        ; it_ty <- zonkTcType (idType it_id)
@@ -2039,6 +2045,25 @@ tcUserStmt (L loc (BodyStmt expr _ _ _))
                                 --- checkNoErrs defeats the error recovery of let-bindings
                        ; tcGhciStmts [let_stmt, print_it] } ]
 
+              -- Plans where we don't bind "it"
+              no_it_plans = [
+                    tcGhciStmts [no_it_a] ,
+                    tcGhciStmts [no_it_b] ,
+                    tcGhciStmts [no_it_c] ]
+
+
+        -- Ensure that type errors don't get deferred when type checking the
+        -- naked expression. Deferring type errors here is unhelpful because the
+        -- expression gets evaluated right away anyway. It also would potentially
+        -- emit two redundant type-error warnings, one from each plan.
+        ; generate_it <- goptM Opt_NoIt
+        ; plan <- unsetGOptM Opt_DeferTypeErrors $
+                  unsetGOptM Opt_DeferTypedHoles $
+                    runPlans $ if generate_it
+                                 then no_it_plans
+                                 else it_plans
+
+
         ; fix_env <- getFixityEnv
         ; return (plan, fix_env) }
 
@@ -2080,6 +2105,27 @@ tcUserStmt rdr_stmt@(L loc _)
                                     (mkRnSyntaxExpr thenIOName) noSyntaxExpr
                                     placeHolderType
 
+{-
+Note [GHCi Plans]
+
+When a user types an expression in the repl we try to print it in three different
+ways. Also, depending on whether -fno-it is set, we bind a variable called `it`
+which can be used to refer to the result of the expression subsequently in the repl.
+
+The normal plans are :
+  A. [it <- e; print e]     but not if it::()
+  B. [it <- e]
+  C. [let it = e; print it]
+
+When -fno-it is set, the plans are:
+  A. [e >>= print]
+  B. [e]
+  C. [let it = e in print it]
+
+The reason for -fno-it is explained in #14336. `it` can lead to the repl
+leaking memory as it is repeatedly queried.
+-}
+
 -- | Typecheck the statements given and then return the results of the
 -- statement in the form 'IO [()]'.
 tcGhciStmts :: [GhciLStmt GhcRn] -> TcM PlanResult
diff --git a/docs/users_guide/ghci.rst b/docs/users_guide/ghci.rst
index eae98f7..f5dcfe3 100644
--- a/docs/users_guide/ghci.rst
+++ b/docs/users_guide/ghci.rst
@@ -1027,6 +1027,20 @@ The corresponding translation for an IO-typed ``e`` is
 Note that ``it`` is shadowed by the new value each time you evaluate a
 new expression, and the old value of ``it`` is lost.
 
+In order to stop the value ``it`` being bound on each command, the flag
+:ghc-flag:`-fno-it` can be set. The ``it`` variable can be the source
+of space leaks due to how shadowed declarations are handled by
+GHCi (see :ref:`ghci-decls`).
+
+.. ghc-flag:: -fno-it
+    :shortdesc: No longer set the special variable ``it``.
+    :type: dynamic
+    :reverse: -fno-no-it
+    :category:
+
+    When this flag is set, the variable ``it`` will no longer be set
+    to the result of the previously evaluated expression.
+
 .. _extended-default-rules:
 
 Type defaulting in GHCi



More information about the ghc-commits mailing list