GHC/GHCi

From HaskellWiki
Jump to navigation Jump to search

Introduction

GHCi is GHC's interactive environment, in which Haskell expressions can be interactively evaluated and programs can be interpreted. The GHC User's Guide contains more fundamental and detailed information about GHCi.

This page is a place to collect advice about how to use GHCi beyond what User's Guide covers. Please add to it!

Advanced customization

Using .ghci, a mini-tutorial

There is a lot more one can do to customize and extend GHCi. Some extended examples can be found in an email posted to haskell-cafe, titled getting more out of ghci. Dating from September 2007, and using GHC 6.6.1, some of the GHCi tickets mentioned in there have since been fixed, but the message should still serve as a useful introduction to writing your own .ghci files. It also provides several useful commands you might want to copy into your own file!-) Newer GHCis support the multiline commands mentioned in the message, allowing for more readable .ghci files (at the time, definitions had to be squashed into single lines, so you have to read the message to understand the `.ghci` file). For those still using older GHCis, a variant file for 6.4.1 is available, too:

Customized GHCi interactive environments

You can create shell commands that start up GHCi and initialize it for use as a specialized interactive computing environment for any purpose that you can imagine.

The idea is that if you put the following lines in your .ghci file, GHCi will load commands at startup from whatever file whose path you specify in the GHCIRC environment variable. You can then easily write shell scripts that exploit this to initialize GHCi in any manner you please.

-- Read GHCI commands from the file whose name is
-- in the GHCIRC environment variable
:def _load const(System.Environment.getEnvironment>>=maybe(return"")readFile.lookup"GHCIRC")
:_load
:undef _load

External tool integration

Hoogle

External command-line tools like Hoogle can be integrated in GHCi by adding a line to .ghci similar to

:def hoogle \str -> return $ ":! hoogle --count=15 \"" ++ str ++ "\""

Make sure that the directory containing the executable is in your PATH environment variable or modify the line to point directly to the executable. Invoke the executable with commands like

:hoogle map

Hlint

Hlint can be similarly integrated. It is much more complex, however, as one must acquire the filename to run hlint on:

-- <http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/dot-squashed.ghci641>
let { redir varcmd = case break Data.Char.isSpace varcmd of { (var,_:cmd) -> return $ unlines [":set -fno-print-bind-result","tmp <- System.Directory.getTemporaryDirectory","(f,h) <- System.IO.openTempFile tmp \"ghci\"","sto <- GHC.Handle.hDuplicate System.IO.stdout","GHC.Handle.hDuplicateTo h System.IO.stdout","System.IO.hClose h",cmd,"GHC.Handle.hDuplicateTo sto System.IO.stdout","let readFileNow f = readFile f >>= \\t->length t `seq` return t",var++" <- readFileNow f","System.Directory.removeFile f"]; _ -> return "putStrLn \"usage: :redir <var> <cmd>\"" } }
:def redir redir
-- End copied material

-- Integration with the hlint code style tool
let hlint _ = return $ unlines [":set -w",    ":redir hlintvar1 :show modules", ":cmd return (\":! hlint \" ++ (concat $ Data.List.intersperse \" \" (map (fst . break (==',') . drop 2 . snd . break (== '(')) $ lines hlintvar1)))",    ":set -Wall"]
:def hlint hlint

(There may be a more up-to-date version in the hlint darcs repo.)

Package and documentation lookup

Ever tried to find the users guide for the version of GHCi you are currently running? Or information about the packages installed for it? The new ghc-paths package makes such tasks easier by exporting a GHC.Paths module:

Prelude> :browse GHC.Paths
docdir :: FilePath
ghc :: FilePath
ghc_pkg :: FilePath
libdir :: FilePath

We can define some auxiliary commands to make this more comfortable:

:ghc_pkg cmds           -- run ghc-pkg commands
:browser url            -- start browser with url
:doc [relative]         -- open docs, with optional relative path
:users_guide [relative] -- open users guide, with optional relative path
So,
:ghc_pkg list
will list the packages for the current GHCi instance,
:ghc_pkg find-module Text.Regex
will tell us what package that module is in, etc.
:doc
will open a browser window on the documentation for this GHCi version,
:doc /Cabal/index.html
takes us to the Cabal docs, and
:users_guide /flag-reference.html
takes us to the flag reference, all matching the version of GHCi we're in, provided that the docs and ghc-paths are installed.

