
One of my most used GHCi commands is :info, but quite often the type or class definitions that I'm interested in get drowned in lots of instances. So a week ago I wrote a feature request and a little patch that allowed the following: :info Show -- See class definition and instances :info -Show -- See class definition only SPJ agreed with the idea itself, but suggested an alternative set of commands: :info Show -- See class definition only :instances Show -- See instances of Show This would have the advantage of making it easier to later add additional features: :instances Show (Tree _) -- See instances of form (Show (Tree ...)) However, it would make ":i" ambiguous, which is rather sad. Another potential addition to :info (or another command) would be evaluating types to their normal form, that is, expanding (associated) type synonyms. E.g.: :typeeval Plus (Suc Zero) (Suc Zero) -- (Suc (Suc (Suc (Suc Zero)))) Again, the question is whether this is really useful (or reasonably easy to implement, SPJ?) and if so, what interface is to be preferred? So what's your favourite syntax? One of these options or something else? Or are these features completely unnecessary? Oh, the ticket can be found at http://hackage.haskell.org/trac/ghc/ticket/2986#comment:3 Groeten, Remi

Remi Turk wrote:
SPJ agreed with the idea itself, but suggested an alternative set of commands:
:info Show -- See class definition only :instances Show -- See instances of Show
Hi Remi, If you do not want to wait till this is implemented you can do it yourself using ghci scripting. Details how to do it are in tutorial from Claus Reinke: http://www.haskell.org/pipermail/haskell-cafe/2007-September/032260.html Understanding all the possibilities and limitations of ghci scripting may take a day or maybe even more. But once you are done with it you can implement your :instances command and and something like :infoWithoutInstances withing an hour at most. And it is more interesting that you could do much more extensions like this easily if you need them in the future. Peter.

