[GHC] #11801: RFC: Make browse command display everything unqualified

#11801: RFC: Make browse command display everything unqualified -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: lowest | Milestone: Component: GHCi | Version: Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- What the title says, sometimes the output of `:browse` (`:bro`) is highly verbose. If you want unqualified names you need to (as far as I know) import the modules in question, even then names may still be qualified if they clash with names from other modules in scope. {{{ ghci> :browse Control.Applicative.Free data Control.Applicative.Free.Ap (f :: * -> *) a where Control.Applicative.Free.Pure :: a -> Control.Applicative.Free.Ap f a Control.Applicative.Free.Ap :: (f a1) -> (Control.Applicative.Free.Ap f (a1 -> a)) -> Control.Applicative.Free.Ap f a Control.Applicative.Free.hoistAp :: (forall a. f a -> g a) -> Control.Applicative.Free.Ap f b -> Control.Applicative.Free.Ap g b }}} versus {{{ ghci> :newbrowse Control.Applicative.Free data Ap (f :: * -> *) a where Pure :: a -> Ap f a Ap :: (f a1) -> (Ap f (a1 -> a)) -> Ap f a hoistAp :: (forall a. f a -> g a) -> Ap f b -> Ap g b ... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11801 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11801: RFC: Make browse command display everything unqualified -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: lowest | Milestone: Component: GHCi | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): What about names that occur in types that are not from the browed module, and not in scope? Should they be qualified? Is this attempt to be precise what you want: “:browse Foo” should never print the names of symbols (left of `::`) qualified, and in the types, should print as if `Foo` is imported, i.e. only qualify it if there would be a clash. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11801#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11801: RFC: Make browse command display everything unqualified -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: lowest | Milestone: Component: GHCi | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): My thought would be to display everything unqualified, but it could always be a flag: `:newbrowse!`. The actual command name can be bikesheded -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11801#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11801: RFC: Make browse command display everything unqualified -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: lowest | Milestone: Component: GHCi | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11208 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: => #11208 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11801#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11801: RFC: Make browse command display everything unqualified -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: lowest | Milestone: Component: GHCi | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11208 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Don’t resort to configurability (or additional commands) until we are sure that there is not a design that works for everyone :-) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11801#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11801: RFC: Make browse command display everything unqualified -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: lowest | Milestone: Component: GHCi | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11208 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata):
My thought would be to display everything unqualified,
Let’s get more concrete. Assume we have this module: {{{#!hs module Foo import Prelude hiding (Either) import qualified Prelude import Bar (OtherType) type SomeType = .. type Either a b = .. foo :: SomeType -> OtherType -> Either a b -> Maybe a -> Prelude.Either a b }}} then currently `:browse Foo` (with only `Prelude` imported, but not `Bar` or `Foo`) would give this {{{#!hs
:browse Foo Foo.foo :: SomeType -> Bar.OtherType -> Foo.Either a b -> Maybe a -> Either a b }}}
Your suggestion (everything unqualified) would be {{{#!hs
:browse Foo type SomeType type Either a b foo :: SomeType -> OtherType -> Either a b -> Maybe a -> Either a b }}}
while mine would yield: {{{#!hs
:browse Foo type SomeType type Either a b foo :: SomeType -> Bar.OtherType -> Foo.Either a b -> Maybe a -> Either a b }}}
Note how my variant of your proposal * avoids disambiguities in the types of symbols, if there are name clashes with type in scope * still indicates modules of symbols that are neither in scope nor from the browsed module * still avoids lots of module prefixes -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11801#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC