summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJoachim Breitner <mail@joachim-breitner.de>2021-12-12 15:47:29 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-12-14 20:52:00 -0500
commita5d8d47f2a95de4b66c7299c25c301b89e6252f6 (patch)
treec218f03c01469ceb38978b2609f2217036d4432c
parent1c8d609a0509d99722ccc0056dbf3336904bf102 (diff)
downloadhaskell-a5d8d47f2a95de4b66c7299c25c301b89e6252f6.tar.gz
Ghci environment: Do not remove shadowed ids
Names defined earier but shadowed need to be kept around, e.g. for type signatures: ``` ghci> data T = T ghci> let t = T ghci> data T = T ghci> :t t t :: Ghci1.T ``` and indeed they can be used: ``` ghci> let t2 = Ghci1.T :: Ghci1.T ghci> :t t2 t2 :: Ghci1.T ``` However, previously this did not happen for ids (non-types), although they are still around under the qualified name internally: ``` ghci> let t = "other t" ghci> t' <interactive>:8:1: error: • Variable not in scope: t' • Perhaps you meant one of these: ‘Ghci2.t’ (imported from Ghci2), ‘t’ (line 7), ‘t2’ (line 5) ghci> Ghci2.t <interactive>:9:1: error: • GHC internal error: ‘Ghci2.t’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [] • In the expression: Ghci2.t In an equation for ‘it’: it = Ghci2.t ``` This fixes the problem by simply removing the code that tries to remove shadowed ids from the environment. Now you can refer to shadowed ids using `Ghci2.t`, just like you can do for data and type constructors. This simplifies the code, makes terms and types more similar, and also fixes #20455. Now all names ever defined in GHCi are in `ic_tythings`, which is printed by `:show bindings`. But for that commands, it seems to be more ergonomic to only list those bindings that are not shadowed. Or, even if it is not more ergonomic, it’s the current behavour. So let's restore that by filtering in `icInScopeTTs`. Of course a single `TyThing` can be associated with many names. We keep it it in the bindings if _any_ of its names are still visible unqualifiedly. It's a judgement call. This commit also turns a rather old comment into a test files. The comment is is rather stale and things are better explained elsewhere. Fixes #925. Two test cases are regressing: T14052(ghci) ghc/alloc 2749444288.0 12192109912.0 +343.4% BAD T14052Type(ghci) ghc/alloc 7365784616.0 10767078344.0 +46.2% BAD This is not unexpected; the `ic_tythings list grows` a lot more if we don’t remove shadowed Ids. I tried to alleviate it a bit with earlier MRs, but couldn’t make up for it completely. Metric Increase: T14052 T14052Type
-rw-r--r--compiler/GHC/Runtime/Context.hs49
-rw-r--r--compiler/GHC/Tc/Module.hs19
-rw-r--r--docs/users_guide/ghci.rst40
-rw-r--r--testsuite/tests/ghci/scripts/T11547.stderr5
-rw-r--r--testsuite/tests/ghci/scripts/T11547.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/T20455.script17
-rw-r--r--testsuite/tests/ghci/scripts/T20455.stderr10
-rw-r--r--testsuite/tests/ghci/scripts/T20455.stdout5
-rw-r--r--testsuite/tests/ghci/scripts/T925.script7
-rw-r--r--testsuite/tests/ghci/scripts/T925.stdout2
-rwxr-xr-xtestsuite/tests/ghci/scripts/all.T3
-rw-r--r--testsuite/tests/ghci/scripts/shadow-bindings.script48
-rw-r--r--testsuite/tests/ghci/scripts/shadow-bindings.stdout41
13 files changed, 199 insertions, 48 deletions
diff --git a/compiler/GHC/Runtime/Context.hs b/compiler/GHC/Runtime/Context.hs
index 4b042aacca..a1df5fd029 100644
--- a/compiler/GHC/Runtime/Context.hs
+++ b/compiler/GHC/Runtime/Context.hs
@@ -32,7 +32,6 @@ import GHC.Core.Type
import GHC.Types.Avail
import GHC.Types.Fixity.Env
-import GHC.Types.Id ( isRecordSelector )
import GHC.Types.Id.Info ( IdDetails(..) )
import GHC.Types.Name
import GHC.Types.Name.Env
@@ -68,7 +67,7 @@ This scheme deals well with shadowing. For example:
Here we must display info about constructor A, but its type T has been
shadowed by the second declaration. But it has a respectable
qualified name (Ghci1.T), and its source location says where it was
-defined.
+defined, and it can also be used with the qualified name.
So the main invariant continues to hold, that in any session an
original name M.T only refers to one unique thing. (In a previous
@@ -242,7 +241,9 @@ data InteractiveContext
ic_tythings :: [TyThing],
-- ^ TyThings defined by the user, in reverse order of
- -- definition (ie most recent at the front)
+ -- definition (ie most recent at the front).
+ -- Also used in GHC.Tc.Module.runTcInteractive to fill the type
+ -- checker environment.
-- See Note [ic_tythings]
ic_gre_cache :: IcGlobalRdrEnv,
@@ -331,20 +332,32 @@ icInteractiveModule (InteractiveContext { ic_mod_index = index })
= mkInteractiveModule index
-- | This function returns the list of visible TyThings (useful for
--- e.g. showBindings)
+-- e.g. showBindings).
+--
+-- It picks only those TyThings that are not shadowed by later definitions on the interpreter,
+-- to not clutter :showBindings with shadowed ids, which would show up as Ghci9.foo.
+--
+-- Some TyThings define many names; we include them if _any_ name is still
+-- available unqualified.
icInScopeTTs :: InteractiveContext -> [TyThing]
-icInScopeTTs = ic_tythings
+icInScopeTTs ictxt = filter in_scope_unqualified (ic_tythings ictxt)
+ where
+ in_scope_unqualified thing = or
+ [ unQualOK gre
+ | avail <- tyThingAvailInfo thing
+ , name <- availNames avail
+ , Just gre <- [lookupGRE_Name (icReaderEnv ictxt) name]
+ ]
+
-- | Get the PrintUnqualified function based on the flags and this InteractiveContext
icPrintUnqual :: UnitEnv -> InteractiveContext -> PrintUnqualified
icPrintUnqual unit_env ictxt = mkPrintUnqualified unit_env (icReaderEnv ictxt)
-- | extendInteractiveContext is called with new TyThings recently defined to update the
--- InteractiveContext to include them. Ids are easily removed when shadowed,
--- but Classes and TyCons are not. Some work could be done to determine
--- whether they are entirely shadowed, but as you could still have references
--- to them (e.g. instances for classes or values of the type for TyCons), it's
--- not clear whether removing them is even the appropriate behavior.
+-- InteractiveContext to include them. By putting new things first, unqualified
+-- use will pick the most recently defined thing with a given name, while
+-- still keeping the old names in scope in their qualified form (Ghci1.foo).
extendInteractiveContext :: InteractiveContext
-> [TyThing]
-> [ClsInst] -> [FamInst]
@@ -355,7 +368,7 @@ extendInteractiveContext ictxt new_tythings new_cls_insts new_fam_insts defaults
= ictxt { ic_mod_index = ic_mod_index ictxt + 1
-- Always bump this; even instances should create
-- a new mod_index (#9426)
- , ic_tythings = new_tythings ++ old_tythings
+ , ic_tythings = new_tythings ++ ic_tythings ictxt
, ic_gre_cache = ic_gre_cache ictxt `icExtendIcGblRdrEnv` new_tythings
, ic_instances = ( new_cls_insts ++ old_cls_insts
, new_fam_insts ++ fam_insts )
@@ -365,9 +378,6 @@ extendInteractiveContext ictxt new_tythings new_cls_insts new_fam_insts defaults
, ic_fix_env = fix_env -- See Note [Fixity declarations in GHCi]
}
where
- new_ids = [id | AnId id <- new_tythings]
- old_tythings = filterOut (shadowed_by new_ids) (ic_tythings ictxt)
-
-- Discard old instances that have been fully overridden
-- See Note [Override identical instances in GHCi]
(cls_insts, fam_insts) = ic_instances ictxt
@@ -379,20 +389,11 @@ extendInteractiveContextWithIds ictxt new_ids
| null new_ids = ictxt
| otherwise
= ictxt { ic_mod_index = ic_mod_index ictxt + 1
- , ic_tythings = new_tythings ++ old_tythings
+ , ic_tythings = new_tythings ++ ic_tythings ictxt
, ic_gre_cache = ic_gre_cache ictxt `icExtendIcGblRdrEnv` new_tythings
}
where
new_tythings = map AnId new_ids
- old_tythings = filterOut (shadowed_by new_ids) (ic_tythings ictxt)
-
-shadowed_by :: [Id] -> TyThing -> Bool
-shadowed_by ids = shadowed
- where
- -- Keep record selectors because they might be needed by HasField (#19322)
- shadowed (AnId id) | isRecordSelector id = False
- shadowed tything = getOccName tything `elemOccSet` new_occs
- new_occs = mkOccSet (map getOccName ids)
setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
setInteractivePrintName ic n = ic{ic_int_print = n}
diff --git a/compiler/GHC/Tc/Module.hs b/compiler/GHC/Tc/Module.hs
index 6dfcf5d357..06270c1848 100644
--- a/compiler/GHC/Tc/Module.hs
+++ b/compiler/GHC/Tc/Module.hs
@@ -2171,25 +2171,6 @@ tcRnStmt hsc_env rdr_stmt
global_ids <- mapM (externaliseAndTidyId this_mod) zonked_ids ;
-- Note [Interactively-bound Ids in GHCi] in GHC.Driver.Env
-{- ---------------------------------------------
- At one stage I removed any shadowed bindings from the type_env;
- they are inaccessible but might, I suppose, cause a space leak if we leave them there.
- However, with Template Haskell they aren't necessarily inaccessible. Consider this
- GHCi session
- Prelude> let f n = n * 2 :: Int
- Prelude> fName <- runQ [| f |]
- Prelude> $(return $ AppE fName (LitE (IntegerL 7)))
- 14
- Prelude> let f n = n * 3 :: Int
- Prelude> $(return $ AppE fName (LitE (IntegerL 7)))
- In the last line we use 'fName', which resolves to the *first* 'f'
- in scope. If we delete it from the type env, GHCi crashes because
- it doesn't expect that.
-
- Hence this code is commented out
-
--------------------------------------------------- -}
-
traceOptTcRn Opt_D_dump_tc
(vcat [text "Bound Ids" <+> pprWithCommas ppr global_ids,
text "Typechecked expr" <+> ppr zonked_expr]) ;
diff --git a/docs/users_guide/ghci.rst b/docs/users_guide/ghci.rst
index 72fba318bf..07377dab77 100644
--- a/docs/users_guide/ghci.rst
+++ b/docs/users_guide/ghci.rst
@@ -910,6 +910,46 @@ GHCi knows about. Using :ghci-cmd:`:module` or ``import`` to try bring into
scope a non-loaded module may result in the message
``module M is not loaded``.
+Shadowing and the ``Ghci1`` module name
+^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
+
+Bindings on the prompt can shadow earlier bindings:
+
+.. code-block:: none
+
+ ghci> let foo = True
+ ghci> let foo = False
+ ghci> :show bindings
+ foo :: Bool = False
+
+But the shadowed thing still exists, and may show up again later, for example
+in a type signature:
+
+.. code-block:: none
+
+ ghci> data T = A | B deriving Eq
+ ghci> let a = A
+ ghci> data T = ANewType
+ ghci> :t a
+ a :: Ghci1.T
+
+Now the type of ``a`` is printed using the fully qualified name of ``T``, using
+the module name ``Ghci1`` (and ``Ghci2`` for the next set of bindings, and so
+on). You can use these qualified names as well:
+
+.. code-block:: none
+
+ ghci> a == Ghci1.A
+ True
+ ghci> let a = False -- shadowing a
+ ghci> Ghci2.a == Ghci1.A
+ True
+
+The command ``:show bindings`` only shows bindings that are not shadowed.
+Bindings that define multiple names, such as a type constructor and its data
+constructors, are shown if *any* defined name is still available without the
+need for qualification.
+
The ``it`` variable
~~~~~~~~~~~~~~~~~~~
diff --git a/testsuite/tests/ghci/scripts/T11547.stderr b/testsuite/tests/ghci/scripts/T11547.stderr
deleted file mode 100644
index 2623e4659f..0000000000
--- a/testsuite/tests/ghci/scripts/T11547.stderr
+++ /dev/null
@@ -1,5 +0,0 @@
-
-<interactive>:1:1: error:
- • GHC internal error: ‘Ghci1.foo’ is not in scope during type checking, but it passed the renamer
- tcl_env of environment: []
- • In the expression: Ghci1.foo
diff --git a/testsuite/tests/ghci/scripts/T11547.stdout b/testsuite/tests/ghci/scripts/T11547.stdout
index f808e0c90e..6f2a8333c3 100644
--- a/testsuite/tests/ghci/scripts/T11547.stdout
+++ b/testsuite/tests/ghci/scripts/T11547.stdout
@@ -1,4 +1,5 @@
Ghci1.foo :: t
Ghci2.foo :: t
+Ghci1.foo :: t
Foo :: Ghci3.Foo
Ghci3.Bar :: Ghci3.Foo
diff --git a/testsuite/tests/ghci/scripts/T20455.script b/testsuite/tests/ghci/scripts/T20455.script
new file mode 100644
index 0000000000..a3261fe91c
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T20455.script
@@ -0,0 +1,17 @@
+let l = "first l"
+let l = "second l"
+ll -- should not recommend Ghci.l
+Ghci1.l
+l
+:info Ghci1.l
+:browse Ghci1
+
+-- Now the same for types
+data T = T
+t = T :: T
+data T = T
+:info t
+:type t
+t2 = Ghci5.T :: Ghci5.T
+
+
diff --git a/testsuite/tests/ghci/scripts/T20455.stderr b/testsuite/tests/ghci/scripts/T20455.stderr
new file mode 100644
index 0000000000..cb94e6ee3d
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T20455.stderr
@@ -0,0 +1,10 @@
+
+<interactive>:3:1: error:
+ • Variable not in scope: ll
+ • Perhaps you meant one of these:
+ ‘Ghci1.l’ (imported from Ghci1), ‘l’ (line 2),
+ ‘all’ (imported from Prelude)
+
+<no location info>: error:
+ Could not find module ‘Ghci1’
+ It is not a module in the current program, or in any known package.
diff --git a/testsuite/tests/ghci/scripts/T20455.stdout b/testsuite/tests/ghci/scripts/T20455.stdout
new file mode 100644
index 0000000000..8687a8e0b5
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T20455.stdout
@@ -0,0 +1,5 @@
+"first l"
+"second l"
+Ghci1.l :: String -- Defined at <interactive>:1:5
+t :: Ghci5.T -- Defined at <interactive>:11:1
+t :: Ghci5.T
diff --git a/testsuite/tests/ghci/scripts/T925.script b/testsuite/tests/ghci/scripts/T925.script
new file mode 100644
index 0000000000..ce003174f7
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T925.script
@@ -0,0 +1,7 @@
+:set -XTemplateHaskell
+let f n = n * 2::Int
+import Language.Haskell.TH
+fName <- runQ [| f |]
+$(return $ AppE fName (LitE (IntegerL 7)))
+let f n = n * 3::Int
+$(return $ AppE fName (LitE (IntegerL 7)))
diff --git a/testsuite/tests/ghci/scripts/T925.stdout b/testsuite/tests/ghci/scripts/T925.stdout
new file mode 100644
index 0000000000..e7376ef157
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T925.stdout
@@ -0,0 +1,2 @@
+14
+14
diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T
index 884df5a811..abecdcd76e 100755
--- a/testsuite/tests/ghci/scripts/all.T
+++ b/testsuite/tests/ghci/scripts/all.T
@@ -346,6 +346,9 @@ test('T20019', normal, ghci_script, ['T20019.script'])
test('T20101', normal, ghci_script, ['T20101.script'])
test('T20206', normal, ghci_script, ['T20206.script'])
test('T20217', normal, ghci_script, ['T20217.script'])
+test('T20455', normal, ghci_script, ['T20455.script'])
+test('shadow-bindings', normal, ghci_script, ['shadow-bindings.script'])
+test('T925', normal, ghci_script, ['T925.script'])
test('T7388', normal, ghci_script, ['T7388.script'])
test('T20627', normal, ghci_script, ['T20627.script'])
test('T20473a', normal, ghci_script, ['T20473a.script'])
diff --git a/testsuite/tests/ghci/scripts/shadow-bindings.script b/testsuite/tests/ghci/scripts/shadow-bindings.script
new file mode 100644
index 0000000000..6918ad9298
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/shadow-bindings.script
@@ -0,0 +1,48 @@
+-- Exercising the behaviour of :show bindings and shadowing
+let foo = True
+foo && True
+putStrLn "Expecting foo = True"
+:show bindings
+
+let foo = False
+foo && True
+putStrLn "Expecting foo = False"
+:show bindings
+:reload
+
+data T = A | B
+:show bindings
+-- shadow T
+data T = C
+putStrLn "Expecting T and Ghci1.T"
+:show bindings
+:reload
+
+data T = A | B
+-- shadow just A and B
+data T' = A | B'
+putStrLn "Expecting T and T'"
+:show bindings
+:reload
+
+
+data T = A | B
+-- shadow all
+data T = A | B | C
+putStrLn "Expecting only T, no Ghci1.T"
+:show bindings
+:reload
+
+
+-- Now with record selectors
+data T = A {foo :: Bool}
+putStrLn "Expecting T and foo with function type"
+:show bindings
+let foo = True
+putStrLn "Expecting T and foo :: Bool"
+:show bindings
+data T = A
+putStrLn "Expecting foo, T"
+:show bindings
+
+
diff --git a/testsuite/tests/ghci/scripts/shadow-bindings.stdout b/testsuite/tests/ghci/scripts/shadow-bindings.stdout
new file mode 100644
index 0000000000..ef7d5bc9c6
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/shadow-bindings.stdout
@@ -0,0 +1,41 @@
+True
+Expecting foo = True
+foo :: Bool = True
+it :: () = ()
+False
+Expecting foo = False
+foo :: Bool = False
+it :: () = ()
+type T :: *
+data T = ...
+Expecting T and Ghci1.T
+type Ghci1.T :: *
+data Ghci1.T = ...
+type T :: *
+data T = ...
+it :: () = ()
+Expecting T and T'
+type T :: *
+data T = ...
+type T' :: *
+data T' = ...
+it :: () = ()
+Expecting only T, no Ghci1.T
+type T :: *
+data T = ...
+it :: () = ()
+Expecting T and foo with function type
+type T :: *
+data T = ...
+foo :: T -> Bool = _
+it :: () = ()
+Expecting T and foo :: Bool
+type T :: *
+data T = ...
+foo :: Bool = True
+it :: () = ()
+Expecting foo, T
+foo :: Bool = True
+type T :: *
+data T = ...
+it :: () = ()