:info Show -- See class definition only :instances Show -- See instances of Show
If you do not want to wait till this is implemented you can do it yourself using ghci scripting.
Here's a first stab (ghci 6.8.3, using the :redir command from that tutorial), filtering out lines beginning with "instance" until indentation level returns to zero): Prelude> :{ Prelude| :def infoNoInsts \x->return $ unlines Prelude| [":redir out :info "++x Prelude| ,"let noInsts [] = []; Prelude| noInsts (l:ls) = if \"instance\" `Data.List.isPrefixOf` l Prelude| then noInsts $ dropWhile (Data.Char.isSpace . head) ls Prelude| else l:noInsts ls" Prelude| ,"putStr $ unlines $ noInsts $ lines out"] Prelude| :} Prelude> :infoNoInsts Show class Show a where showsPrec :: Int -> a -> ShowS show :: a -> String showList :: [a] -> ShowS -- Defined in GHC.Show Prelude> :infoNoInsts [] Maybe Int data [] a = [] | a : [a] -- Defined in GHC.Base data Maybe a = Nothing | Just a -- Defined in Data.Maybe data Int = GHC.Base.I# GHC.Prim.Int# -- Defined in GHC.Base
Details how to do it are in tutorial from Claus Reinke: http://www.haskell.org/pipermail/haskell-cafe/2007-September/032260.html Understanding all the possibilities and limitations of ghci scripting may take a day or maybe even more. But once you are done with it you can implement your :instances command and and something like :infoWithoutInstances withing an hour at most. And it is more interesting that you could do much more extensions like this easily if you need them in the future.
Note that "understanding" is unlikely to mean "feel comfortable with" here:-( the quoting and scope management are rather attrocious in 'ghciscript', and as others have pointed out, my tutorial is rather short on explanations (you really need to work through the examples). It does, however, afford you the means to prototype your ghci ideas quickly, and to build yourself a library of useful definitions for working with ghci. Please remember to share any interesting ideas/code at the ghci wiki page http://www.haskell.org/haskellwiki/Ghci (once haskell wiki access is resurrected) Claus

On Thu, Feb 05, 2009 at 12:35:43PM +0100, Peter Hercek wrote:
Remi Turk wrote:
SPJ agreed with the idea itself, but suggested an alternative set of commands:
:info Show -- See class definition only :instances Show -- See instances of Show
Hi Remi,
If you do not want to wait till this is implemented you can do it yourself using ghci scripting.
Thank you Peter, but in this case it won't be of much help: I am already running a patched GHCi: http://hackage.haskell.org/trac/ghc/attachment/ticket/2986/ghci-info-no-inst... But I may use it for something else later, so thanks anyway! Cheers, Remi

On 2009 Feb 5, at 5:49, Remi Turk wrote:
SPJ agreed with the idea itself, but suggested an alternative set of commands:
:info Show -- See class definition only :instances Show -- See instances of Show (...) However, it would make ":i" ambiguous, which is rather sad.
:class Show -- unique prefix :cl, already many such collisions :instance Show -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Sat, Feb 07, 2009 at 12:39:03AM -0500, Brandon S. Allbery KF8NH wrote:
On 2009 Feb 5, at 5:49, Remi Turk wrote:
SPJ agreed with the idea itself, but suggested an alternative set of commands:
:info Show -- See class definition only :instances Show -- See instances of Show (...) However, it would make ":i" ambiguous, which is rather sad.
:class Show -- unique prefix :cl, already many such collisions :instance Show
That could work, but then how to get information about types as opposed to classes? Its not in the above example, but "Show" actually stands for an arbitrary typeclass _or type_. However, as igloo pointed out on the ticket, abbreviations don't actually have to be unique: "For example, :b means :break even though we also have :back, :browse and :browse!. " [1] That would personally lead me to prefer the :info/:instances combo, with :i as an abbreviation of :info. Groeten, Remi [1] http://hackage.haskell.org/trac/ghc/ticket/2986#comment:4

Remi Turk wrote:
On Sat, Feb 07, 2009 at 12:39:03AM -0500, Brandon S. Allbery KF8NH wrote:
On 2009 Feb 5, at 5:49, Remi Turk wrote:
SPJ agreed with the idea itself, but suggested an alternative set of commands:
:info Show -- See class definition only :instances Show -- See instances of Show (...) However, it would make ":i" ambiguous, which is rather sad. :class Show -- unique prefix :cl, already many such collisions :instance Show
That could work, but then how to get information about types as opposed to classes? Its not in the above example, but "Show" actually stands for an arbitrary typeclass _or type_.
However, as igloo pointed out on the ticket, abbreviations don't actually have to be unique:
"For example, :b means :break even though we also have :back, :browse and :browse!. " [1]
That would personally lead me to prefer the :info/:instances combo, with :i as an abbreviation of :info.
My vote would be: :info class Show :info type Show :info instance Show where :info Show displays information about everything called "Show" I know that classes and types share the same namespace currently, but it might not always be so. Cheers, Simon

On Tue, Feb 10, 2009 at 01:31:24PM +0000, Simon Marlow wrote:
Remi Turk wrote:
On Sat, Feb 07, 2009 at 12:39:03AM -0500, Brandon S. Allbery KF8NH wrote:
On 2009 Feb 5, at 5:49, Remi Turk wrote:
SPJ agreed with the idea itself, but suggested an alternative set of commands:
:info Show -- See class definition only :instances Show -- See instances of Show (...) However, it would make ":i" ambiguous, which is rather sad. :class Show -- unique prefix :cl, already many such collisions :instance Show
That could work, but then how to get information about types as opposed to classes? Its not in the above example, but "Show" actually stands for an arbitrary typeclass _or type_.
However, as igloo pointed out on the ticket, abbreviations don't actually have to be unique:
"For example, :b means :break even though we also have :back, :browse and :browse!. " [1]
That would personally lead me to prefer the :info/:instances combo, with :i as an abbreviation of :info.
My vote would be:
:info class Show :info type Show :info instance Show
where
:info Show
displays information about everything called "Show"
I know that classes and types share the same namespace currently, but it might not always be so.
Sounds good in principle, and has the advantage of being 100% backward compatible, but ":i class Show" for the common case (ahum, _my_ common case at least ;) still seems rather verbose, so how to abbreviate that? Remi

Remi Turk wrote:
On Tue, Feb 10, 2009 at 01:31:24PM +0000, Simon Marlow wrote:
Remi Turk wrote:
On Sat, Feb 07, 2009 at 12:39:03AM -0500, Brandon S. Allbery KF8NH wrote:
On 2009 Feb 5, at 5:49, Remi Turk wrote:
SPJ agreed with the idea itself, but suggested an alternative set of commands:
:info Show -- See class definition only :instances Show -- See instances of Show (...) However, it would make ":i" ambiguous, which is rather sad. :class Show -- unique prefix :cl, already many such collisions :instance Show That could work, but then how to get information about types as opposed to classes? Its not in the above example, but "Show" actually stands for an arbitrary typeclass _or type_.
However, as igloo pointed out on the ticket, abbreviations don't actually have to be unique:
"For example, :b means :break even though we also have :back, :browse and :browse!. " [1]
That would personally lead me to prefer the :info/:instances combo, with :i as an abbreviation of :info. My vote would be:
:info class Show :info type Show :info instance Show
where
:info Show
displays information about everything called "Show"
I know that classes and types share the same namespace currently, but it might not always be so.
Sounds good in principle, and has the advantage of being 100% backward compatible, but ":i class Show" for the common case (ahum, _my_ common case at least ;) still seems rather verbose, so how to abbreviate that?
How about a macro? :def ic return . (":info class " ++) Cheers, Simon

On Thu, Feb 12, 2009 at 08:47:36AM +0000, Simon Marlow wrote:
Remi Turk wrote:
On Tue, Feb 10, 2009 at 01:31:24PM +0000, Simon Marlow wrote:
My vote would be:
:info class Show :info type Show :info instance Show
where
:info Show
displays information about everything called "Show"
I know that classes and types share the same namespace currently, but it might not always be so.
Sounds good in principle, and has the advantage of being 100% backward compatible, but ":i class Show" for the common case (ahum, _my_ common case at least ;) still seems rather verbose, so how to abbreviate that?
How about a macro?
:def ic return . (":info class " ++)
Ah of course, I keep forgetting about :def :) Note that when classes and types would stop sharing their namespace, ":info instance Show" would again be ambiguous though.. Groeten, Remi
participants (5)
-
Brandon S. Allbery KF8NH
-
Claus Reinke
-
Peter Hercek
-
Remi Turk
-
Simon Marlow