GHCi commands all begin with
‘:
’ and consist of a single command
name followed by zero or more parameters. The command name may be
abbreviated, with ambiguities being resolved in favour of the more
commonly used commands.
:abandon
Abandons the current evaluation (only available when stopped at a breakpoint).
:add
[*
]module
...
Add module
(s) to the
current target set, and perform a
reload. Normally pre-compiled code for the module will be
loaded if available, or otherwise the module will be
compiled to byte-code. Using the *
prefix forces the module to be loaded as byte-code.
:back
Travel back one step in the history. See Section 2.5.5, “Tracing and history”. See also:
:trace
, :history
,
:forward
.
:break [identifier
|
[module
] line
[column
]]
Set a breakpoint on the specified function or line and column. See Section 2.5.1.1, “Setting breakpoints”.
:browse
[!
] [[*
]module
] ...
Displays the identifiers exported by the module
module
, which must be either
loaded into GHCi or be a member of a package. If
module
is omitted, the most
recently-loaded module is used.
Like all other GHCi commands, the output is always displayed in the current GHCi scope (Section 2.4.5, “What's really in scope at the prompt?”).
There are two variants of the browse command:
If the *
symbol is placed before
the module name, then all the
identifiers in scope in module
(rather that just its exports) are shown.
The *
-form is only available for modules
which are interpreted; for compiled modules (including
modules from packages) only the non-*
form of :browse
is available.
Data constructors and class methods are usually
displayed in the context of their data type or class declaration.
However, if the !
symbol is appended to the
command, thus :browse!
,
they are listed individually.
The !
-form also annotates the listing
with comments giving possible imports for each group of
entries. Here is an example:
Prelude> :browse! Data.Maybe -- not currently imported Data.Maybe.catMaybes :: [Maybe a] -> [a] Data.Maybe.fromJust :: Maybe a -> a Data.Maybe.fromMaybe :: a -> Maybe a -> a Data.Maybe.isJust :: Maybe a -> Bool Data.Maybe.isNothing :: Maybe a -> Bool Data.Maybe.listToMaybe :: [a] -> Maybe a Data.Maybe.mapMaybe :: (a -> Maybe b) -> [a] -> [b] Data.Maybe.maybeToList :: Maybe a -> [a] -- imported via Prelude Just :: a -> Maybe a data Maybe a = Nothing | Just a Nothing :: Maybe a maybe :: b -> (a -> b) -> Maybe a -> b
This output shows that, in the context of the current session (ie in the scope
of Prelude
), the first group of items from
Data.Maybe
are not in scope (althought they are available in
fully qualified form in the GHCi session - see Section 2.4.5, “What's really in scope at the prompt?”), whereas the second group of items are in scope
(via Prelude
) and are therefore available either
unqualified, or with a Prelude.
qualifier.
:cd
dir
Changes the current working directory to
dir
. A
‘˜
’ symbol at the
beginning of dir
will be replaced
by the contents of the environment variable
HOME
.
See also the :show paths
command for
showing the current working directory.
NOTE: changing directories causes all currently loaded modules to be unloaded. This is because the search path is usually expressed using relative directories, and changing the search path in the middle of a session is not supported.
:cmd
expr
Executes expr
as a computation of
type IO String
, and then executes the resulting
string as a list of GHCi commands. Multiple commands are separated
by newlines. The :cmd
command is useful with
:def
and :set stop
.
:complete
type
[n
-][m
]
string-literal
This command allows to request command completions from GHCi even when interacting over a pipe instead of a proper terminal and is designed for integrating GHCi's completion with text editors and IDEs.
When called, :complete
prints the
n
th to
m
th
completion candidates for the partial input
string-literal
for the completion
domain denoted by
type
. Currently, only the
repl
domain is supported which denotes
the kind of completion that would be provided interactively
by GHCi at the input prompt.
If omitted, n
and
m
default to the first or last
available completion candidate respectively. If there are
less candidates than requested via the range argument,
n
and
m
are implicitly capped to the
number of available completition candidates.
The output of :complete
begins with
a header line containing three space-delimited fields:
l
of printed
completions,
The header line is followed by l
lines each containing one completion candidate encoded as
(quoted) string literal. Here are some example invocations
showing the various cases:
Prelude> :complete repl 0 "" 0 470 "" Prelude> :complete repl 5 "import For" 5 21 "import " "Foreign" "Foreign.C" "Foreign.C.Error" "Foreign.C.String" "Foreign.C.Types" Prelude> :complete repl 5-10 "import For" 6 21 "import " "Foreign.C.Types" "Foreign.Concurrent" "Foreign.ForeignPtr" "Foreign.ForeignPtr.Safe" "Foreign.ForeignPtr.Unsafe" "Foreign.Marshal" Prelude> :complete repl 20- "import For" 2 21 "import " "Foreign.StablePtr" "Foreign.Storable" Prelude> :complete repl "map" 3 3 "" "map" "mapM" "mapM_" Prelude> :complete repl 5-10 "map" 0 3 ""
:continue
Continue the current evaluation, when stopped at a breakpoint.
:ctags
[filename
]
:etags
[filename
]
Generates a “tags” file for Vi-style editors
(:ctags
) or
Emacs-style editors (:etags
). If
no filename is specified, the default tags
or
TAGS
is
used, respectively. Tags for all the functions, constructors and
types in the currently loaded modules are created. All modules must
be interpreted for these commands to work.
:def[!] [name
expr
]
:def
is used to define new
commands, or macros, in GHCi. The command
:def
name
expr
defines a new GHCi command
:
,
implemented by the Haskell expression
name
expr
, which must have type
String -> IO String
. When
:
is typed at the
prompt, GHCi will run the expression
name
args
(
, take the
resulting name
args
)String
, and feed it back into
GHCi as a new sequence of commands. Separate commands in
the result must be separated by
‘\n
’.
That's all a little confusing, so here's a few examples. To start with, here's a new GHCi command which doesn't take any arguments or produce any results, it just outputs the current date & time:
Prelude> let date _ = Time.getClockTime >>= print >> return "" Prelude> :def date date Prelude> :date Fri Mar 23 15:16:40 GMT 2001
Here's an example of a command that takes an argument.
It's a re-implementation of :cd
:
Prelude> let mycd d = Directory.setCurrentDirectory d >> return "" Prelude> :def mycd mycd Prelude> :mycd ..
Or I could define a simple way to invoke
“ghc --make Main
” in the
current directory:
Prelude> :def make (\_ -> return ":! ghc --make Main")
We can define a command that reads GHCi input from a file. This might be useful for creating a set of bindings that we want to repeatedly load into the GHCi session:
Prelude> :def . readFile Prelude> :. cmds.ghci
Notice that we named the command
:.
, by analogy with the
‘.
’ Unix shell command that
does the same thing.
Typing :def
on its own lists the
currently-defined macros. Attempting to redefine an
existing command name results in an error unless the
:def!
form is used, in which case the old
command with that name is silently overwritten.
:delete * | num
...
Delete one or more breakpoints by number (use :show
breaks
to see the number of each breakpoint). The
*
form deletes all the breakpoints.
:edit [file
]
Opens an editor to edit the file
file
, or the most recently loaded
module if file
is omitted. The
editor to invoke is taken from the EDITOR
environment variable, or a default editor on your system if
EDITOR
is not set. You can change the
editor using :set editor
.
:etags
See :ctags
.
:force identifier
...
Prints the value of identifier
in
the same way as :print
. Unlike
:print
, :force
evaluates each
thunk that it encounters while traversing the value. This may
cause exceptions or infinite loops, or further breakpoints (which
are ignored, but displayed).
:forward
Move forward in the history. See Section 2.5.5, “Tracing and history”. See also:
:trace
, :history
,
:back
.
:help
,
:?
Displays a list of the available commands.
:
Repeat the previous command.
:history [num
]
Display the history of evaluation steps. With a
number, displays that many steps (default: 20). For use
with :trace
; see Section 2.5.5, “Tracing and history”. To set the number of history entries stored by GHCi,
use
-fghci-hist-size=
.n
:info
[!
]name
...
Displays information about the given name(s). For
example, if name
is a class, then
the class methods and their types will be printed; if
name
is a type constructor, then
its definition will be printed; if
name
is a function, then its type
will be printed. If name
has
been loaded from a source file, then GHCi will also display
the location of its definition in the source.
For types and classes, GHCi also summarises instances that
mention them. To avoid showing irrelevant information, an instance
is shown only if (a) its head mentions name
,
and (b) all the other things mentioned in the instance
are in scope (either qualified or otherwise) as a result of
a :load
or :module
commands.
The command :info!
works in a similar fashion
but it removes restriction (b), showing all instances that are in
scope and mention name
in their head.
:issafe
[module
]
Displays Safe Haskell information about the given module (or the current module if omitted). This includes the trust type of the module and its containing package.
:kind
[!
]
type
Infers and prints the kind of
type
. The latter can be an arbitrary
type expression, including a partial application of a type constructor,
such as Either Int
. In fact, :kind
even allows you to write a partial application of a type synonym (usually disallowed),
so that this works:
ghci> type T a b = (a,b,a) ghci> :k T Int Bool T Int Bool :: * ghci> :k T T :: * -> * -> * ghci> :k T Int T Int :: * -> *
If you specify the
optional "!
", GHC will in addition normalise the type
by expanding out type synonyms and evaluating type-function applications,
and display the normalised result.
:list
identifier
Lists the source code around the definition of
identifier
or the current
breakpoint if not given. This requires that the identifier be
defined in an interpreted module. If your output device
supports it, then GHCi will highlight the active
subexpression in bold.
:list
[module
] line
Lists the source code around the given line number of
module
. This requires that the module be
interpreted. If your output device supports it, then GHCi will
highlight the active subexpression in bold.
:load
[*
]module
...
Recursively loads the specified
module
s, and all the modules they
depend on. Here, each module
must be a module name or filename, but may not be the name
of a module in a package.
All previously loaded modules, except package modules,
are forgotten. The new set of modules is known as the
target set. Note that
:load
can be used without any arguments
to unload all the currently loaded modules and
bindings.
Normally pre-compiled code for a module will be loaded
if available, or otherwise the module will be compiled to
byte-code. Using the *
prefix forces a
module to be loaded as byte-code.
After a :load
command, the current
context is set to:
module
, if it was loaded
successfully, or
the most recently successfully loaded module, if
any other modules were loaded as a result of the current
:load
, or
Prelude
otherwise.
:main arg1
... argn
When a program is compiled and executed, it can use the
getArgs
function to access the
command-line arguments.
However, we cannot simply pass the arguments to the
main
function while we are testing in ghci,
as the main
function doesn't take its
arguments directly.
Instead, we can use the :main
command.
This runs whatever main
is in scope, with
any arguments being treated the same as command-line arguments,
e.g.:
Prelude> let main = System.Environment.getArgs >>= print Prelude> :main foo bar ["foo","bar"]
We can also quote arguments which contains characters like spaces, and they are treated like Haskell strings, or we can just use Haskell list syntax:
Prelude> :main foo "bar baz" ["foo","bar baz"] Prelude> :main ["foo", "bar baz"] ["foo","bar baz"]
Finally, other functions can be called, either with the
-main-is
flag or the :run
command:
Prelude> let foo = putStrLn "foo" >> System.Environment.getArgs >>= print Prelude> let bar = putStrLn "bar" >> System.Environment.getArgs >>= print Prelude> :set -main-is foo Prelude> :main foo "bar baz" foo ["foo","bar baz"] Prelude> :run bar ["foo", "bar baz"] bar ["foo","bar baz"]
:module [+|-] [*]mod1
... [*]modn
,
import mod
Sets or modifies the current context for statements
typed at the prompt. The form import
is equivalent to
mod
:module +
.
See Section 2.4.5, “What's really in scope at the prompt?” for
more details.mod
:print
names
...
Prints a value without forcing its evaluation.
:print
may be used on values whose types are
unknown or partially known, which might be the case for local
variables with polymorphic types at a breakpoint. While inspecting
the runtime value, :print
attempts to
reconstruct the type of the value, and will elaborate the type in
GHCi's environment if possible. If any unevaluated components
(thunks) are encountered, then :print
binds
a fresh variable with a name beginning with _t
to each thunk. See Section 2.5.1, “Breakpoints and inspecting variables” for more
information. See also the :sprint
command,
which works like :print
but does not bind new
variables.
:quit
Quits GHCi. You can also quit by typing control-D at the prompt.
:reload
Attempts to reload the current target set (see
:load
) if any of the modules in the set,
or any dependent module, has changed. Note that this may
entail loading new modules, or dropping modules which are no
longer indirectly required by the target.
:run
See :main
.
:script
[n
]
filename
Executes the lines of a file as a series of GHCi commands. This command
is compatible with multiline statements as set by :set +m
:set
[option
...]
Sets various options. See Section 2.8, “The :set
and :seti
commands” for a list of
available options and Section 4.20.10, “Interactive-mode options” for a
list of GHCi-specific flags. The :set
command by
itself shows which options are currently set. It also lists the current
dynamic flag settings, with GHCi-specific flags listed separately.
:set
args
arg
...
Sets the list of arguments which are returned when the
program calls System.getArgs
.
:set
editor
cmd
Sets the command used by :edit
to
cmd
.
:set
prog
prog
Sets the string to be returned when the program calls
System.getProgName
.
:set
prompt
prompt
Sets the string to be used as the prompt in GHCi.
Inside prompt
, the sequence
%s
is replaced by the names of the
modules currently in scope, %l
is replaced
by the line number (as referenced in compiler messages) of the
current prompt, and %%
is replaced by
%
. If prompt
starts with " then it is parsed as a Haskell String;
otherwise it is treated as a literal string.
:set
prompt2
prompt
Sets the string to be used as the continuation prompt
(used when using the :{
command) in GHCi.
:set
stop
[num
] cmd
Set a command to be executed when a breakpoint is hit, or a new
item in the history is selected. The most common use of
:set stop
is to display the source code at the
current location, e.g. :set stop :list
.
If a number is given before the command, then the commands are
run when the specified breakpoint (only) is hit. This can be quite
useful: for example, :set stop 1 :continue
effectively disables breakpoint 1, by running
:continue
whenever it is hit (although GHCi will
still emit a message to say the breakpoint was hit). What's more,
with cunning use of :def
and
:cmd
you can use :set stop
to
implement conditional breakpoints:
*Main> :def cond \expr -> return (":cmd if (" ++ expr ++ ") then return \"\" else return \":continue\"") *Main> :set stop 0 :cond (x < 3)
Ignoring breakpoints for a specified number of iterations is also possible using similar techniques.
:seti
[option
...]
Like :set
, but options set with
:seti
affect only expressions and
commands typed at the prompt, and not modules loaded with
:load
(in contrast, options set with
:set
apply everywhere). See Section 2.8.3, “Setting options for interactive evaluation only”.
Without any arguments, displays the current set of options that are applied to expressions and commands typed at the prompt.
:show bindings
Show the bindings made at the prompt and their types.
:show breaks
List the active breakpoints.
:show context
List the active evaluations that are stopped at breakpoints.
:show imports
Show the imports that are currently in force, as
created by import
and
:module
commands.
:show modules
Show the list of modules currently loaded.
:show packages
Show the currently active package flags, as well as the list of packages currently loaded.
:show paths
Show the current working directory (as set via
:cd
command), as well as the list of
directories searched for source files (as set by the
-i
option).
:show language
Show the currently active language flags for source files.
:showi language
Show the currently active language flags for
expressions typed at the prompt (see also :seti
).
:show [args|prog|prompt|editor|stop]
Displays the specified setting (see
:set
).
:sprint
Prints a value without forcing its evaluation.
:sprint
is similar to :print
,
with the difference that unevaluated subterms are not bound to new
variables, they are simply denoted by ‘_’.
:step
[expr
]
Enable all breakpoints and begin evaluating an
expression in single-stepping mode. In this
mode evaluation will be stopped after every reduction,
allowing local variables to be inspected.
If expr
is not given, evaluation will
resume at the last breakpoint.
See Section 2.5.2, “Single-stepping”.
:steplocal
Enable only breakpoints in the current top-level binding and resume evaluation at the last breakpoint.
:stepmodule
Enable only breakpoints in the current module and resume evaluation at the last breakpoint.
:trace [expr
]
Evaluates the given expression (or from the last breakpoint if
no expression is given), and additionally logs the evaluation
steps for later inspection using :history
. See
Section 2.5.5, “Tracing and history”.
:type
expression
Infers and prints the type of
expression
, including explicit
forall quantifiers for polymorphic types. The monomorphism
restriction is not applied to the
expression during type inference.
:undef
name
Undefines the user-defined command
name
(see :def
above).
:unset
option
...
Unsets certain options. See Section 2.8, “The :set
and :seti
commands”
for a list of available options.
:!
command
...
Executes the shell command
command
.