When you type an expression at the prompt, GHCi immediately evaluates and prints the result:
Prelude> reverse "hello" "olleh" Prelude> 5+5 10
GHCi does more than simple expression evaluation at the prompt.
If you enter an expression of type IO a
for some
a
, then GHCi executes it
as an IO-computation.
Prelude> "hello" "hello" Prelude> putStrLn "hello" hello
This works even if the type of the expression is more general,
provided it can be instantiated to IO a
. For example
Prelude> return True True
Furthermore, GHCi will print the result of the I/O action if (and only if):
The result type is an instance of Show
.
The result type is not
()
.
For example, remembering that putStrLn :: String -> IO ()
:
Prelude> putStrLn "hello" hello Prelude> do { putStrLn "hello"; return "yes" } hello "yes"
GHCi actually accepts statements rather than just expressions at the prompt. This means you can bind values and functions to names, and use them in future expressions or statements.
The syntax of a statement accepted at the GHCi prompt is
exactly the same as the syntax of a statement in a Haskell
do
expression. However, there's no monad
overloading here: statements typed at the prompt must be in the
IO
monad.
Prelude> x <- return 42 Prelude> print x 42 Prelude>
The statement x <- return 42
means
“execute return 42
in the
IO
monad, and bind the result to
x
”. We can then use
x
in future statements, for example to print
it as we did above.
If -fprint-bind-result
is set then
GHCi will print the result of a statement if and only if:
The statement is not a binding, or it is a monadic binding
(p <- e
) that binds exactly one
variable.
The variable's type is not polymorphic, is not
()
, and is an instance of
Show
Of course, you can also bind normal non-IO expressions
using the let
-statement:
Prelude> let x = 42 Prelude> x 42 Prelude>
Another important difference between the two types of binding
is that the monadic bind (p <- e
) is
strict (it evaluates e
),
whereas with the let
form, the expression
isn't evaluated immediately:
Prelude> let x = error "help!" Prelude> print x *** Exception: help! Prelude>
Note that let
bindings do not automatically
print the value bound, unlike monadic bindings.
Hint: you can also use let
-statements
to define functions at the prompt:
Prelude> let add a b = a + b Prelude> add 1 2 3 Prelude>
However, this quickly gets tedious when defining functions with multiple clauses, or groups of mutually recursive functions, because the complete definition has to be given on a single line, using explicit braces and semicolons instead of layout:
Prelude> let { f op n [] = n ; f op n (h:t) = h `op` f op n t } Prelude> f (+) 0 [1..3] 6 Prelude>
To alleviate this issue, GHCi commands can be split over
multiple lines, by wrapping them in :{
and
:}
(each on a single line of its own):
Prelude> :{ Prelude| let { g op n [] = n Prelude| ; g op n (h:t) = h `op` g op n t Prelude| } Prelude| :} Prelude> g (*) 1 [1..3] 6
Such multiline commands can be used with any GHCi command,
and the lines between :{
and
:}
are simply merged into a single line for
interpretation. That implies that each such group must form a single
valid command when merged, and that no layout rule is used.
The main purpose of multiline commands is not to replace module
loading but to make definitions in .ghci-files (see Section 2.9, “The .ghci
file”) more readable and maintainable.
Any exceptions raised during the evaluation or execution
of the statement are caught and printed by the GHCi command line
interface (for more information on exceptions, see the module
Control.Exception
in the libraries
documentation).
Every new binding shadows any existing bindings of the same name, including entities that are in scope in the current module context.
WARNING: temporary bindings introduced at the prompt only
last until the next :load
or
:reload
command, at which time they will be
simply lost. However, they do survive a change of context with
:module
: the temporary bindings just move to
the new location.
HINT: To get a list of the bindings currently in scope, use the
:show bindings
command:
Prelude> :show bindings x :: Int Prelude>
HINT: if you turn on the +t
option,
GHCi will show the type of each variable bound by a statement.
For example:
Prelude> :set +t Prelude> let (x:xs) = [1..] x :: Integer xs :: [Integer]
Apart from the :{ ... :}
syntax for
multi-line input mentioned above, GHCi also has a multiline
mode, enabled by :set +m
,
in which GHCi detects automatically when the current statement
is unfinished and allows further lines to be added. A
multi-line input is terminated with an empty line. For example:
Prelude> :set +m Prelude> let x = 42 Prelude|
Further bindings can be added to
this let
statement, so GHCi indicates that
the next line continues the previous one by changing the
prompt. Note that layout is in effect, so to add more bindings
to this let
we have to line them up:
Prelude> :set +m Prelude> let x = 42 Prelude| y = 3 Prelude| Prelude>
Explicit braces and semicolons can be used instead of layout, as usual:
Prelude> do { Prelude| putStrLn "hello" Prelude| ;putStrLn "world" Prelude| } hello world Prelude>
Note that after the closing brace, GHCi knows that the current statement is finished, so no empty line is required.
Multiline mode is useful when entering monadic
do
statements:
Control.Monad.State> flip evalStateT 0 $ do Control.Monad.State| i <- get Control.Monad.State| lift $ do Control.Monad.State| putStrLn "Hello World!" Control.Monad.State| print i Control.Monad.State| "Hello World!" 0 Control.Monad.State>
During a multiline interaction, the user can interrupt and return to the top-level prompt.
Prelude> do Prelude| putStrLn "Hello, World!" Prelude| ^C Prelude>
At the GHCi
prompt you can also enter any top-level Haskell declaration,
including data
, type
, newtype
, class
, instance
, deriving
,
and foreign
declarations. For
example:
Prelude> data T = A | B | C deriving (Eq, Ord, Show, Enum) Prelude> [A ..] [A,B,C] Prelude> :i T data T = A | B | C -- Defined at <interactive>:2:6 instance Enum T -- Defined at <interactive>:2:45 instance Eq T -- Defined at <interactive>:2:30 instance Ord T -- Defined at <interactive>:2:34 instance Show T -- Defined at <interactive>:2:39
As with ordinary variable bindings, later definitions shadow earlier ones, so you can re-enter a declaration to fix a problem with it or extend it. But there's a gotcha: when a new type declaration shadows an older one, there might be other declarations that refer to the old type. The thing to remember is that the old type still exists, and these other declarations still refer to the old type. However, while the old and the new type have the same name, GHCi will treat them as distinct. For example:
Prelude> data T = A | B Prelude> let f A = True; f B = False Prelude> data T = A | B | C Prelude> f A <interactive>:2:3: Couldn't match expected type `main::Interactive.T' with actual type `T' In the first argument of `f', namely `A' In the expression: f A In an equation for `it': it = f A Prelude>
The old, shadowed, version of T
is
displayed as main::Interactive.T
by GHCi in
an attempt to distinguish it from the new T
,
which is displayed as simply T
.
Class and type-family instance declarations are simply added to the list of available instances, with one exception. Since type-family instances are not permitted to overlap, but you might want to re-define one, a type-family instance replaces any earlier type instance with an identical left hand side. (See Section 7.7, “Type families”.)
When you type an expression at the prompt, what identifiers and types are in scope? GHCi provides a flexible way to control exactly how the context for an expression is constructed:
The :load
, :add
,
and :reload
commands (Section 2.4.5.1, “The effect of :load
on what is in scope”).
The import
declaration (Section 2.4.5.2, “Controlling what is in scope with import
”).
The :module
command (Section 2.4.5.3, “Controlling what is in scope with the :module
command”).
The command :show imports
will show a summary of which modules
contribute to the top-level scope.
Hint: GHCi will tab-complete names that are in scope; for
example, if you run GHCi and type J<tab>
then GHCi will expand it to “Just
”.
The :load
, :add
, and :reload
commands (Section 2.2, “Loading source files”
and Section 2.3, “Loading compiled code”) affect the top-level scope.
Let's start with the simple cases; when you start
GHCi the prompt looks like this:
Prelude>
which indicates that everything from the module
Prelude
is currently in scope; the visible
identifiers are exactly those that would be visible in a Haskell
source file with no import
declarations.
If we now load a file into GHCi, the prompt will change:
Prelude> :load Main.hs Compiling Main ( Main.hs, interpreted ) *Main>
The new prompt is *Main
, which
indicates that we are typing expressions in the context of the
top-level of the Main
module. Everything
that is in scope at the top-level in the module
Main
we just loaded is also in scope at the
prompt (probably including Prelude
, as long
as Main
doesn't explicitly hide it).
The syntax in the prompt
*
indicates
that it is the full top-level scope of
module
module
that is contributing to the
scope for expressions typed at the prompt. Without the
*
, just the exports of the module are
visible.
NOTE: for technical reasons, GHCi can only support the
*
-form for modules that are interpreted.
Compiled modules and package modules can only contribute their
exports to the current scope. To ensure that GHCi loads the
interpreted version of a module, add the *
when loading the module, e.g. :load *M
.
In general, after a :load
command, an automatic
import is added to the scope for the most recently loaded
"target" module, in a *
-form if possible.
For example, if you say :load foo.hs bar.hs
and bar.hs
contains module
Bar
, then the scope will be set to
*Bar
if Bar
is
interpreted, or if Bar
is compiled it will be
set to Prelude Bar
(GHCi automatically adds
Prelude
if it isn't present and there aren't
any *
-form modules). These
automatically-added imports can be seen with
:show imports
:
Prelude> :load hello.hs [1 of 1] Compiling Main ( hello.hs, interpreted ) Ok, modules loaded: Main. *Main> :show imports :module +*Main -- added automatically *Main>
and the automatically-added import is replaced the next time you
use :load
, :add
, or
:reload
. It can also be removed by
:module
as with normal imports.
We are not limited to a single module: GHCi can combine
scopes from multiple modules, in any mixture of
*
and non-*
forms. GHCi
combines the scopes from all of these modules to form the scope
that is in effect at the prompt.
To add modules to the scope, use ordinary Haskell
import
syntax:
Prelude> import System.IO Prelude System.IO> hPutStrLn stdout "hello\n" hello Prelude System.IO>
The full Haskell import syntax is supported, including
hiding
and as
clauses.
The prompt shows the modules that are currently imported, but it
omits details about hiding
,
as
, and so on. To see the full story, use
:show imports
:
Prelude> import System.IO Prelude System.IO> import Data.Map as Map Prelude System.IO Map> :show imports import Prelude -- implicit import System.IO import Data.Map as Map Prelude System.IO Map>
Note that the Prelude
import is marked
as implicit. It can be overridden with an explicit
Prelude
import, just like in a Haskell
module.
With multiple modules in scope, especially multiple
*
-form modules, it is likely that name
clashes will occur. Haskell specifies that name clashes are
only reported when an ambiguous identifier is used, and GHCi
behaves in the same way for expressions typed at the
prompt.
Another way to manipulate the scope is to use the
:module
command, whose syntax is this:
:module [+|-] [*]mod1
... [*]modn
Using the +
form of the
module
commands adds modules to the current
scope, and -
removes them. Without either
+
or -
, the current scope
is replaced by the set of modules specified. Note that if you
use this form and leave out Prelude
, an
implicit Prelude
import will be added
automatically.
The :module
command provides a way to do
two things that cannot be done with ordinary
import
declarations:
:module
supports the
*
modifier on modules, which opens the
full top-level scope of a module, rather than just its
exports.
Imports can be removed from the
context, using the syntax :module -M
.
The import
syntax is cumulative (as in a
Haskell module), so this is the only way to subtract from
the scope.
To make life slightly easier, the GHCi prompt also
behaves as if there is an implicit import
qualified
declaration for every module in every
package, and every module currently loaded into GHCi. This
behaviour can be disabled with the flag -fno-implicit-import-qualified
.
It might seem that :module
/import
and
:load
/:add
/:reload
do similar things: you can use both
to bring a module into scope. However, there is a very important
difference. GHCi is concerned with two sets of modules:
The set of modules that are currently
loaded. This set is modified by
:load
, :add
and
:reload
, and can be shown with
:show modules
.
The set of modules that are currently in
scope at the prompt. This set is modified by
import
and :module
, and
it is also modified automatically after
:load
, :add
, and
:reload
, as described above.
The set of modules in scope can be shown with
:show imports
.
You can add a module to the scope (via :module
or import
)
only if either (a) it is loaded, or
(b) it is a module from a package that GHCi knows about.
Using :module
or import
to try bring into scope a non-loaded module may result
in the message “module M is not
loaded
”.
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
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"]
Whenever an expression (or a non-binding statement, to be
precise) is typed at the prompt, GHCi implicitly binds its value
to the variable it
. For example:
Prelude> 1+2 3 Prelude> it * 2 6
What actually happens is that GHCi typechecks the
expression, and if it doesn't have an IO
type,
then it transforms it as follows: an expression
e
turns into
let it = e
;
print it
which is then run as an IO-action.
Hence, the original expression must have a type which is an
instance of the Show
class, or GHCi will
complain:
Prelude> id <interactive>:1:0: No instance for (Show (a -> a)) arising from use of `print' at <interactive>:1:0-1 Possible fix: add an instance declaration for (Show (a -> a)) In the expression: print it In a 'do' expression: print it
The error message contains some clues as to the transformation happening internally.
If the expression was instead of type IO a
for
some a
, then it
will be
bound to the result of the IO
computation,
which is of type a
. eg.:
Prelude> Time.getClockTime Wed Mar 14 12:23:13 GMT 2001 Prelude> print it Wed Mar 14 12:23:13 GMT 2001
The corresponding translation for an IO-typed
e
is
it <- e
Note that it
is shadowed by the new
value each time you evaluate a new expression, and the old value
of it
is lost.
Consider this GHCi session:
ghci> reverse []
What should GHCi do? Strictly speaking, the program is ambiguous. show (reverse [])
(which is what GHCi computes here) has type Show a => String
and how that displays depends
on the type a
. For example:
ghci> reverse ([] :: String) "" ghci> reverse ([] :: [Int]) []
However, it is tiresome for the user to have to specify the type, so GHCi extends Haskell's type-defaulting
rules (Section 4.3.4 of the Haskell 2010 Report) as follows. The
standard rules take each group of constraints (C1 a, C2 a, ..., Cn
a)
for each type variable a
, and defaults the
type variable if
The type variable a
appears in no
other constraints
All the classes Ci
are standard.
At least one of the classes Ci
is
numeric.
At the GHCi prompt, or with GHC if the
-XExtendedDefaultRules
flag is given,
the following additional differences apply:
Rule 2 above is relaxed thus:
All of the classes
Ci
are single-parameter type classes.
Rule 3 above is relaxed this:
At least one of the classes Ci
is
numeric, or is Show
,
Eq
, or
Ord
.
The unit type ()
is added to the
start of the standard list of types which are tried when
doing type defaulting.
The last point means that, for example, this program:
main :: IO () main = print def instance Num () def :: (Num a, Enum a) => a def = toEnum 0
prints ()
rather than 0
as the
type is defaulted to ()
rather than
Integer
.
The motivation for the change is that it means IO a
actions default to IO ()
, which in turn means that
ghci won't try to print a result when running them. This is
particularly important for printf
, which has an
instance that returns IO a
.
However, it is only able to return
undefined
(the reason for the instance having this type is so that printf
doesn't require extensions to the class system), so if the type defaults to
Integer
then ghci gives an error when running a
printf.
See also Section 2.4.1, “I/O actions at the prompt” for how the monad of a computational
expression defaults to IO
if possible.
[New in version 7.6.1]
By default, GHCi prints the result of expressions typed at the prompt
using the function System.IO.print
. Its type
signature is Show a => a -> IO ()
, and it works by
converting the value to String
using
show
.
This is not ideal in certain cases, like when the output is long, or contains strings with non-ascii characters.
The -interactive-print
flag allows to specify any
function of type C a => a -> IO ()
, for some
constraint C
, as the function for printing evaluated
expressions. The function can reside in any loaded module or any
registered package.
As an example, suppose we have following special printing module:
module SpecPrinter where import System.IO sprint a = putStrLn $ show a ++ "!"
The sprint
function adds an exclamation mark at the
end of any printed value. Running GHCi with the command:
ghci -interactive-print=SpecPrinter.sprinter SpecPrinter
will start an interactive session where values with be printed using
sprint
:
*SpecPrinter> [1,2,3] [1,2,3]! *SpecPrinter> 42 42!
A custom pretty printing function can be used, for example, to format tree-like and nested structures in a more readable way.
The -interactive-print
flag can also be used when
running GHC in -e mode
:
% ghc -e "[1,2,3]" -interactive-print=SpecPrinter.sprint SpecPrinter [1,2,3]!