Here are the definitions - adapt to your preferences (note that the construction of the documentation path from libdir and docdir is slightly dodgy):

:def ghc_pkg (\l->return $ ":!"++GHC.Paths.ghc_pkg++" "++l)

:def browser (\l->return $ ":!c:/Progra~1/Opera/Opera.exe "++l)

let doc p = return $ ":browser "++GHC.Paths.libdir++dropWhile (/='/')GHC.Paths.docdir++relative where { relative = if p=="" then "/index.html" else p }
:def doc doc

let users_guide p = doc ("/users_guide"++if null p then "/index.html" else p)
:def users_guide users_guide

GHCi on Acid

GHCi on Acid is an extension to GHCi (Interactive GHC) for adding useful lambdabot features. It does pretty much anything lambadabot does, just nicely embedded inside your GHCi.

Features

Here are some examples of the commands that can be used.

The :instances command shows all the instances of a class:

GOA> :instances Monad
((->) r), ArrowMonad a, Cont r, ContT r m, Either e, ErrorT e m, IO, Maybe, RWS r w s, RWST r w s m, Reader r, ReaderT r m, ST s, State s, StateT s m, Writer w, WriterT w m, []
GOA> :instances Arrow
(->), Kleisli m
GOA> :instances Num
Double, Float, Int, Integer

Here we have the :hoogle command, for querying the Hoogle database. Great for looking for functions of a specific type:

GOA> :hoogle Arrow
Control.Arrow :: module
Control.Arrow.Arrow :: class Arrow a
Control.Arrow.ArrowZero :: class Arrow a => ArrowZero a
GOA> :hoogle b -> (a -> b) -> Maybe a -> b
Prelude.maybe :: b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe :: b -> (a -> b) -> Maybe a -> b

The :source command gives a link to the source code of a module (sometimes you are curious):

GOA> :source Data.Maybe
http://darcs.haskell.org/packages/base/Data/Maybe.hs

Similarly, :docs gives a link to the documentation of a module.

GOA> :docs Data.Maybe
http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Maybe.html

The :index command is a nice way to search modules.

GOA> :index Monad
Control.Monad, Prelude, Control.Monad.Reader, Control.Monad.Writer, Control.Monad.State, Control.Monad.RWS, Control.Monad.Identity, Control.Monad.Cont, Control.Monad.Error, Control.Monad.List

Then we have :pl, which shows the pointless (or: point-free) way of writing a function, which is very useful for learning and sometimes for fun:

GOA> :pl (\x -> x * x)
join (*)
GOA> :pl (\x y -> (x * 5) + (y * 5))
(. (5 *)) . (+) . (5 *)

How to install

 $ cabal install lamdabot
 $ cabal install goa

Then edit your .ghci to look like the following:

:m - Prelude
:m + GOA
setLambdabotHome "/home/chris/.cabal/bin"
:def bs        lambdabot "botsnack"
:def pl        lambdabot "pl"
:def unpl      lambdabot "unpl"
:def redo      lambdabot "redo"
:def undo      lambdabot "undo"
:def index     lambdabot "index"
:def docs      lambdabot "docs"
:def instances lambdabot "instances"
:def hoogle    lambdabot "hoogle"
:def source    lambdabot "fptools"
:def where     lambdabot "where"
:def version   lambdabot "version"
:def src       lambdabot "src"

And you should be able to do this:

chris@chrisamilo:~$ ghci
GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Loading package syb ... linking ... done.
Loading package base-3.0.3.1 ... linking ... done.
Loading package old-locale-1.0.0.1 ... linking ... done.
Loading package old-time-1.0.0.2 ... linking ... done.
Loading package filepath-1.1.0.2 ... linking ... done.
Loading package unix-2.3.2.0 ... linking ... done.
Loading package directory-1.0.0.3 ... linking ... done.
Loading package process-1.0.1.1 ... linking ... done.
Loading package goa-3.0.2 ... linking ... done.
GOA> :src foldr
src foldr
foldr f z []     = z
foldr f z (x:xs) = f x (foldr f z xs)
GOA> 

Tip: if you accidentally unload the GOA module, use :m + GOA to load it.

Frequently Asked Questions (FAQ)

How do I stop GHCi from printing the result of a bind statement?

Sometimes you want to perform an IO action at the prompt that will produce a lot of data (e.g. reading a large file). When you try to do this, GHCi will helpfully spew this data all over your terminal, making the console temporarily unavailable.

To prevent this, use :set -fno-print-bind-result. If you want this option to be permanently set, add it to your .ghci file.

Additional command advice

The :def command

The :def command, documented here, allows quite GHCi's commands to be extended in quite a powerful way.

Here is one example.

 Prelude> let loop = do { l <- getLine; if l == "\^D" then return () else do appendFile "foo.hs" (l++"\n"); loop }
 Prelude> :def pasteCode (\_ -> loop >> return ":load foo.hs")

This defines a new command :pasteCode, which allows you to paste Haskell code directly into GHCi. You type the command :pasteCode, followed by the code you want, followed by ^D, followed (unfortunately) by enter, and your code is executed. Thus:

 Prelude> :pasteCode
 x = 42
 ^D
 Compiling Main             ( foo.hs, interpreted )
 Ok, modules loaded: Main.
 *Main> x
 42
 *Main>

Compatibility/shell/platform integration

Readline/editline

There are some tricks to getting readline/editline to work as expected with GHCi.

A readline-aware GHCi on Windows

Mauricio reports: I've just uploaded a package (rlwrap) to Cygwin that I like to use with ghci. You can use it like this:

  rlwrap ghcii.sh

and then you will use ghc as if it were readline aware (i.e., you can press up arrow to get last typed lines etc.). rlwrap is very stable and I never had unexpected results while using it.

Since the issue of ghci integration with terminals has been raised here sometimes, I thought some guys here would be interested (actually, I found rlwrap looking for a better way to use ghci).

rlwrap (for GHCI compiled without readline/editline)

GHCi has support for session-specific command-line completion, but only if it was built with the readline or editline package, and some versions of GHCi aren't. In such cases, you can try rlwrap (readline wrapper) to attach readline "from the outside", which isn't as specific, but gives basic completion support. In particular, there's an rlwrap package for Cygwin.

For starters,

 rlwrap -cr ghci

gives you filename completion, and completion wrt to previous input/output in your GHCi session (so if a GHCi error message suggests to set AnnoyinglyLongVerySpecificOption, that will be available for completion;-).

If you want to get more specific, you need to supply files with possible completions - flags and modules spring to mind, but where to get those?

1. extracting a list of options from the flag-reference in the users guide:

  cat /cygdrive/c/ghc/ghc-6.9.20080514/doc/users_guide/flag-reference.html
    | sed 's/</\n</g' 
    | sed '/<code class="option">/!d;s/<code class="option">\(.*\)$/\1/'
    > options.txt
  actually, we only want the dynamic or :setable options, and no duplicates, so:
  cat /cygdrive/c/ghc/ghc-6.9.20080514/doc/users_guide/flag-reference.html 
    | sed 's/<tr/\n<tr/g' 
    | grep '<code class="option".*>\(dynamic\|:set\)<' 
    | sed 's/^.*<code class="option">\([^<]*\)<.*$/\1/' 
    | uniq
    > options.txt

2. extracting a list of modules from ghc-pkg:

 ghc-pkg  field '*' exposed-modules | sed 's/exposed-modules: //; s/^\s\+//g' >modules.txt

And now,

 rlwrap -cr -f modules.txt -f options.txt ghcii.sh

will give you completion wrt filenames, options, module names, and previous session contents, as well as the usual readline goodies, like history search and editing. The main drawback is that the completion is neither session nor context-specific, so it will suggest filenames where module names are expected, it will suggest module names that may not be exposed, etc.