Neat! /me is going to love :grep and :redir

All these are for playing with the debugger.

-- running main in tracing mode
*Main> :main arg1 arg2 ...
*Main> :maintraced arg1 arg2 ...

-- stepping into main
*Main> :mainstep arg1 arg2 ...

-- eval to whnf
Prelude> let li = map Just [1..3]
Prelude> :sp li
li = _
Prelude> :eval li
()
Prelude> :sp li
li = _ : _

Attachment: .ghci
Description: Binary data


On 08/09/2007, at 3:30, Claus Reinke wrote:

having only recently started to play with ghci's :def and :cmd,
i'm still in the process of figuring out what is and what isn't possible, and i've been wondering what wonderful things other ghci users have in their .ghci files? to start with, here are my current favourites (definitions attached, this is using a recent ghc 6.7). i'm looking forward to seeing your
gems and favourites:-)

-- capturing command output in variables:
*Main> :redir out :info Monad
*Main> putStrLn out
class Monad m where
 (>>=) :: m a -> (a -> m b) -> m b
 (>>) :: m a -> m b -> m b
 return :: a -> m a
 fail :: String -> m a
       -- Defined in GHC.Base
instance Monad Maybe -- Defined in Data.Maybe
instance Monad [] -- Defined in GHC.Base
instance Monad IO -- Defined in GHC.IOBase

-- filtering command output for lines matching pattern:
*Main> :grep break :?

:abandon at a breakpoint, abandon current computation :break [<mod>] <l> [<col>] set a breakpoint at the specified location :break <name> set a breakpoint on the specified function
  :continue                   resume after a breakpoint
  :delete <number>            delete the specified breakpoint
  :delete *                   delete all breakpoints
:step single-step after stopping at a breakpoint
  :trace                      trace after stopping at a breakpoint
:trace <expr> trace into <expr> (remembers breakpoints for :history) :set stop <cmd> set the command to run when a breakpoint is hit
  :show breaks                show the active breakpoints
  :show context               show the breakpoint context

*Main> :grep class :browse Control.Monad

class Monad m where
class Functor f where fmap :: (a -> b) -> f a -> f b
class (Monad m) => MonadPlus m where

-- Hugs' :find <id>, calling editor to open definition of <id>
*Main> :find main

probably, there should be a wiki page collecting such :definitions,
and other ways of improving the ghci usage experience. but i'm unsure whether to add to the haskell wiki

   http://haskell.org/haskellwiki/GHC/GHCi

or to the ghc developer's wiki

   http://hackage.haskell.org/trac/ghc

opinions? suggestions? tips? tricks?-)
claus<cmds.ghci>_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to