[GHC] #11208: GHCi doesn't qualify types anymore

#11208: GHCi doesn't qualify types anymore -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: GHCi | Version: 7.11 Keywords: regression | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `M.hs` contains: {{{#!hs module M where import qualified Prelude as P f n = n P.+ 1 g h (P.Just x) = P.Just (h x) g _ P.Nothing = P.Nothing }}} GHC 7.10.3 behaves as expected: {{{ $ ghci-7.10.3 -ignore-dot-ghci M.hs GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling M ( M.hs, interpreted ) Ok, modules loaded: M. *M> :browse f :: P.Num a => a -> a g :: (t -> a) -> P.Maybe t -> P.Maybe a *M> :t f f :: P.Num a => a -> a *M> :t g g :: (t -> a) -> P.Maybe t -> P.Maybe a }}} However, GHC HEAD drops the module qualifiers {{{ $ ghci-7.11.20151209 -ignore-dot-ghci M.hs GHCi, version 7.11.20151209: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling M ( M.hs, interpreted ) Ok, modules loaded: M. *M> :browse f :: Num a => a -> a g :: (t -> a) -> Maybe t -> Maybe a *M> :t f f :: Num a => a -> a *M> :t g g :: (t -> a) -> Maybe t -> Maybe a *M> Nothing :: Maybe () <interactive>:4:12: error: Not in scope: type constructor or class ‘Maybe’ Perhaps you meant ‘P.Maybe’ (imported from Prelude) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11208 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11208: GHCi doesn't qualify types anymore -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: GHCi | Version: 7.11 Resolution: | Keywords: regression Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): This change is intentional, though perhaps not in this particular setting. I forget the ticket number though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11208#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11208: GHCi doesn't qualify types anymore -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: GHCi | Version: 7.11 Resolution: | Keywords: regression Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): I notice this also applies to warning messages, i.e. {{{ M.hs:5:1: Warning: Top-level binding with no type signature: f :: forall a. P.Num a => a -> a M.hs:7:1: Warning: Top-level binding with no type signature: g :: forall t a. (t -> a) -> P.Maybe t -> P.Maybe a }}} vs {{{ M.hs:5:1: warning: Top-level binding with no type signature: f :: forall a. Num a => a -> a M.hs:7:1: warning: Top-level binding with no type signature: g :: forall a r. (r -> a) -> Maybe r -> Maybe a }}} In any case, this causes breakage for tooling (and users) relying on the warnings and ghci-output to be qualified in the module-scope they've been triggered from. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11208#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11208: GHCi doesn't qualify types anymore -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: GHCi | Version: 7.11 Resolution: | Keywords: regression Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hvr): * cc: simonpj (added) Comment: Looks like this regression was caused by 547c597112954353cef7157cb0a389bc4f6303eb -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11208#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11208: GHCi doesn't qualify types anymore -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: GHCi | Version: 7.11 Resolution: | Keywords: regression Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm sorry about that. For the benefit of other readers, GHCi tries to print types that make sense in the lexical scope of the REPL (i.e. the interactive context). If a type needs to be qualified, GHC will qualify it when printing it out. But in the commit hvr points to in comment:3, I gave the pacakges `ghc- prim`, `base` and `template-haskell` special behaviour, and are printed unqualified. How bad is that? Does tooling really parse error messages? (If so there should be a Better Way!) My motivation, as explained in the commit, was to avoid printing a heavily-qualified `Constraint` when giving kind signatures. But maybe there is a better way to do that? I'd be happy with an agreed design change here. As the commit says, it's a bit arbitrary as it stands. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11208#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

How bad is that? Does tooling really parse error messages? (If so
#11208: GHCi doesn't qualify types anymore -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: GHCi | Version: 7.11 Resolution: | Keywords: regression Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): Replying to [comment:4 simonpj]: there should be a Better Way!) While there *should* be a better way, there isn't yet... GHC doesn't ship with anything better than GHC(i) right now Here's two ways how this regression affects Emacs' haskell-mode: - For warnings about missing type-signatures, Emacs parses the warning message and then inserts the extracted missing type-signature - Another feature is based on GHCi, which queries the symbol under the cursors for its type, and then inserts that above as a type-signature There may be other features I may have forgotten about which also require to know renamer-information. In both cases it's important to know how to qualify (if needed) symbols. And in passive mode (e.g. when parsing GHC's warning messages w/o an active GHCi session attached) Emacs has no way to query the module namespace. In active mode (e.g. when using GHCi to resolve/introspect information) Emacs uses `:type`/`:browse`/`:info` as well as other commands newly added (soon) to GHC 8.0 (see #10874). Those now are missing the module qualifications -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11208#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11208: GHCi doesn't qualify types anymore
-------------------------------------+-------------------------------------
Reporter: hvr | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: GHCi | Version: 7.11
Resolution: | Keywords: regression
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Other | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11208: GHCi doesn't qualify types anymore -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: GHCi | Version: 7.11 Resolution: fixed | Keywords: regression Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: The above commit drastically reduced the scope of the special-casing. Hopefully this should help make the output a bit more predictable. For the list of names that will be unconditionally printed as unqualified see `forceUnqualNames` in `mkPrintUnqualified`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11208#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC