[[project @ 2001-03-15 16:16:24 by simonmar]
simonmar**20010315161624
nearly finished GHCi docs.
] {
hunk ./ghc/docs/users_guide/ghci.sgml 3
+ GHCi
+ interpreter
hunk ./ghc/docs/users_guide/ghci.sgml 6
- ToDo
+ GHCi
+ The ‘i’ stands for “Interactive”
+
+ is GHC's interactive environment, in which Haskell expressions can
+ be interactively evaluated and programs can be interpreted. If
+ you're famililar with HugsHugs
+ , then you'll be right at home with GHCi. However, GHCi
+ also has support for interactively loading compiled code, as well as
+ supporting allexcept the FFI, at the moment
+ the language extensions that GHC provides.
+
+
+ Introduction to GHCi
+
+ Let's start with an example GHCi session. You can fire up
+ GHCi with the command ghci:
+
+
+$ ghci
+ ___ ___ _
+ / _ \ /\ /\/ __(_)
+ / /_\// /_/ / / | | GHC Interactive, version 4.11, For Haskell 98.
+/ /_\\/ __ / /___| | http://www.haskell.org/ghc/
+\____/\/ /_/\____/|_| Type :? for help.
+
+Loading package std ... linking ... done.
+Prelude>
+
+
+ There may be a short pause while GHCi loads the prelude and
+ standard libraries, after which the prompt is shown. If we follow
+ the instructions and type :? for help, we
+ get:
+
+
+ Commands available from the prompt:
+ <stmt> evaluate/run <stmt>
+ :cd <dir> change directory to <dir>
+ :def <cmd> <expr> define a macro :<cmd>
+ :help, :? display this list of commands
+ :load <filename> load a module (and it dependents)
+ :module <mod> set the context for expression evaluation to <mod>
+ :reload reload the current module set
+ :set <option> ... set options
+ :type <expr> show the type of <expr>
+ :unset <option> ... unset options
+ :quit exit GHCi
+ :!<command> run the shell command <command>
+ Options for `:set' and `:unset':
+ +r revert top-level expressions after each evaluation
+ +s print timing/memory stats after each evaluation
+ +t print type after evaluation
+ -<flag> most GHC command line flags can also be set here
+ (eg. -v2, -fglasgow-exts, etc.)
+
+
+ We'll explain most of these commands as we go along. For
+ Hugs users: many things work the same as in Hugs, so you should be
+ able to get going straight away.
+
+ Haskell expressions can be typed at the prompt:
+ promptGHCi
+
+
+
+Prelude> 1+2
+3
+PrePrelude> let x = 42 in x / 9
+4.666666666666667
+Prelude>
+
+
+ GHCi interprets the whole line as an expression to evaluate.
+ The expression may not span several lines - as soon as you press
+ enter, GHCi will attempt to evaluate it.
+
+
+
+ Loading source files
+
+ Suppose we have the following Haskell source code, which we
+ place in a file Main.hs in the current
+ directory:
+
+
+main = print (fac 20)
+
+fac 0 = 1
+fac n = n * fac (n-1)
+
+
+ To load a Haskell source file into GHCi, use the
+ :load command:
+
+
+Prelude> :load Main
+Compiling Main ( Main.hs, interpreted )
+Ok, modules loaded: Main.
+Main>
+
+
+ GHCi has loaded the Main module, and the
+ prompt has changed to “Main>” to
+ indicate that the current context for expressions typed at the
+ prompt is the Main module we just
+ loaded. So we can now type expressions involving the functions
+ from Main.hs:
+
+
+Main> fac 17
+355687428096000
+
+
+ Loading a multi-module program is just as straightforward;
+ just give the name of the “topmost” module to the
+ :load command (hint: :load
+ can be abbreviated to :l). The topmost module
+ will normally be Main, but it doesn't have to
+ be. GHCi will discover which modules are required, directly or
+ indirectly, by the topmost module, and load them all in dependency
+ order.
+
+
+ Modules vs. filenames
+
+ Question: How does GHC find the filename which contains
+ module M? Answer: it looks for the
+ file M.hs, or
+ M.lhs. This means
+ that for most modules, the module name must match the filename.
+ If it doesn't, GHCi won't be able to find it.
+
+ There is one exception to this general rule: when you load
+ a program with :load, or specify it when you
+ invoke ghci, you can give a filename rather
+ than a module name. This filename is loaded if it exists, and
+ it may contain any module you like. This is particularly
+ convenient if you have several Main modules
+ in the same directory and you can't call them all
+ Main.hs.
+
+ One final note: if you load a module called Main, it must
+ contain a main function, just like in
+ GHC.
+
+
+
+ Making changes and recompilation
+
+ If you make some changes to the source code and want GHCi
+ to recompile the program, give the :reload
+ command. The program will be recompiled as necessary, with GHCi
+ doing its best to avoid actually recompiling modules if their
+ external dependencies haven't changed. This is the same
+ mechanism we use to avoid re-compiling modules in the batch
+ compilation setting (see ).
+
+
+
+
+ Loading compiled code
+
+ When you load a Haskell source module into GHCi, it is
+ normally converted to byte-code and run using the interpreter.
+ However, interpreted code can also run alongside compiled code in
+ GHCi; indeed, normally when GHCi starts, it loads up a compiled
+ copy of package std, which contains the Prelude
+ and standard libraries.
+
+ Why should we want to run compiled code? Well, compiled
+ code is roughly 10x faster than interpreted code, but takes about
+ 2x longer to produce (perhaps longer if optimisation is on). So
+ it pays to compile the parts of a program that aren't changing
+ very often, and use the interpreter for the code being actively
+ developed.
+
+ When loading up source files with :load,
+ GHCi looks for any corresponding compiled object files, and will
+ use one in preference to interpreting the source if possible. For
+ example, suppose we have a 4-module program consisting of modules
+ A, B, C, and D. Modules B and C both import D only,
+ and A imports both B & C:
+
+ A
+ / \
+ B C
+ \ /
+ D
+
+ We can compile D, then load the whole program, like this:
+
+Prelude> :! ghc -c D.hs
+Prelude> :load A
+Skipping D ( D.hs, D.o )
+Compiling C ( C.hs, interpreted )
+Compiling B ( B.hs, interpreted )
+Compiling A ( A.hs, interpreted )
+Ok, modules loaded: A, B, C, D.
+Main>
+
+
+ In the messages from the compiler, we see that it skipped D,
+ and used the object file D.o. The message
+ Skippingmodule
+ indicates that compilation for module
+ isn't necessary, because the source and everything it depends on
+ is unchanged since the last compilation.
+
+ If we now modify the source of D (or pretend to: using Unix
+ command touch on the source file is handy for
+ this), the compiler will no longer be able to use the object file,
+ because it might be out of date:
+
+
+Main> :! touch D.hs
+Main> :reload
+Compiling D ( D.hs, interpreted )
+Skipping C ( C.hs, interpreted )
+Skipping B ( B.hs, interpreted )
+Skipping A ( A.hs, interpreted )
+Ok, modules loaded: A, B, C, D.
+Main>
+
+
+ Note that module D was compiled, but in this instance
+ because its source hadn't really changed, its interface remained
+ the same, and the recompilation checker determined that A, B and C
+ didn't need to be recompiled.
+
+ So let's try compiling one of the other modules:
+
+
+Main> :! ghc -c C.hs
+Main> :load A
+Compiling D ( D.hs, interpreted )
+Compiling C ( C.hs, interpreted )
+Compiling B ( B.hs, interpreted )
+Compiling A ( A.hs, interpreted )
+Ok, modules loaded: A, B, C, D.
+
+
+ We didn't get the compiled version of C! What happened?
+ Well, in GHCi a compiled module may only depend on other compiled
+ modules, and in this case C depends on D, which doesn't have an
+ object file, so GHCi also rejected C's object file. Ok, so let's
+ also compile D:
+
+
+Main> :! ghc -c D.hs
+Main> :reload
+Ok, modules loaded: A, B, C, D.
+
+
+ Nothing happened! Here's another lesson: newly compiled
+ modules aren't picked up by :reload, only
+ :load:
+
+
+Main> :load A
+Skipping D ( D.hs, D.o )
+Skipping C ( C.hs, C.o )
+Compiling B ( B.hs, interpreted )
+Compiling A ( A.hs, interpreted )
+Ok, modules loaded: A, B, C, D.
+
+
+ HINT: since GHCi will only use a compiled object file if it
+ can sure that the compiled version is up-to-date, a good technique
+ when working on a large program is to occasionally run
+ ghc --make to compile the whole project (say
+ before you go for lunch :-), then continue working in the
+ interpreter. As you modify code, the new modules will be
+ interpreted, but the rest of the project will remain
+ compiled.
+
+
+
+
+ Interactive evaluation at the prompt
+
+ When you type an expression at the prompt, GHCi immediately
+ evaluates and prints the result. But that's not the whole story:
+ if you type something of type IO a for some
+ a, then GHCi executes it
+ as an IO-computation, and doesn't attempt to print the
+ result:.
+
+
+Prelude> "hello"
+"hello"
+Prelude> putStrLn "hello"
+hello
+
+
+ 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 in print it. It then runs
+ the new expression 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
+No instance for `Show (a -> a)'
+arising from use of `print'
+in a `do' expression pattern binding: print it
+
+
+ The error message contains some clues as to the
+ transformation happening internally.
+
+
+ What's really in scope at the prompt?
+
+ When you type an expression at the prompt, what
+ identifiers and types are in scope? GHCi has a concept of a
+ context module, which can be set using
+ the :module command.
+
+ The context module is shown in the prompt: for example,
+ the prompt Prelude> indicates that the
+ current context for evaluating expressions is the Haskell
+ Prelude module. This is the default context
+ when you start up GHCi.
+ Prelude
+
+ Exactly which entities are in scope in a given context
+ depends on whether the context module is compiled or
+ interpreted:
+
+
+
+ If the context module is interpreted, then everything
+ that was in scope during compilation of that module is also
+ in scope at the prompt, i.e. all the imports and any
+ top-level functions, types and classes defined in that
+ module.
+
+
+
+ If the context module comes from a package, or is
+ otherwise compiled, then only the exports of that module are
+ in scope at the prompt. So for example, when the current
+ context module is Prelude, everything the
+ Prelude exports is in scope, but if we
+ switch context to eg. Time, then
+ everything from the Prelude is now
+ invisible.
+
+
+
+ The reason for this unfortunate distinction is boring: for
+ a compiled module when the source isn't available, the compiler
+ has no way of knowing what was in scope when the module was
+ compiled (and we don't store this information in the interface
+ file). However, in practice it shouldn't be a problem: if you
+ want both Time and Prelude
+ in scope at the same time, just create a file containing the
+ line import Time and load it into
+ GHCi.
+
+ 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. So in the above example where the
+ Prelude was invisible, we can always get at
+ Prelude identifiers by qualifying them, eg.
+ Prelude.map.
+
+
+
+ Using do-notation at the prompt
+
+ 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.
+
+ Here's an example:
+
+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.
+
+ Of course, you can also bind normal non-IO expressions
+ using the let-statement:
+
+Prelude> let x = 42
+Prelude> print x
+42
+Prelude>
+
+ An 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>
+
+ Any exceptions raised during the evaluation or execution
+ of the statement are caught and printed by the GHCi command line
+ interface (see for more
+ information on GHC's Exception support).
+
+ 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: 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]
+
+
+
+
+
+ The it variable
+ it
+
+
+ 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
+
+
+ If the expression was 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
+Prelude> print it
+Wed Mar 14 12:23:13 GMT 2001
+
+
+ Note that it is shadowed by the new
+ value each time you evaluate a new expression, and the old value
+ of it is lost.
+
+
+
+
+
+ Invoking GHCi
+
+ GHCi is invoked with the command ghci or
+ ghc --interactive. A module or filename can
+ also be specified on the command line; this instructs GHCi to load
+ the that module or filename (and all the modules it depends on),
+ just as if you had said
+ :load module at the GHCi prompt
+ (see ). For example, to start GHCi
+ and load the program whose topmost module is in the file
+ Main.hs, we could say:
+
+
+$ ghci Main.hs
+
+
+ Note: only one module name or filename
+ may be given on the command line.
+
+ Most of the command-line options accepted by GHC (see ) also make sense in interactive mode. The ones
+ that don't make sense are mostly obvious; for example, GHCi
+ doesn't generate interface files, so options related to interface
+ file generation won't have any effect.
+
+
+ Packages
+
+ GHCi can make use of all the packages that come with GHC,
+ but note: packages must be specified on the
+ GHCi command line, you can't add extra packages after GHCi has
+ started up. For example, to start up GHCi with the
+ text package loaded:
+
+
+$ ghci -package text
+ ___ ___ _
+ / _ \ /\ /\/ __(_)
+ / /_\// /_/ / / | | GHC Interactive, version 4.11, For Haskell 98.
+/ /_\\/ __ / /___| | http://www.haskell.org/ghc/
+\____/\/ /_/\____/|_| Type :? for help.
+
+Loading package std ... linking ... done.
+Loading package lang ... linking ... done.
+Loading package text ... linking ... done.
+Prelude>
+
+
+ Note that GHCi also loaded the lang
+ package even though we didn't ask for it: that's because the
+ text package makes use of one or more of the
+ modules in lang, and therefore has a
+ dependency on it.
+
+
+
+ Extra libraries
+
+ Extra libraries may be specified on the command line using
+ the normal -llib
+ option. For example, to load the “m” library:
+
+
+$ ghci -lm
+
+
+ On systems with .so-style shared
+ libraries, the actual library loaded will the
+ liblib.so. If
+ no such library exists on the standard library search path,
+ including paths given using
+ -Lpath, then
+ ghci will signal an error.
+
+ On systems with .dll-style shared
+ libraries, the actual library loaded will be
+ lib.dll. Again,
+ GHCi will signal an error if it can't find the library.
+
+
+
+
+
+ GHCi commands
+
+ GHCi commands all begin with
+ ‘:’ and consist of a single command
+ name followed by zero or more parameters. The command name may be
+ abbreviated, as long as the abbreviation is not ambiguous. All of
+ the builtin commands, with the exception of
+ :unset and :undef, may be
+ abbreviated to a single letter.
+
+
+
+ :cddir
+
+ 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.
+
+
+
+
+ :def
+
+ ToDo.
+
+
+
+
+ :help
+ :?
+
+ Displays a list of the available commands.
+
+
+
+
+ :loadmodule
+
+ Recursively loads module
+ (which may be a module name or filename), and all the
+ modules it depends on. All previously loaded modules are
+ forgotten. The module module is
+ known as the target.
+
+
+
+
+ :modulemodule
+
+ Sets the current context for statements typed at the
+ prompt to module, which must be a
+ module name which is already loaded or in a package. See
+ for more information on what
+ effect the context has on what entities are in scope at the
+ prompt.
+
+
+
+
+ :quitmodule
+
+ Quits GHCi. You can also quit by typing a control-D
+ at the prompt.
+
+
+
+
+ :reload
+
+ Attempts to reload the current target (see
+ :load) if it, or any module it depends
+ on, has changed. Note that this may entail loading new
+ modules, or even dropping modules which are no longer
+ indirectly required by the target.
+
+
+
+
+ :setoption...
+
+ Sets various options. See
+ for a list of available options. The
+ :set command by itself shows which
+ options are currently set.
+
+
+
+
+ :typeexpression
+
+ 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.
+
+
+
+
+ :unsetoption...
+
+ Unsets certain options. See
+ for a list of available options.
+
+
+
+
+ :!command...
+
+ Executes the shell command
+ command.
+
+
+
+
+
+
+
+ The :set command
+
+ The :set command sets two types of
+ options: GHCi options, which begin with
+ ‘+” and “command-line”
+ options, which begin with ‘-’. Either type of option
+ may be set using :set and unset using
+ :unset.
+
+ The available GHCi options are:
+
+
+
+ +r
+
+ Normally, any evaluation of top-level expressions
+ (otherwise known as CAFs or Constant Applicative Forms) in
+ loaded modules is retained between evaluations. Turning on
+ +r causes all evaluation of top-level
+ expressions to be discarded after each evaluation (they are
+ still retained during a single
+ evaluation).
+
+ This option may help if the evaluated top-level
+ expressions are consuming large amounts of space, or if you
+ need repeatable performance measurements.
+
+
+
+
+ +s
+
+ Display some stats after evaluating each expression,
+ including the elapsed time and number of bytes allocated.
+ NOTE: the allocation figure is only accurate to the size of
+ the storage manager's allocation area, because it is
+ calculated at every GC. Hence, you might see values of zero
+ if no GC has occurred.
+
+
+
+
+ +t
+
+ Display the type of each variable bound after a
+ statement is entered at the prompt. If the statement is a
+ single expression, then the only variable binding will be
+ for the variable ‘it’.
+
+
+
+
+ In addition, any normal GHC command-line option that is
+ designated as dynamic (see the table in
+ ), may be set using
+ :set. Certain static options
+ (, , and
+ in particular) will also work, but may not take effect until the
+ next reload.
+
+
+
+ The .ghci file
+ .ghcifile
+
+ startupfiles, GHCi
+
+
+ When it starts, GHCi always reads and executes commands from
+ $HOME/.ghci, followed by
+ ./.ghci.
+
+ The .ghci in your home directory is
+ most useful for turning on favourite options (eg. :set
+ +s), and defining useful macros. Placing a
+ .ghci file in a directory with a Haskell
+ project is a useful way to set certain project-wide options so you
+ don't have to type them everytime you start GHCi: eg. if your
+ project uses GHC extensions and CPP, and has source files in three
+ subdirectories A B and C, you might put the following lines in
+ .ghci:
+
+
+:set -fglasgow-exts -cpp
+:set -iA:B:C
+
+
+ (Note that strictly speaking the flag is
+ a static one, but in fact it works to set it using
+ :set like this. The changes won't take effect
+ until the next :load, though.)
+
+
+
+ FAQ and Things To Watch Out For
+
+
+
+ System.exit causes GHCi to exit!
+
+ Yes, it does.
+
+
+
+
+ System.getArgs returns GHCi's command
+ line arguments!
+
+ Yes, it does.
+
+
+
+
+ The interpreter can't load modules with FFI
+ declarations!
+
+ Unfortunately not. We haven't implemented it yet.
+ Please compile any offending modules by hand before loading
+ them into GHCi.
+
+
+
+
+ Hugs has a :add command for adding
+ modules without throwing away any that are already loaded.
+ Why doesn't this work in GHCi?
+
+ We haven't implemented it yet. Sorry about that.
+
+
+
+
+ -O doesn't work with GHCi!
+
+
+
+ For technical reasons, the bytecode compiler doesn't
+ interact well with one of the optimisation passes, so we
+ have disabled optimisation when using the interpreter. This
+ isn't a great loss: you'll get a much bigger win by
+ compiling the bits of your code that need to go fast, rather
+ than interpreting them with optimisation turned on.
+
+
+
+
+ Unboxed tuples don't work with GHCi
+
+ That's right. You can always compile a module that
+ uses unboxed tuples and load it into GHCi, however.
+ (Incidentally the previous point, namely that
+ -O is incompatible with GHCi, is because
+ the bytecode compiler can't deal with unboxed
+ tuples).
+
+
+
+
+ Concurrent threads don't carry on running when GHCi is
+ waiting for input.
+
+ No, they don't. This is because the Haskell binding
+ to the GNU readline library doesn't support reading from the
+ terminal in a non-blocking way, which is required to work
+ properly with GHC's concurrency model.
+
+
+
+
+
+
}