Fix catching exit exceptions in ghc -e
[ghc-hetmet.git] / compiler / ghci / InteractiveUI.hs
1 {-# OPTIONS -#include "Linker.h" #-}
2 -----------------------------------------------------------------------------
3 --
4 -- GHC Interactive User Interface
5 --
6 -- (c) The GHC Team 2005-2006
7 --
8 -----------------------------------------------------------------------------
9
10 module InteractiveUI ( interactiveUI, ghciWelcomeMsg ) where
11
12 #include "HsVersions.h"
13
14 import GhciMonad
15 import GhciTags
16 import Debugger
17
18 -- The GHC interface
19 import qualified GHC
20 import GHC              ( Session, LoadHowMuch(..), Target(..),  TargetId(..),
21                           Module, ModuleName, TyThing(..), Phase,
22                           BreakIndex, SrcSpan, Resume, SingleStep )
23 import PprTyThing
24 import DynFlags
25
26 import Packages
27 #ifdef USE_READLINE
28 import PackageConfig
29 import UniqFM
30 #endif
31
32 import HscTypes         ( implicitTyThings )
33 import qualified RdrName ( getGRE_NameQualifier_maybes ) -- should this come via GHC?
34 import Outputable       hiding (printForUser, printForUserPartWay)
35 import Module           -- for ModuleEnv
36 import Name
37 import SrcLoc
38
39 -- Other random utilities
40 import Digraph
41 import BasicTypes hiding (isTopLevel)
42 import Panic      hiding (showException)
43 import Config
44 import StaticFlags
45 import Linker
46 import Util
47 import NameSet
48 import Maybes           ( orElse )
49 import FastString
50 import Encoding
51
52 #ifndef mingw32_HOST_OS
53 import System.Posix hiding (getEnv)
54 #else
55 import GHC.ConsoleHandler ( flushConsole )
56 import qualified System.Win32
57 import System.FilePath
58 #endif
59
60 #ifdef USE_READLINE
61 import Control.Concurrent       ( yield )       -- Used in readline loop
62 import System.Console.Readline as Readline
63 #endif
64
65 --import SystemExts
66
67 import Control.Exception as Exception
68 -- import Control.Concurrent
69
70 import qualified Data.ByteString.Char8 as BS
71 import Data.List
72 import Data.Maybe
73 import System.Cmd
74 import System.Environment
75 import System.Exit      ( exitWith, ExitCode(..) )
76 import System.Directory
77 import System.IO
78 import System.IO.Error as IO
79 import Data.Char
80 import Data.Dynamic
81 import Data.Array
82 import Control.Monad as Monad
83 import Text.Printf
84 import Foreign
85 import Foreign.C        ( withCStringLen )
86 import GHC.Exts         ( unsafeCoerce# )
87 import GHC.IOBase       ( IOErrorType(InvalidArgument) )
88
89 import Data.IORef       ( IORef, readIORef, writeIORef )
90
91 #ifdef USE_READLINE
92 import System.Posix.Internals ( setNonBlockingFD )
93 #endif
94
95 -----------------------------------------------------------------------------
96
97 ghciWelcomeMsg :: String
98 ghciWelcomeMsg = "GHCi, version " ++ cProjectVersion ++
99                  ": http://www.haskell.org/ghc/  :? for help"
100
101 cmdName :: Command -> String
102 cmdName (n,_,_,_) = n
103
104 macros_ref :: IORef [Command]
105 GLOBAL_VAR(macros_ref, [], [Command])
106
107 builtin_commands :: [Command]
108 builtin_commands = [
109         -- Hugs users are accustomed to :e, so make sure it doesn't overlap
110   ("?",         keepGoing help,                 Nothing, completeNone),
111   ("add",       keepGoingPaths addModule,       Just filenameWordBreakChars, completeFilename),
112   ("abandon",   keepGoing abandonCmd,           Nothing, completeNone),
113   ("break",     keepGoing breakCmd,             Nothing, completeIdentifier),
114   ("back",      keepGoing backCmd,              Nothing, completeNone),
115   ("browse",    keepGoing (browseCmd False),    Nothing, completeModule),
116   ("browse!",   keepGoing (browseCmd True),     Nothing, completeModule),
117   ("cd",        keepGoing changeDirectory,      Just filenameWordBreakChars, completeFilename),
118   ("check",     keepGoing checkModule,          Nothing, completeHomeModule),
119   ("continue",  keepGoing continueCmd,          Nothing, completeNone),
120   ("cmd",       keepGoing cmdCmd,               Nothing, completeIdentifier),
121   ("ctags",     keepGoing createCTagsFileCmd,   Just filenameWordBreakChars, completeFilename),
122   ("def",       keepGoing (defineMacro False),  Nothing, completeIdentifier),
123   ("def!",      keepGoing (defineMacro True),   Nothing, completeIdentifier),
124   ("delete",    keepGoing deleteCmd,            Nothing, completeNone),
125   ("e",         keepGoing editFile,             Just filenameWordBreakChars, completeFilename),
126   ("edit",      keepGoing editFile,             Just filenameWordBreakChars, completeFilename),
127   ("etags",     keepGoing createETagsFileCmd,   Just filenameWordBreakChars, completeFilename),
128   ("force",     keepGoing forceCmd,             Nothing, completeIdentifier),
129   ("forward",   keepGoing forwardCmd,           Nothing, completeNone),
130   ("help",      keepGoing help,                 Nothing, completeNone),
131   ("history",   keepGoing historyCmd,           Nothing, completeNone), 
132   ("info",      keepGoing info,                 Nothing, completeIdentifier),
133   ("kind",      keepGoing kindOfType,           Nothing, completeIdentifier),
134   ("load",      keepGoingPaths loadModule_,     Just filenameWordBreakChars, completeHomeModuleOrFile),
135   ("list",      keepGoing listCmd,              Nothing, completeNone),
136   ("module",    keepGoing setContext,           Nothing, completeModule),
137   ("main",      keepGoing runMain,              Nothing, completeIdentifier),
138   ("print",     keepGoing printCmd,             Nothing, completeIdentifier),
139   ("quit",      quit,                           Nothing, completeNone),
140   ("reload",    keepGoing reloadModule,         Nothing, completeNone),
141   ("run",       keepGoing runRun,               Nothing, completeIdentifier),
142   ("set",       keepGoing setCmd,               Just flagWordBreakChars, completeSetOptions),
143   ("show",      keepGoing showCmd,              Nothing, completeNone),
144   ("sprint",    keepGoing sprintCmd,            Nothing, completeIdentifier),
145   ("step",      keepGoing stepCmd,              Nothing, completeIdentifier), 
146   ("steplocal", keepGoing stepLocalCmd,         Nothing, completeIdentifier), 
147   ("stepmodule",keepGoing stepModuleCmd,        Nothing, completeIdentifier), 
148   ("type",      keepGoing typeOfExpr,           Nothing, completeIdentifier),
149   ("trace",     keepGoing traceCmd,             Nothing, completeIdentifier), 
150   ("undef",     keepGoing undefineMacro,        Nothing, completeMacro),
151   ("unset",     keepGoing unsetOptions,         Just flagWordBreakChars,  completeSetOptions)
152   ]
153
154
155 -- We initialize readline (in the interactiveUI function) to use 
156 -- word_break_chars as the default set of completion word break characters.
157 -- This can be overridden for a particular command (for example, filename
158 -- expansion shouldn't consider '/' to be a word break) by setting the third
159 -- entry in the Command tuple above.
160 -- 
161 -- NOTE: in order for us to override the default correctly, any custom entry
162 -- must be a SUBSET of word_break_chars.
163 #ifdef USE_READLINE
164 word_break_chars :: String
165 word_break_chars = let symbols = "!#$%&*+/<=>?@\\^|-~"
166                        specials = "(),;[]`{}"
167                        spaces = " \t\n"
168                    in spaces ++ specials ++ symbols
169 #endif
170
171 flagWordBreakChars, filenameWordBreakChars :: String
172 flagWordBreakChars = " \t\n"
173 filenameWordBreakChars = " \t\n\\`@$><=;|&{(" -- bash defaults
174
175
176 keepGoing :: (String -> GHCi ()) -> (String -> GHCi Bool)
177 keepGoing a str = a str >> return False
178
179 keepGoingPaths :: ([FilePath] -> GHCi ()) -> (String -> GHCi Bool)
180 keepGoingPaths a str
181  = do case toArgs str of
182           Left err -> io (hPutStrLn stderr err)
183           Right args -> a args
184       return False
185
186 shortHelpText :: String
187 shortHelpText = "use :? for help.\n"
188
189 helpText :: String
190 helpText =
191  " Commands available from the prompt:\n" ++
192  "\n" ++
193  "   <statement>                 evaluate/run <statement>\n" ++
194  "   :                           repeat last command\n" ++
195  "   :{\\n ..lines.. \\n:}\\n       multiline command\n" ++
196  "   :add <filename> ...         add module(s) to the current target set\n" ++
197  "   :browse[!] [[*]<mod>]       display the names defined by module <mod>\n" ++
198  "                               (!: more details; *: all top-level names)\n" ++
199  "   :cd <dir>                   change directory to <dir>\n" ++
200  "   :cmd <expr>                 run the commands returned by <expr>::IO String\n" ++
201  "   :ctags [<file>]             create tags file for Vi (default: \"tags\")\n" ++
202  "   :def <cmd> <expr>           define a command :<cmd>\n" ++
203  "   :edit <file>                edit file\n" ++
204  "   :edit                       edit last module\n" ++
205  "   :etags [<file>]             create tags file for Emacs (default: \"TAGS\")\n" ++
206  "   :help, :?                   display this list of commands\n" ++
207  "   :info [<name> ...]          display information about the given names\n" ++
208  "   :kind <type>                show the kind of <type>\n" ++
209  "   :load <filename> ...        load module(s) and their dependents\n" ++
210  "   :main [<arguments> ...]     run the main function with the given arguments\n" ++
211  "   :module [+/-] [*]<mod> ...  set the context for expression evaluation\n" ++
212  "   :quit                       exit GHCi\n" ++
213  "   :reload                     reload the current module set\n" ++
214  "   :run function [<arguments> ...] run the function with the given arguments\n" ++
215  "   :type <expr>                show the type of <expr>\n" ++
216  "   :undef <cmd>                undefine user-defined command :<cmd>\n" ++
217  "   :!<command>                 run the shell command <command>\n" ++
218  "\n" ++
219  " -- Commands for debugging:\n" ++
220  "\n" ++
221  "   :abandon                    at a breakpoint, abandon current computation\n" ++
222  "   :back                       go back in the history (after :trace)\n" ++
223  "   :break [<mod>] <l> [<col>]  set a breakpoint at the specified location\n" ++
224  "   :break <name>               set a breakpoint on the specified function\n" ++
225  "   :continue                   resume after a breakpoint\n" ++
226  "   :delete <number>            delete the specified breakpoint\n" ++
227  "   :delete *                   delete all breakpoints\n" ++
228  "   :force <expr>               print <expr>, forcing unevaluated parts\n" ++
229  "   :forward                    go forward in the history (after :back)\n" ++
230  "   :history [<n>]              show the last <n> items in the history (after :trace)\n" ++
231  "   :print [<name> ...]         prints a value without forcing its computation\n" ++
232  "   :sprint [<name> ...]        simplifed version of :print\n" ++
233  "   :step                       single-step after stopping at a breakpoint\n"++
234  "   :step <expr>                single-step into <expr>\n"++
235  "   :steplocal                  single-step restricted to the current top level decl.\n"++
236  "   :stepmodule                 single-step restricted to the current module\n"++
237  "   :trace                      trace after stopping at a breakpoint\n"++
238  "   :trace <expr>               trace into <expr> (remembers breakpoints for :history)\n"++
239
240  "\n" ++
241  " -- Commands for changing settings:\n" ++
242  "\n" ++
243  "   :set <option> ...           set options\n" ++
244  "   :set args <arg> ...         set the arguments returned by System.getArgs\n" ++
245  "   :set prog <progname>        set the value returned by System.getProgName\n" ++
246  "   :set prompt <prompt>        set the prompt used in GHCi\n" ++
247  "   :set editor <cmd>           set the command used for :edit\n" ++
248  "   :set stop <cmd>             set the command to run when a breakpoint is hit\n" ++
249  "   :unset <option> ...         unset options\n" ++
250  "\n" ++
251  "  Options for ':set' and ':unset':\n" ++
252  "\n" ++
253  "    +r            revert top-level expressions after each evaluation\n" ++
254  "    +s            print timing/memory stats after each evaluation\n" ++
255  "    +t            print type after evaluation\n" ++
256  "    -<flags>      most GHC command line flags can also be set here\n" ++
257  "                         (eg. -v2, -fglasgow-exts, etc.)\n" ++
258  "                    for GHCi-specific flags, see User's Guide,\n"++
259  "                    Flag reference, Interactive-mode options\n" ++
260  "\n" ++
261  " -- Commands for displaying information:\n" ++
262  "\n" ++
263  "   :show bindings              show the current bindings made at the prompt\n" ++
264  "   :show breaks                show the active breakpoints\n" ++
265  "   :show context               show the breakpoint context\n" ++
266  "   :show modules               show the currently loaded modules\n" ++
267  "   :show packages              show the currently active package flags\n" ++
268  "   :show languages             show the currently active language flags\n" ++
269  "   :show <setting>             show anything that can be set with :set (e.g. args)\n" ++
270  "\n" 
271
272 findEditor :: IO String
273 findEditor = do
274   getEnv "EDITOR" 
275     `IO.catch` \_ -> do
276 #if mingw32_HOST_OS
277         win <- System.Win32.getWindowsDirectory
278         return (win </> "notepad.exe")
279 #else
280         return ""
281 #endif
282
283 interactiveUI :: Session -> [(FilePath, Maybe Phase)] -> Maybe [String]
284               -> IO ()
285 interactiveUI session srcs maybe_exprs = do
286    -- HACK! If we happen to get into an infinite loop (eg the user
287    -- types 'let x=x in x' at the prompt), then the thread will block
288    -- on a blackhole, and become unreachable during GC.  The GC will
289    -- detect that it is unreachable and send it the NonTermination
290    -- exception.  However, since the thread is unreachable, everything
291    -- it refers to might be finalized, including the standard Handles.
292    -- This sounds like a bug, but we don't have a good solution right
293    -- now.
294    newStablePtr stdin
295    newStablePtr stdout
296    newStablePtr stderr
297
298     -- Initialise buffering for the *interpreted* I/O system
299    initInterpBuffering session
300
301    when (isNothing maybe_exprs) $ do
302         -- Only for GHCi (not runghc and ghc -e):
303
304         -- Turn buffering off for the compiled program's stdout/stderr
305         turnOffBuffering
306         -- Turn buffering off for GHCi's stdout
307         hFlush stdout
308         hSetBuffering stdout NoBuffering
309         -- We don't want the cmd line to buffer any input that might be
310         -- intended for the program, so unbuffer stdin.
311         hSetBuffering stdin NoBuffering
312
313 #ifdef USE_READLINE
314         is_tty <- hIsTerminalDevice stdin
315         when is_tty $ do
316             Readline.initialize
317             Readline.setAttemptedCompletionFunction (Just completeWord)
318             --Readline.parseAndBind "set show-all-if-ambiguous 1"
319
320             Readline.setBasicWordBreakCharacters word_break_chars
321             Readline.setCompleterWordBreakCharacters word_break_chars
322             Readline.setCompletionAppendCharacter Nothing
323 #endif
324
325    -- initial context is just the Prelude
326    prel_mod <- GHC.findModule session (GHC.mkModuleName "Prelude") 
327                                       (Just basePackageId)
328    GHC.setContext session [] [prel_mod]
329
330    default_editor <- findEditor
331
332    startGHCi (runGHCi srcs maybe_exprs)
333         GHCiState{ progname = "<interactive>",
334                    args = [],
335                    prompt = "%s> ",
336                    stop = "",
337                    editor = default_editor,
338                    session = session,
339                    options = [],
340                    prelude = prel_mod,
341                    break_ctr = 0,
342                    breaks = [],
343                    tickarrays = emptyModuleEnv,
344                    last_command = Nothing,
345                    cmdqueue = [],
346                    remembered_ctx = Nothing
347                  }
348
349 #ifdef USE_READLINE
350    Readline.resetTerminal Nothing
351 #endif
352
353    return ()
354
355 runGHCi :: [(FilePath, Maybe Phase)] -> Maybe [String] -> GHCi ()
356 runGHCi paths maybe_exprs = do
357   let read_dot_files = not opt_IgnoreDotGhci
358
359   when (read_dot_files) $ do
360     -- Read in ./.ghci.
361     let file = "./.ghci"
362     exists <- io (doesFileExist file)
363     when exists $ do
364        dir_ok  <- io (checkPerms ".")
365        file_ok <- io (checkPerms file)
366        when (dir_ok && file_ok) $ do
367           either_hdl <- io (IO.try (openFile "./.ghci" ReadMode))
368           case either_hdl of
369              Left _e   -> return ()
370              Right hdl -> runCommands (fileLoop hdl False False)
371
372   when (read_dot_files) $ do
373     -- Read in $HOME/.ghci
374     either_dir <- io (IO.try getHomeDirectory)
375     case either_dir of
376        Left _e -> return ()
377        Right dir -> do
378           cwd <- io (getCurrentDirectory)
379           when (dir /= cwd) $ do
380              let file = dir ++ "/.ghci"
381              ok <- io (checkPerms file)
382              when ok $ do
383                either_hdl <- io (IO.try (openFile file ReadMode))
384                case either_hdl of
385                   Left _e   -> return ()
386                   Right hdl -> runCommands (fileLoop hdl False False)
387
388   -- Perform a :load for files given on the GHCi command line
389   -- When in -e mode, if the load fails then we want to stop
390   -- immediately rather than going on to evaluate the expression.
391   when (not (null paths)) $ do
392      ok <- ghciHandle (\e -> do showException e; return Failed) $
393                 loadModule paths
394      when (isJust maybe_exprs && failed ok) $
395         io (exitWith (ExitFailure 1))
396
397   -- if verbosity is greater than 0, or we are connected to a
398   -- terminal, display the prompt in the interactive loop.
399   is_tty <- io (hIsTerminalDevice stdin)
400   dflags <- getDynFlags
401   let show_prompt = verbosity dflags > 0 || is_tty
402
403   case maybe_exprs of
404         Nothing ->
405           do
406 #if defined(mingw32_HOST_OS)
407             -- The win32 Console API mutates the first character of
408             -- type-ahead when reading from it in a non-buffered manner. Work
409             -- around this by flushing the input buffer of type-ahead characters,
410             -- but only if stdin is available.
411             flushed <- io (IO.try (GHC.ConsoleHandler.flushConsole stdin))
412             case flushed of
413              Left err | isDoesNotExistError err -> return ()
414                       | otherwise -> io (ioError err)
415              Right () -> return ()
416 #endif
417             -- enter the interactive loop
418             interactiveLoop is_tty show_prompt
419         Just exprs -> do
420             -- just evaluate the expression we were given
421             enqueueCommands exprs
422             let handleEval (ExitException code) = io (exitWith code)
423                 handleEval e                    = handler e
424             runCommands' handleEval (return Nothing)
425
426   -- and finally, exit
427   io $ do when (verbosity dflags > 0) $ putStrLn "Leaving GHCi."
428
429
430 interactiveLoop :: Bool -> Bool -> GHCi ()
431 interactiveLoop is_tty show_prompt =
432   -- Ignore ^C exceptions caught here
433   ghciHandleDyn (\e -> case e of 
434                         Interrupted -> do
435 #if defined(mingw32_HOST_OS)
436                                 io (putStrLn "")
437 #endif
438                                 interactiveLoop is_tty show_prompt
439                         _other      -> return ()) $ 
440
441   ghciUnblock $ do -- unblock necessary if we recursed from the 
442                    -- exception handler above.
443
444   -- read commands from stdin
445 #ifdef USE_READLINE
446   if (is_tty) 
447         then runCommands readlineLoop
448         else runCommands (fileLoop stdin show_prompt is_tty)
449 #else
450   runCommands (fileLoop stdin show_prompt is_tty)
451 #endif
452
453
454 -- NOTE: We only read .ghci files if they are owned by the current user,
455 -- and aren't world writable.  Otherwise, we could be accidentally 
456 -- running code planted by a malicious third party.
457
458 -- Furthermore, We only read ./.ghci if . is owned by the current user
459 -- and isn't writable by anyone else.  I think this is sufficient: we
460 -- don't need to check .. and ../.. etc. because "."  always refers to
461 -- the same directory while a process is running.
462
463 checkPerms :: String -> IO Bool
464 #ifdef mingw32_HOST_OS
465 checkPerms _ =
466   return True
467 #else
468 checkPerms name =
469   Util.handle (\_ -> return False) $ do
470      st <- getFileStatus name
471      me <- getRealUserID
472      if fileOwner st /= me then do
473         putStrLn $ "WARNING: " ++ name ++ " is owned by someone else, IGNORING!"
474         return False
475       else do
476         let mode =  fileMode st
477         if (groupWriteMode == (mode `intersectFileModes` groupWriteMode))
478            || (otherWriteMode == (mode `intersectFileModes` otherWriteMode)) 
479            then do
480                putStrLn $ "*** WARNING: " ++ name ++ 
481                           " is writable by someone else, IGNORING!"
482                return False
483           else return True
484 #endif
485
486 fileLoop :: Handle -> Bool -> Bool -> GHCi (Maybe String)
487 fileLoop hdl show_prompt is_tty = do
488    when show_prompt $ do
489         prompt <- mkPrompt
490         (io (putStr prompt))
491    l <- io (IO.try (hGetLine hdl))
492    case l of
493         Left e | isEOFError e              -> return Nothing
494                | InvalidArgument <- etype  -> return Nothing
495                | otherwise                 -> io (ioError e)
496                 where etype = ioeGetErrorType e
497                 -- treat InvalidArgument in the same way as EOF:
498                 -- this can happen if the user closed stdin, or
499                 -- perhaps did getContents which closes stdin at
500                 -- EOF.
501         Right l -> do
502                    str <- io $ consoleInputToUnicode is_tty l
503                    return (Just str)
504
505 #ifdef mingw32_HOST_OS
506 -- Convert the console input into Unicode according to the current code page.
507 -- The Windows console stores Unicode characters directly, so this is a
508 -- rather roundabout way of doing things... oh well.
509 -- See #782, #1483, #1649
510 consoleInputToUnicode :: Bool -> String -> IO String
511 consoleInputToUnicode is_tty str
512   | is_tty = do
513     cp <- System.Win32.getConsoleCP
514     System.Win32.stringToUnicode cp str
515   | otherwise =
516     decodeStringAsUTF8 str
517 #else
518 -- for Unix, assume the input is in UTF-8 and decode it to a Unicode String. 
519 -- See #782.
520 consoleInputToUnicode :: Bool -> String -> IO String
521 consoleInputToUnicode _is_tty str = decodeStringAsUTF8 str
522 #endif
523
524 decodeStringAsUTF8 :: String -> IO String
525 decodeStringAsUTF8 str =
526   withCStringLen str $ \(cstr,len) -> 
527     utf8DecodeString (castPtr cstr :: Ptr Word8) len
528
529 mkPrompt :: GHCi String
530 mkPrompt = do
531   session <- getSession
532   (toplevs,exports) <- io (GHC.getContext session)
533   resumes <- io $ GHC.getResumeContext session
534   -- st <- getGHCiState
535
536   context_bit <-
537         case resumes of
538             [] -> return empty
539             r:_ -> do
540                 let ix = GHC.resumeHistoryIx r
541                 if ix == 0
542                    then return (brackets (ppr (GHC.resumeSpan r)) <> space)
543                    else do
544                         let hist = GHC.resumeHistory r !! (ix-1)
545                         span <- io$ GHC.getHistorySpan session hist
546                         return (brackets (ppr (negate ix) <> char ':' 
547                                           <+> ppr span) <> space)
548   let
549         dots | _:rs <- resumes, not (null rs) = text "... "
550              | otherwise = empty
551
552         
553
554         modules_bit = 
555        -- ToDo: maybe...
556        --  let (btoplevs, bexports) = fromMaybe ([],[]) (remembered_ctx st) in
557        --  hsep (map (\m -> text "!*" <> ppr (GHC.moduleName m)) btoplevs) <+>
558        --  hsep (map (\m -> char '!'  <> ppr (GHC.moduleName m)) bexports) <+>
559              hsep (map (\m -> char '*'  <> ppr (GHC.moduleName m)) toplevs) <+>
560              hsep (map (ppr . GHC.moduleName) exports)
561
562         deflt_prompt = dots <> context_bit <> modules_bit
563
564         f ('%':'s':xs) = deflt_prompt <> f xs
565         f ('%':'%':xs) = char '%' <> f xs
566         f (x:xs) = char x <> f xs
567         f [] = empty
568    --
569   st <- getGHCiState
570   return (showSDoc (f (prompt st)))
571
572
573 #ifdef USE_READLINE
574 readlineLoop :: GHCi (Maybe String)
575 readlineLoop = do
576    io yield
577    saveSession -- for use by completion
578    prompt <- mkPrompt
579    l <- io (readline prompt `finally` setNonBlockingFD 0)
580                 -- readline sometimes puts stdin into blocking mode,
581                 -- so we need to put it back for the IO library
582    splatSavedSession
583    case l of
584         Nothing -> return Nothing
585         Just l  -> do
586                    io (addHistory l)
587                    str <- io $ consoleInputToUnicode True l
588                    return (Just str)
589 #endif
590
591 queryQueue :: GHCi (Maybe String)
592 queryQueue = do
593   st <- getGHCiState
594   case cmdqueue st of
595     []   -> return Nothing
596     c:cs -> do setGHCiState st{ cmdqueue = cs }
597                return (Just c)
598
599 runCommands :: GHCi (Maybe String) -> GHCi ()
600 runCommands = runCommands' handler
601
602 runCommands' :: (Exception -> GHCi Bool) -- Exception handler
603              -> GHCi (Maybe String) -> GHCi ()
604 runCommands' eh getCmd = do
605   mb_cmd <- noSpace queryQueue
606   mb_cmd <- maybe (noSpace getCmd) (return . Just) mb_cmd
607   case mb_cmd of 
608     Nothing -> return ()
609     Just c  -> do
610       b <- ghciHandle eh (doCommand c)
611       if b then return () else runCommands' eh getCmd
612   where
613     noSpace q = q >>= maybe (return Nothing)
614                             (\c->case removeSpaces c of 
615                                    ""   -> noSpace q
616                                    ":{" -> multiLineCmd q
617                                    c    -> return (Just c) )
618     multiLineCmd q = do
619       st <- getGHCiState
620       let p = prompt st
621       setGHCiState st{ prompt = "%s| " }
622       mb_cmd <- collectCommand q ""
623       getGHCiState >>= \st->setGHCiState st{ prompt = p }
624       return mb_cmd
625     -- we can't use removeSpaces for the sublines here, so 
626     -- multiline commands are somewhat more brittle against
627     -- fileformat errors (such as \r in dos input on unix), 
628     -- we get rid of any extra spaces for the ":}" test; 
629     -- we also avoid silent failure if ":}" is not found;
630     -- and since there is no (?) valid occurrence of \r (as 
631     -- opposed to its String representation, "\r") inside a
632     -- ghci command, we replace any such with ' ' (argh:-(
633     collectCommand q c = q >>= 
634       maybe (io (ioError collectError))
635             (\l->if removeSpaces l == ":}" 
636                  then return (Just $ removeSpaces c) 
637                  else collectCommand q (c++map normSpace l))
638       where normSpace '\r' = ' '
639             normSpace   c  = c
640     -- QUESTION: is userError the one to use here?
641     collectError = userError "unterminated multiline command :{ .. :}"
642     doCommand (':' : cmd) = specialCommand cmd
643     doCommand stmt        = do timeIt $ runStmt stmt GHC.RunToCompletion
644                                return False
645
646 enqueueCommands :: [String] -> GHCi ()
647 enqueueCommands cmds = do
648   st <- getGHCiState
649   setGHCiState st{ cmdqueue = cmds ++ cmdqueue st }
650
651
652 runStmt :: String -> SingleStep -> GHCi Bool
653 runStmt stmt step
654  | null (filter (not.isSpace) stmt) = return False
655  | ["import", mod] <- words stmt    = keepGoing setContext ('+':mod)
656  | otherwise
657  = do st <- getGHCiState
658       session <- getSession
659       result <- io $ withProgName (progname st) $ withArgs (args st) $
660                      GHC.runStmt session stmt step
661       afterRunStmt (const True) result
662
663
664 --afterRunStmt :: GHC.RunResult -> GHCi Bool
665                                  -- False <=> the statement failed to compile
666 afterRunStmt :: (SrcSpan -> Bool) -> GHC.RunResult -> GHCi Bool
667 afterRunStmt _ (GHC.RunException e) = throw e
668 afterRunStmt step_here run_result = do
669   session     <- getSession
670   resumes <- io $ GHC.getResumeContext session
671   case run_result of
672      GHC.RunOk names -> do
673         show_types <- isOptionSet ShowType
674         when show_types $ printTypeOfNames session names
675      GHC.RunBreak _ names mb_info 
676          | isNothing  mb_info || 
677            step_here (GHC.resumeSpan $ head resumes) -> do
678                printForUser $ ptext SLIT("Stopped at") <+> 
679                        ppr (GHC.resumeSpan $ head resumes)
680 --               printTypeOfNames session names
681                let namesSorted = sortBy compareNames names
682                tythings <- catMaybes `liftM` 
683                               io (mapM (GHC.lookupName session) namesSorted)
684                docs <- io$ pprTypeAndContents session [id | AnId id <- tythings]
685                printForUserPartWay docs
686                maybe (return ()) runBreakCmd mb_info
687                -- run the command set with ":set stop <cmd>"
688                st <- getGHCiState
689                enqueueCommands [stop st]
690                return ()
691          | otherwise -> io(GHC.resume session GHC.SingleStep) >>= 
692                         afterRunStmt step_here >> return ()
693      _ -> return ()
694
695   flushInterpBuffers
696   io installSignalHandlers
697   b <- isOptionSet RevertCAFs
698   io (when b revertCAFs)
699
700   return (case run_result of GHC.RunOk _ -> True; _ -> False)
701
702 runBreakCmd :: GHC.BreakInfo -> GHCi ()
703 runBreakCmd info = do
704   let mod = GHC.breakInfo_module info
705       nm  = GHC.breakInfo_number info
706   st <- getGHCiState
707   case  [ loc | (_,loc) <- breaks st,
708                 breakModule loc == mod, breakTick loc == nm ] of
709         []  -> return ()
710         loc:_ | null cmd  -> return ()
711               | otherwise -> do enqueueCommands [cmd]; return ()
712               where cmd = onBreakCmd loc
713
714 printTypeOfNames :: Session -> [Name] -> GHCi ()
715 printTypeOfNames session names
716  = mapM_ (printTypeOfName session) $ sortBy compareNames names
717
718 compareNames :: Name -> Name -> Ordering
719 n1 `compareNames` n2 = compareWith n1 `compare` compareWith n2
720     where compareWith n = (getOccString n, getSrcSpan n)
721
722 printTypeOfName :: Session -> Name -> GHCi ()
723 printTypeOfName session n
724    = do maybe_tything <- io (GHC.lookupName session n)
725         case maybe_tything of
726             Nothing    -> return ()
727             Just thing -> printTyThing thing
728
729
730 data MaybeCommand = GotCommand Command | BadCommand | NoLastCommand
731
732 specialCommand :: String -> GHCi Bool
733 specialCommand ('!':str) = shellEscape (dropWhile isSpace str)
734 specialCommand str = do
735   let (cmd,rest) = break isSpace str
736   maybe_cmd <- lookupCommand cmd
737   case maybe_cmd of
738     GotCommand (_,f,_,_) -> f (dropWhile isSpace rest)
739     BadCommand ->
740       do io $ hPutStr stdout ("unknown command ':" ++ cmd ++ "'\n"
741                            ++ shortHelpText)
742          return False
743     NoLastCommand ->
744       do io $ hPutStr stdout ("there is no last command to perform\n"
745                            ++ shortHelpText)
746          return False
747
748 lookupCommand :: String -> GHCi (MaybeCommand)
749 lookupCommand "" = do
750   st <- getGHCiState
751   case last_command st of
752       Just c -> return $ GotCommand c
753       Nothing -> return NoLastCommand
754 lookupCommand str = do
755   mc <- io $ lookupCommand' str
756   st <- getGHCiState
757   setGHCiState st{ last_command = mc }
758   return $ case mc of
759            Just c -> GotCommand c
760            Nothing -> BadCommand
761
762 lookupCommand' :: String -> IO (Maybe Command)
763 lookupCommand' str = do
764   macros <- readIORef macros_ref
765   let cmds = builtin_commands ++ macros
766   -- look for exact match first, then the first prefix match
767   return $ case [ c | c <- cmds, str == cmdName c ] of
768            c:_ -> Just c
769            [] -> case [ c | c@(s,_,_,_) <- cmds, str `isPrefixOf` s ] of
770                  [] -> Nothing
771                  c:_ -> Just c
772
773 getCurrentBreakSpan :: GHCi (Maybe SrcSpan)
774 getCurrentBreakSpan = do
775   session <- getSession
776   resumes <- io $ GHC.getResumeContext session
777   case resumes of
778     [] -> return Nothing
779     (r:_) -> do
780         let ix = GHC.resumeHistoryIx r
781         if ix == 0
782            then return (Just (GHC.resumeSpan r))
783            else do
784                 let hist = GHC.resumeHistory r !! (ix-1)
785                 span <- io $ GHC.getHistorySpan session hist
786                 return (Just span)
787
788 getCurrentBreakModule :: GHCi (Maybe Module)
789 getCurrentBreakModule = do
790   session <- getSession
791   resumes <- io $ GHC.getResumeContext session
792   case resumes of
793     [] -> return Nothing
794     (r:_) -> do
795         let ix = GHC.resumeHistoryIx r
796         if ix == 0
797            then return (GHC.breakInfo_module `liftM` GHC.resumeBreakInfo r)
798            else do
799                 let hist = GHC.resumeHistory r !! (ix-1)
800                 return $ Just $ GHC.getHistoryModule  hist
801
802 -----------------------------------------------------------------------------
803 -- Commands
804
805 noArgs :: GHCi () -> String -> GHCi ()
806 noArgs m "" = m
807 noArgs _ _  = io $ putStrLn "This command takes no arguments"
808
809 help :: String -> GHCi ()
810 help _ = io (putStr helpText)
811
812 info :: String -> GHCi ()
813 info "" = throwDyn (CmdLineError "syntax: ':i <thing-you-want-info-about>'")
814 info s  = do { let names = words s
815              ; session <- getSession
816              ; dflags <- getDynFlags
817              ; let pefas = dopt Opt_PrintExplicitForalls dflags
818              ; mapM_ (infoThing pefas session) names }
819   where
820     infoThing pefas session str = io $ do
821         names     <- GHC.parseName session str
822         mb_stuffs <- mapM (GHC.getInfo session) names
823         let filtered = filterOutChildren (\(t,_f,_i) -> t) (catMaybes mb_stuffs)
824         unqual <- GHC.getPrintUnqual session
825         putStrLn (showSDocForUser unqual $
826                    vcat (intersperse (text "") $
827                          map (pprInfo pefas) filtered))
828
829   -- Filter out names whose parent is also there Good
830   -- example is '[]', which is both a type and data
831   -- constructor in the same type
832 filterOutChildren :: (a -> TyThing) -> [a] -> [a]
833 filterOutChildren get_thing xs 
834   = [x | x <- xs, not (getName (get_thing x) `elemNameSet` implicits)]
835   where
836     implicits = mkNameSet [getName t | x <- xs, t <- implicitTyThings (get_thing x)]
837
838 pprInfo :: PrintExplicitForalls -> (TyThing, Fixity, [GHC.Instance]) -> SDoc
839 pprInfo pefas (thing, fixity, insts)
840   =  pprTyThingInContextLoc pefas thing
841   $$ show_fixity fixity
842   $$ vcat (map GHC.pprInstance insts)
843   where
844     show_fixity fix 
845         | fix == GHC.defaultFixity = empty
846         | otherwise                = ppr fix <+> ppr (GHC.getName thing)
847
848 runMain :: String -> GHCi ()
849 runMain s = case toArgs s of
850             Left err   -> io (hPutStrLn stderr err)
851             Right args ->
852                 do dflags <- getDynFlags
853                    case mainFunIs dflags of
854                        Nothing -> doWithArgs args "main"
855                        Just f  -> doWithArgs args f
856
857 runRun :: String -> GHCi ()
858 runRun s = case toCmdArgs s of
859            Left err          -> io (hPutStrLn stderr err)
860            Right (cmd, args) -> doWithArgs args cmd
861
862 doWithArgs :: [String] -> String -> GHCi ()
863 doWithArgs args cmd = enqueueCommands ["System.Environment.withArgs " ++
864                                        show args ++ " (" ++ cmd ++ ")"]
865
866 addModule :: [FilePath] -> GHCi ()
867 addModule files = do
868   io (revertCAFs)                       -- always revert CAFs on load/add.
869   files <- mapM expandPath files
870   targets <- mapM (\m -> io (GHC.guessTarget m Nothing)) files
871   session <- getSession
872   io (mapM_ (GHC.addTarget session) targets)
873   prev_context <- io $ GHC.getContext session
874   ok <- io (GHC.load session LoadAllTargets)
875   afterLoad ok session False prev_context
876
877 changeDirectory :: String -> GHCi ()
878 changeDirectory "" = do
879   -- :cd on its own changes to the user's home directory
880   either_dir <- io (IO.try getHomeDirectory)
881   case either_dir of
882      Left _e -> return ()
883      Right dir -> changeDirectory dir
884 changeDirectory dir = do
885   session <- getSession
886   graph <- io (GHC.getModuleGraph session)
887   when (not (null graph)) $
888         io $ putStr "Warning: changing directory causes all loaded modules to be unloaded,\nbecause the search path has changed.\n"
889   prev_context <- io $ GHC.getContext session
890   io (GHC.setTargets session [])
891   io (GHC.load session LoadAllTargets)
892   setContextAfterLoad session prev_context []
893   io (GHC.workingDirectoryChanged session)
894   dir <- expandPath dir
895   io (setCurrentDirectory dir)
896
897 editFile :: String -> GHCi ()
898 editFile str =
899   do file <- if null str then chooseEditFile else return str
900      st <- getGHCiState
901      let cmd = editor st
902      when (null cmd) 
903        $ throwDyn (CmdLineError "editor not set, use :set editor")
904      io $ system (cmd ++ ' ':file)
905      return ()
906
907 -- The user didn't specify a file so we pick one for them.
908 -- Our strategy is to pick the first module that failed to load,
909 -- or otherwise the first target.
910 --
911 -- XXX: Can we figure out what happened if the depndecy analysis fails
912 --      (e.g., because the porgrammeer mistyped the name of a module)?
913 -- XXX: Can we figure out the location of an error to pass to the editor?
914 -- XXX: if we could figure out the list of errors that occured during the
915 -- last load/reaload, then we could start the editor focused on the first
916 -- of those.
917 chooseEditFile :: GHCi String
918 chooseEditFile =
919   do session <- getSession
920      let hasFailed x = io $ fmap not $ GHC.isLoaded session $ GHC.ms_mod_name x
921
922      graph <- io (GHC.getModuleGraph session)
923      failed_graph <- filterM hasFailed graph
924      let order g  = flattenSCCs $ GHC.topSortModuleGraph True g Nothing
925          pick xs  = case xs of
926                       x : _ -> GHC.ml_hs_file (GHC.ms_location x)
927                       _     -> Nothing
928
929      case pick (order failed_graph) of
930        Just file -> return file
931        Nothing   -> 
932          do targets <- io (GHC.getTargets session)
933             case msum (map fromTarget targets) of
934               Just file -> return file
935               Nothing   -> throwDyn (CmdLineError "No files to edit.")
936           
937   where fromTarget (GHC.Target (GHC.TargetFile f _) _) = Just f
938         fromTarget _ = Nothing -- when would we get a module target?
939
940 defineMacro :: Bool{-overwrite-} -> String -> GHCi ()
941 defineMacro overwrite s = do
942   let (macro_name, definition) = break isSpace s
943   macros <- io (readIORef macros_ref)
944   let defined = map cmdName macros
945   if (null macro_name) 
946         then if null defined
947                 then io $ putStrLn "no macros defined"
948                 else io $ putStr ("the following macros are defined:\n" ++
949                                   unlines defined)
950         else do
951   if (not overwrite && macro_name `elem` defined)
952         then throwDyn (CmdLineError 
953                 ("macro '" ++ macro_name ++ "' is already defined"))
954         else do
955
956   let filtered = [ cmd | cmd <- macros, cmdName cmd /= macro_name ]
957
958   -- give the expression a type signature, so we can be sure we're getting
959   -- something of the right type.
960   let new_expr = '(' : definition ++ ") :: String -> IO String"
961
962   -- compile the expression
963   cms <- getSession
964   maybe_hv <- io (GHC.compileExpr cms new_expr)
965   case maybe_hv of
966      Nothing -> return ()
967      Just hv -> io (writeIORef macros_ref --
968                     (filtered ++ [(macro_name, runMacro hv, Nothing, completeNone)]))
969
970 runMacro :: GHC.HValue{-String -> IO String-} -> String -> GHCi Bool
971 runMacro fun s = do
972   str <- io ((unsafeCoerce# fun :: String -> IO String) s)
973   enqueueCommands (lines str)
974   return False
975
976 undefineMacro :: String -> GHCi ()
977 undefineMacro str = mapM_ undef (words str) 
978  where undef macro_name = do
979         cmds <- io (readIORef macros_ref)
980         if (macro_name `notElem` map cmdName cmds) 
981            then throwDyn (CmdLineError 
982                 ("macro '" ++ macro_name ++ "' is not defined"))
983            else do
984             io (writeIORef macros_ref (filter ((/= macro_name) . cmdName) cmds))
985
986 cmdCmd :: String -> GHCi ()
987 cmdCmd str = do
988   let expr = '(' : str ++ ") :: IO String"
989   session <- getSession
990   maybe_hv <- io (GHC.compileExpr session expr)
991   case maybe_hv of
992     Nothing -> return ()
993     Just hv -> do 
994         cmds <- io $ (unsafeCoerce# hv :: IO String)
995         enqueueCommands (lines cmds)
996         return ()
997
998 loadModule :: [(FilePath, Maybe Phase)] -> GHCi SuccessFlag
999 loadModule fs = timeIt (loadModule' fs)
1000
1001 loadModule_ :: [FilePath] -> GHCi ()
1002 loadModule_ fs = do loadModule (zip fs (repeat Nothing)); return ()
1003
1004 loadModule' :: [(FilePath, Maybe Phase)] -> GHCi SuccessFlag
1005 loadModule' files = do
1006   session <- getSession
1007   prev_context <- io $ GHC.getContext session
1008
1009   -- unload first
1010   discardActiveBreakPoints
1011   io (GHC.setTargets session [])
1012   io (GHC.load session LoadAllTargets)
1013
1014   -- expand tildes
1015   let (filenames, phases) = unzip files
1016   exp_filenames <- mapM expandPath filenames
1017   let files' = zip exp_filenames phases
1018   targets <- io (mapM (uncurry GHC.guessTarget) files')
1019
1020   -- NOTE: we used to do the dependency anal first, so that if it
1021   -- fails we didn't throw away the current set of modules.  This would
1022   -- require some re-working of the GHC interface, so we'll leave it
1023   -- as a ToDo for now.
1024
1025   io (GHC.setTargets session targets)
1026   doLoad session False prev_context LoadAllTargets
1027
1028 checkModule :: String -> GHCi ()
1029 checkModule m = do
1030   let modl = GHC.mkModuleName m
1031   session <- getSession
1032   prev_context <- io $ GHC.getContext session
1033   result <- io (GHC.checkModule session modl False)
1034   case result of
1035     Nothing -> io $ putStrLn "Nothing"
1036     Just r  -> io $ putStrLn (showSDoc (
1037         case GHC.checkedModuleInfo r of
1038            Just cm | Just scope <- GHC.modInfoTopLevelScope cm -> 
1039                 let
1040                     (local,global) = partition ((== modl) . GHC.moduleName . GHC.nameModule) scope
1041                 in
1042                         (text "global names: " <+> ppr global) $$
1043                         (text "local  names: " <+> ppr local)
1044            _ -> empty))
1045   afterLoad (successIf (isJust result)) session False prev_context
1046
1047 reloadModule :: String -> GHCi ()
1048 reloadModule m = do
1049   session <- getSession
1050   prev_context <- io $ GHC.getContext session
1051   doLoad session True prev_context $ 
1052         if null m then LoadAllTargets 
1053                   else LoadUpTo (GHC.mkModuleName m)
1054   return ()
1055
1056 doLoad :: Session -> Bool -> ([Module],[Module]) -> LoadHowMuch -> GHCi SuccessFlag
1057 doLoad session retain_context prev_context howmuch = do
1058   -- turn off breakpoints before we load: we can't turn them off later, because
1059   -- the ModBreaks will have gone away.
1060   discardActiveBreakPoints
1061   ok <- io (GHC.load session howmuch)
1062   afterLoad ok session retain_context prev_context
1063   return ok
1064
1065 afterLoad :: SuccessFlag -> Session -> Bool -> ([Module],[Module]) -> GHCi ()
1066 afterLoad ok session retain_context prev_context = do
1067   io (revertCAFs)  -- always revert CAFs on load.
1068   discardTickArrays
1069   loaded_mod_summaries <- getLoadedModules session
1070   let loaded_mods = map GHC.ms_mod loaded_mod_summaries
1071       loaded_mod_names = map GHC.moduleName loaded_mods
1072   modulesLoadedMsg ok loaded_mod_names
1073
1074   st <- getGHCiState
1075   if not retain_context
1076     then do
1077         setGHCiState st{ remembered_ctx = Nothing }
1078         setContextAfterLoad session prev_context loaded_mod_summaries
1079     else do
1080         -- figure out which modules we can keep in the context, which we
1081         -- have to put back, and which we have to remember because they
1082         -- are (temporarily) unavailable.  See ghci.prog009, #1873, #1360
1083         let (as,bs) = prev_context
1084             as1 = filter isHomeModule as -- package modules are kept anyway
1085             bs1 = filter isHomeModule bs
1086             (as_ok, as_bad) = partition (`elem` loaded_mods) as1
1087             (bs_ok, bs_bad) = partition (`elem` loaded_mods) bs1
1088             (rem_as, rem_bs) = fromMaybe ([],[]) (remembered_ctx st)
1089             (rem_as_ok, rem_as_bad) = partition (`elem` loaded_mods) rem_as
1090             (rem_bs_ok, rem_bs_bad) = partition (`elem` loaded_mods) rem_bs
1091             as' = nub (as_ok++rem_as_ok)
1092             bs' = nub (bs_ok++rem_bs_ok)
1093             rem_as' = nub (rem_as_bad ++ as_bad)
1094             rem_bs' = nub (rem_bs_bad ++ bs_bad)
1095
1096          -- Put back into the context any modules that we previously had
1097          -- to drop because they weren't available (rem_as_ok, rem_bs_ok).
1098         setContextKeepingPackageModules session prev_context (as',bs')
1099
1100          -- If compilation failed, remember any modules that we are unable
1101          -- to load, so that we can put them back in the context in the future.
1102         case ok of
1103          Succeeded -> setGHCiState st{ remembered_ctx = Nothing }
1104          Failed    -> setGHCiState st{ remembered_ctx = Just (rem_as',rem_bs') }
1105
1106
1107
1108 setContextAfterLoad :: Session -> ([Module],[Module]) -> [GHC.ModSummary] -> GHCi ()
1109 setContextAfterLoad session prev [] = do
1110   prel_mod <- getPrelude
1111   setContextKeepingPackageModules session prev ([], [prel_mod])
1112 setContextAfterLoad session prev ms = do
1113   -- load a target if one is available, otherwise load the topmost module.
1114   targets <- io (GHC.getTargets session)
1115   case [ m | Just m <- map (findTarget ms) targets ] of
1116         []    -> 
1117           let graph' = flattenSCCs (GHC.topSortModuleGraph True ms Nothing) in
1118           load_this (last graph')         
1119         (m:_) -> 
1120           load_this m
1121  where
1122    findTarget ms t
1123     = case filter (`matches` t) ms of
1124         []    -> Nothing
1125         (m:_) -> Just m
1126
1127    summary `matches` Target (TargetModule m) _
1128         = GHC.ms_mod_name summary == m
1129    summary `matches` Target (TargetFile f _) _ 
1130         | Just f' <- GHC.ml_hs_file (GHC.ms_location summary)   = f == f'
1131    _ `matches` _
1132         = False
1133
1134    load_this summary | m <- GHC.ms_mod summary = do
1135         b <- io (GHC.moduleIsInterpreted session m)
1136         if b then setContextKeepingPackageModules session prev ([m], [])
1137              else do
1138                 prel_mod <- getPrelude
1139                 setContextKeepingPackageModules session prev ([],[prel_mod,m])
1140
1141 -- | Keep any package modules (except Prelude) when changing the context.
1142 setContextKeepingPackageModules
1143         :: Session
1144         -> ([Module],[Module])          -- previous context
1145         -> ([Module],[Module])          -- new context
1146         -> GHCi ()
1147 setContextKeepingPackageModules session prev_context (as,bs) = do
1148   let (_,bs0) = prev_context
1149   prel_mod <- getPrelude
1150   let pkg_modules = filter (\p -> not (isHomeModule p) && p /= prel_mod) bs0
1151   let bs1 = if null as then nub (prel_mod : bs) else bs
1152   io $ GHC.setContext session as (nub (bs1 ++ pkg_modules))
1153
1154 isHomeModule :: Module -> Bool
1155 isHomeModule mod = GHC.modulePackageId mod == mainPackageId
1156
1157 modulesLoadedMsg :: SuccessFlag -> [ModuleName] -> GHCi ()
1158 modulesLoadedMsg ok mods = do
1159   dflags <- getDynFlags
1160   when (verbosity dflags > 0) $ do
1161    let mod_commas 
1162         | null mods = text "none."
1163         | otherwise = hsep (
1164             punctuate comma (map ppr mods)) <> text "."
1165    case ok of
1166     Failed ->
1167        io (putStrLn (showSDoc (text "Failed, modules loaded: " <> mod_commas)))
1168     Succeeded  ->
1169        io (putStrLn (showSDoc (text "Ok, modules loaded: " <> mod_commas)))
1170
1171
1172 typeOfExpr :: String -> GHCi ()
1173 typeOfExpr str 
1174   = do cms <- getSession
1175        maybe_ty <- io (GHC.exprType cms str)
1176        case maybe_ty of
1177           Nothing -> return ()
1178           Just ty -> do dflags <- getDynFlags
1179                         let pefas = dopt Opt_PrintExplicitForalls dflags
1180                         printForUser $ text str <+> dcolon
1181                                         <+> pprTypeForUser pefas ty
1182
1183 kindOfType :: String -> GHCi ()
1184 kindOfType str 
1185   = do cms <- getSession
1186        maybe_ty <- io (GHC.typeKind cms str)
1187        case maybe_ty of
1188           Nothing    -> return ()
1189           Just ty    -> printForUser $ text str <+> dcolon <+> ppr ty
1190           
1191 quit :: String -> GHCi Bool
1192 quit _ = return True
1193
1194 shellEscape :: String -> GHCi Bool
1195 shellEscape str = io (system str >> return False)
1196
1197 -----------------------------------------------------------------------------
1198 -- Browsing a module's contents
1199
1200 browseCmd :: Bool -> String -> GHCi ()
1201 browseCmd bang m = 
1202   case words m of
1203     ['*':s] | looksLikeModuleName s -> do 
1204         m <-  wantInterpretedModule s
1205         browseModule bang m False
1206     [s] | looksLikeModuleName s -> do
1207         m <- lookupModule s
1208         browseModule bang m True
1209     [] -> do
1210         s <- getSession
1211         (as,bs) <- io $ GHC.getContext s
1212                 -- Guess which module the user wants to browse.  Pick
1213                 -- modules that are interpreted first.  The most
1214                 -- recently-added module occurs last, it seems.
1215         case (as,bs) of
1216           (as@(_:_), _)   -> browseModule bang (last as) True
1217           ([],  bs@(_:_)) -> browseModule bang (last bs) True
1218           ([],  [])  -> throwDyn (CmdLineError ":browse: no current module")
1219     _ -> throwDyn (CmdLineError "syntax:  :browse <module>")
1220
1221 -- without bang, show items in context of their parents and omit children
1222 -- with bang, show class methods and data constructors separately, and
1223 --            indicate import modules, to aid qualifying unqualified names
1224 -- with sorted, sort items alphabetically
1225 browseModule :: Bool -> Module -> Bool -> GHCi ()
1226 browseModule bang modl exports_only = do
1227   s <- getSession
1228   -- :browse! reports qualifiers wrt current context
1229   current_unqual <- io (GHC.getPrintUnqual s)
1230   -- Temporarily set the context to the module we're interested in,
1231   -- just so we can get an appropriate PrintUnqualified
1232   (as,bs) <- io (GHC.getContext s)
1233   prel_mod <- getPrelude
1234   io (if exports_only then GHC.setContext s [] [prel_mod,modl]
1235                       else GHC.setContext s [modl] [])
1236   target_unqual <- io (GHC.getPrintUnqual s)
1237   io (GHC.setContext s as bs)
1238
1239   let unqual = if bang then current_unqual else target_unqual
1240
1241   mb_mod_info <- io $ GHC.getModuleInfo s modl
1242   case mb_mod_info of
1243     Nothing -> throwDyn (CmdLineError ("unknown module: " ++
1244                                 GHC.moduleNameString (GHC.moduleName modl)))
1245     Just mod_info -> do
1246         dflags <- getDynFlags
1247         let names
1248                | exports_only = GHC.modInfoExports mod_info
1249                | otherwise    = GHC.modInfoTopLevelScope mod_info
1250                                 `orElse` []
1251
1252                 -- sort alphabetically name, but putting
1253                 -- locally-defined identifiers first.
1254                 -- We would like to improve this; see #1799.
1255             sorted_names = loc_sort local ++ occ_sort external
1256                 where 
1257                 (local,external) = partition ((==modl) . nameModule) names
1258                 occ_sort = sortBy (compare `on` nameOccName) 
1259                 -- try to sort by src location.  If the first name in
1260                 -- our list has a good source location, then they all should.
1261                 loc_sort names
1262                       | n:_ <- names, isGoodSrcSpan (nameSrcSpan n)
1263                       = sortBy (compare `on` nameSrcSpan) names
1264                       | otherwise
1265                       = occ_sort names
1266
1267         mb_things <- io $ mapM (GHC.lookupName s) sorted_names
1268         let filtered_things = filterOutChildren (\t -> t) (catMaybes mb_things)
1269
1270         rdr_env <- io $ GHC.getGRE s
1271
1272         let pefas              = dopt Opt_PrintExplicitForalls dflags
1273             things | bang      = catMaybes mb_things
1274                    | otherwise = filtered_things
1275             pretty | bang      = pprTyThing
1276                    | otherwise = pprTyThingInContext
1277
1278             labels  [] = text "-- not currently imported"
1279             labels  l  = text $ intercalate "\n" $ map qualifier l
1280             qualifier  = maybe "-- defined locally" 
1281                              (("-- imported via "++) . intercalate ", " 
1282                                . map GHC.moduleNameString)
1283             importInfo = RdrName.getGRE_NameQualifier_maybes rdr_env
1284             modNames   = map (importInfo . GHC.getName) things
1285                                         
1286             -- annotate groups of imports with their import modules
1287             -- the default ordering is somewhat arbitrary, so we group 
1288             -- by header and sort groups; the names themselves should
1289             -- really come in order of source appearance.. (trac #1799)
1290             annotate mts = concatMap (\(m,ts)->labels m:ts)
1291                          $ sortBy cmpQualifiers $ group mts
1292               where cmpQualifiers = 
1293                       compare `on` (map (fmap (map moduleNameFS)) . fst)
1294             group []            = []
1295             group mts@((m,_):_) = (m,map snd g) : group ng
1296               where (g,ng) = partition ((==m).fst) mts
1297
1298         let prettyThings = map (pretty pefas) things
1299             prettyThings' | bang      = annotate $ zip modNames prettyThings
1300                           | otherwise = prettyThings
1301         io (putStrLn $ showSDocForUser unqual (vcat prettyThings'))
1302         -- ToDo: modInfoInstances currently throws an exception for
1303         -- package modules.  When it works, we can do this:
1304         --        $$ vcat (map GHC.pprInstance (GHC.modInfoInstances mod_info))
1305
1306 -----------------------------------------------------------------------------
1307 -- Setting the module context
1308
1309 setContext :: String -> GHCi ()
1310 setContext str
1311   | all sensible mods = fn mods
1312   | otherwise = throwDyn (CmdLineError "syntax:  :module [+/-] [*]M1 ... [*]Mn")
1313   where
1314     (fn, mods) = case str of 
1315                         '+':stuff -> (addToContext,      words stuff)
1316                         '-':stuff -> (removeFromContext, words stuff)
1317                         stuff     -> (newContext,        words stuff) 
1318
1319     sensible ('*':m) = looksLikeModuleName m
1320     sensible m       = looksLikeModuleName m
1321
1322 separate :: Session -> [String] -> [Module] -> [Module] 
1323         -> GHCi ([Module],[Module])
1324 separate _       []             as bs = return (as,bs)
1325 separate session (('*':str):ms) as bs = do
1326   m <- wantInterpretedModule str
1327   separate session ms (m:as) bs
1328 separate session (str:ms) as bs = do
1329   m <- lookupModule str
1330   separate session ms as (m:bs)
1331
1332 newContext :: [String] -> GHCi ()
1333 newContext strs = do
1334   s <- getSession
1335   (as,bs) <- separate s strs [] []
1336   prel_mod <- getPrelude
1337   let bs' = if null as && prel_mod `notElem` bs then prel_mod:bs else bs
1338   io $ GHC.setContext s as bs'
1339
1340
1341 addToContext :: [String] -> GHCi ()
1342 addToContext strs = do
1343   s <- getSession
1344   (as,bs) <- io $ GHC.getContext s
1345
1346   (new_as,new_bs) <- separate s strs [] []
1347
1348   let as_to_add = new_as \\ (as ++ bs)
1349       bs_to_add = new_bs \\ (as ++ bs)
1350
1351   io $ GHC.setContext s (as ++ as_to_add) (bs ++ bs_to_add)
1352
1353
1354 removeFromContext :: [String] -> GHCi ()
1355 removeFromContext strs = do
1356   s <- getSession
1357   (as,bs) <- io $ GHC.getContext s
1358
1359   (as_to_remove,bs_to_remove) <- separate s strs [] []
1360
1361   let as' = as \\ (as_to_remove ++ bs_to_remove)
1362       bs' = bs \\ (as_to_remove ++ bs_to_remove)
1363
1364   io $ GHC.setContext s as' bs'
1365
1366 ----------------------------------------------------------------------------
1367 -- Code for `:set'
1368
1369 -- set options in the interpreter.  Syntax is exactly the same as the
1370 -- ghc command line, except that certain options aren't available (-C,
1371 -- -E etc.)
1372 --
1373 -- This is pretty fragile: most options won't work as expected.  ToDo:
1374 -- figure out which ones & disallow them.
1375
1376 setCmd :: String -> GHCi ()
1377 setCmd ""
1378   = do st <- getGHCiState
1379        let opts = options st
1380        io $ putStrLn (showSDoc (
1381               text "options currently set: " <> 
1382               if null opts
1383                    then text "none."
1384                    else hsep (map (\o -> char '+' <> text (optToStr o)) opts)
1385            ))
1386        dflags <- getDynFlags
1387        io $ putStrLn (showSDoc (
1388           vcat (text "GHCi-specific dynamic flag settings:" 
1389                :map (flagSetting dflags) ghciFlags)
1390           ))
1391        io $ putStrLn (showSDoc (
1392           vcat (text "other dynamic, non-language, flag settings:" 
1393                :map (flagSetting dflags) nonLanguageDynFlags)
1394           ))
1395   where flagSetting dflags (str,f)
1396           | dopt f dflags = text "  " <> text "-f"    <> text str
1397           | otherwise     = text "  " <> text "-fno-" <> text str
1398         (ghciFlags,others)  = partition (\(_,f)->f `elem` flags) 
1399                                         DynFlags.fFlags
1400         nonLanguageDynFlags = filter (\(_,f)->not $ f `elem` map snd xFlags) 
1401                                      others
1402         flags = [Opt_PrintExplicitForalls
1403                 ,Opt_PrintBindResult
1404                 ,Opt_BreakOnException
1405                 ,Opt_BreakOnError
1406                 ,Opt_PrintEvldWithShow
1407                 ] 
1408 setCmd str
1409   = case getCmd str of
1410     Right ("args",   rest) ->
1411         case toArgs rest of
1412             Left err -> io (hPutStrLn stderr err)
1413             Right args -> setArgs args
1414     Right ("prog",   rest) ->
1415         case toArgs rest of
1416             Right [prog] -> setProg prog
1417             _ -> io (hPutStrLn stderr "syntax: :set prog <progname>")
1418     Right ("prompt", rest) -> setPrompt $ dropWhile isSpace rest
1419     Right ("editor", rest) -> setEditor $ dropWhile isSpace rest
1420     Right ("stop",   rest) -> setStop   $ dropWhile isSpace rest
1421     _ -> case toArgs str of
1422          Left err -> io (hPutStrLn stderr err)
1423          Right wds -> setOptions wds
1424
1425 setArgs, setOptions :: [String] -> GHCi ()
1426 setProg, setEditor, setStop, setPrompt :: String -> GHCi ()
1427
1428 setArgs args = do
1429   st <- getGHCiState
1430   setGHCiState st{ args = args }
1431
1432 setProg prog = do
1433   st <- getGHCiState
1434   setGHCiState st{ progname = prog }
1435
1436 setEditor cmd = do
1437   st <- getGHCiState
1438   setGHCiState st{ editor = cmd }
1439
1440 setStop str@(c:_) | isDigit c
1441   = do let (nm_str,rest) = break (not.isDigit) str
1442            nm = read nm_str
1443        st <- getGHCiState
1444        let old_breaks = breaks st
1445        if all ((/= nm) . fst) old_breaks
1446               then printForUser (text "Breakpoint" <+> ppr nm <+>
1447                                  text "does not exist")
1448               else do
1449        let new_breaks = map fn old_breaks
1450            fn (i,loc) | i == nm   = (i,loc { onBreakCmd = dropWhile isSpace rest })
1451                       | otherwise = (i,loc)
1452        setGHCiState st{ breaks = new_breaks }
1453 setStop cmd = do
1454   st <- getGHCiState
1455   setGHCiState st{ stop = cmd }
1456
1457 setPrompt value = do
1458   st <- getGHCiState
1459   if null value
1460       then io $ hPutStrLn stderr $ "syntax: :set prompt <prompt>, currently \"" ++ prompt st ++ "\""
1461       else setGHCiState st{ prompt = remQuotes value }
1462   where
1463      remQuotes ('\"':xs) | not (null xs) && last xs == '\"' = init xs
1464      remQuotes x = x
1465
1466 setOptions wds =
1467    do -- first, deal with the GHCi opts (+s, +t, etc.)
1468       let (plus_opts, minus_opts)  = partitionWith isPlus wds
1469       mapM_ setOpt plus_opts
1470       -- then, dynamic flags
1471       newDynFlags minus_opts
1472
1473 newDynFlags :: [String] -> GHCi ()
1474 newDynFlags minus_opts = do
1475       dflags <- getDynFlags
1476       let pkg_flags = packageFlags dflags
1477       (dflags',leftovers) <- io $ GHC.parseDynamicFlags dflags minus_opts
1478
1479       if (not (null leftovers))
1480                 then throwDyn (CmdLineError ("unrecognised flags: " ++ 
1481                                                 unwords leftovers))
1482                 else return ()
1483
1484       new_pkgs <- setDynFlags dflags'
1485
1486       -- if the package flags changed, we should reset the context
1487       -- and link the new packages.
1488       dflags <- getDynFlags
1489       when (packageFlags dflags /= pkg_flags) $ do
1490         io $ hPutStrLn stderr "package flags have changed, ressetting and loading new packages..."
1491         session <- getSession
1492         io (GHC.setTargets session [])
1493         io (GHC.load session LoadAllTargets)
1494         io (linkPackages dflags new_pkgs)
1495         -- package flags changed, we can't re-use any of the old context
1496         setContextAfterLoad session ([],[]) []
1497       return ()
1498
1499
1500 unsetOptions :: String -> GHCi ()
1501 unsetOptions str
1502   = do -- first, deal with the GHCi opts (+s, +t, etc.)
1503        let opts = words str
1504            (minus_opts, rest1) = partition isMinus opts
1505            (plus_opts, rest2)  = partitionWith isPlus rest1
1506
1507        if (not (null rest2)) 
1508           then io (putStrLn ("unknown option: '" ++ head rest2 ++ "'"))
1509           else do
1510
1511        mapM_ unsetOpt plus_opts
1512  
1513        let no_flag ('-':'f':rest) = return ("-fno-" ++ rest)
1514            no_flag f = throwDyn (ProgramError ("don't know how to reverse " ++ f))
1515
1516        no_flags <- mapM no_flag minus_opts
1517        newDynFlags no_flags
1518
1519 isMinus :: String -> Bool
1520 isMinus ('-':_) = True
1521 isMinus _ = False
1522
1523 isPlus :: String -> Either String String
1524 isPlus ('+':opt) = Left opt
1525 isPlus other     = Right other
1526
1527 setOpt, unsetOpt :: String -> GHCi ()
1528
1529 setOpt str
1530   = case strToGHCiOpt str of
1531         Nothing -> io (putStrLn ("unknown option: '" ++ str ++ "'"))
1532         Just o  -> setOption o
1533
1534 unsetOpt str
1535   = case strToGHCiOpt str of
1536         Nothing -> io (putStrLn ("unknown option: '" ++ str ++ "'"))
1537         Just o  -> unsetOption o
1538
1539 strToGHCiOpt :: String -> (Maybe GHCiOption)
1540 strToGHCiOpt "s" = Just ShowTiming
1541 strToGHCiOpt "t" = Just ShowType
1542 strToGHCiOpt "r" = Just RevertCAFs
1543 strToGHCiOpt _   = Nothing
1544
1545 optToStr :: GHCiOption -> String
1546 optToStr ShowTiming = "s"
1547 optToStr ShowType   = "t"
1548 optToStr RevertCAFs = "r"
1549
1550 -- ---------------------------------------------------------------------------
1551 -- code for `:show'
1552
1553 showCmd :: String -> GHCi ()
1554 showCmd str = do
1555   st <- getGHCiState
1556   case words str of
1557         ["args"]     -> io $ putStrLn (show (args st))
1558         ["prog"]     -> io $ putStrLn (show (progname st))
1559         ["prompt"]   -> io $ putStrLn (show (prompt st))
1560         ["editor"]   -> io $ putStrLn (show (editor st))
1561         ["stop"]     -> io $ putStrLn (show (stop st))
1562         ["modules" ] -> showModules
1563         ["bindings"] -> showBindings
1564         ["linker"]   -> io showLinkerState
1565         ["breaks"]   -> showBkptTable
1566         ["context"]  -> showContext
1567         ["packages"]  -> showPackages
1568         ["languages"]  -> showLanguages
1569         _ -> throwDyn (CmdLineError "syntax:  :show [args|prog|prompt|editor|stop|modules|bindings|breaks|context]")
1570
1571 showModules :: GHCi ()
1572 showModules = do
1573   session <- getSession
1574   loaded_mods <- getLoadedModules session
1575         -- we want *loaded* modules only, see #1734
1576   let show_one ms = do m <- io (GHC.showModule session ms); io (putStrLn m)
1577   mapM_ show_one loaded_mods
1578
1579 getLoadedModules :: GHC.Session -> GHCi [GHC.ModSummary]
1580 getLoadedModules session = do
1581   graph <- io (GHC.getModuleGraph session)
1582   filterM (io . GHC.isLoaded session . GHC.ms_mod_name) graph
1583
1584 showBindings :: GHCi ()
1585 showBindings = do
1586   s <- getSession
1587   bindings <- io (GHC.getBindings s)
1588   docs     <- io$ pprTypeAndContents s 
1589                   [ id | AnId id <- sortBy compareTyThings bindings]
1590   printForUserPartWay docs
1591
1592 compareTyThings :: TyThing -> TyThing -> Ordering
1593 t1 `compareTyThings` t2 = getName t1 `compareNames` getName t2
1594
1595 printTyThing :: TyThing -> GHCi ()
1596 printTyThing tyth = do dflags <- getDynFlags
1597                        let pefas = dopt Opt_PrintExplicitForalls dflags
1598                        printForUser (pprTyThing pefas tyth)
1599
1600 showBkptTable :: GHCi ()
1601 showBkptTable = do
1602   st <- getGHCiState
1603   printForUser $ prettyLocations (breaks st)
1604
1605 showContext :: GHCi ()
1606 showContext = do
1607    session <- getSession
1608    resumes <- io $ GHC.getResumeContext session
1609    printForUser $ vcat (map pp_resume (reverse resumes))
1610   where
1611    pp_resume resume =
1612         ptext SLIT("--> ") <> text (GHC.resumeStmt resume)
1613         $$ nest 2 (ptext SLIT("Stopped at") <+> ppr (GHC.resumeSpan resume))
1614
1615 showPackages :: GHCi ()
1616 showPackages = do
1617   pkg_flags <- fmap packageFlags getDynFlags
1618   io $ putStrLn $ showSDoc $ vcat $
1619     text ("active package flags:"++if null pkg_flags then " none" else "")
1620     : map showFlag pkg_flags
1621   pkg_ids <- fmap (preloadPackages . pkgState) getDynFlags
1622   io $ putStrLn $ showSDoc $ vcat $
1623     text "packages currently loaded:" 
1624     : map (nest 2 . text . packageIdString) pkg_ids
1625   where showFlag (ExposePackage p) = text $ "  -package " ++ p
1626         showFlag (HidePackage p)   = text $ "  -hide-package " ++ p
1627         showFlag (IgnorePackage p) = text $ "  -ignore-package " ++ p
1628
1629 showLanguages :: GHCi ()
1630 showLanguages = do
1631    dflags <- getDynFlags
1632    io $ putStrLn $ showSDoc $ vcat $
1633       text "active language flags:" :
1634       [text ("  -X" ++ str) | (str,f) <- DynFlags.xFlags, dopt f dflags]
1635
1636 -- -----------------------------------------------------------------------------
1637 -- Completion
1638
1639 completeNone :: String -> IO [String]
1640 completeNone _w = return []
1641
1642 completeMacro, completeIdentifier, completeModule,
1643     completeHomeModule, completeSetOptions, completeFilename,
1644     completeHomeModuleOrFile 
1645     :: String -> IO [String]
1646
1647 #ifdef USE_READLINE
1648 completeWord :: String -> Int -> Int -> IO (Maybe (String, [String]))
1649 completeWord w start end = do
1650   line <- Readline.getLineBuffer
1651   let line_words = words (dropWhile isSpace line)
1652   case w of
1653      ':':_ | all isSpace (take (start-1) line) -> wrapCompleter completeCmd w
1654      _other
1655         | ((':':c) : _) <- line_words -> do
1656            completionVars <- lookupCompletionVars c
1657            case completionVars of
1658              (Nothing,complete) -> wrapCompleter complete w
1659              (Just breakChars,complete) 
1660                     -> let (n,w') = selectWord 
1661                                         (words' (`elem` breakChars) 0 line)
1662                            complete' w = do rets <- complete w
1663                                             return (map (drop n) rets)
1664                        in wrapCompleter complete' w'
1665         | ("import" : _) <- line_words ->
1666                 wrapCompleter completeModule w
1667         | otherwise     -> do
1668                 --printf "complete %s, start = %d, end = %d\n" w start end
1669                 wrapCompleter completeIdentifier w
1670     where words' _ _ [] = []
1671           words' isBreak n str = let (w,r) = break isBreak str
1672                                      (s,r') = span isBreak r
1673                                  in (n,w):words' isBreak (n+length w+length s) r'
1674           -- In a Haskell expression we want to parse 'a-b' as three words
1675           -- where a compiler flag (ie. -fno-monomorphism-restriction) should
1676           -- only be a single word.
1677           selectWord [] = (0,w)
1678           selectWord ((offset,x):xs)
1679               | offset+length x >= start = (start-offset,take (end-offset) x)
1680               | otherwise = selectWord xs
1681           
1682           lookupCompletionVars ('!':_) = return (Just filenameWordBreakChars,
1683                                             completeFilename)
1684           lookupCompletionVars c = do
1685               maybe_cmd <- lookupCommand' c
1686               case maybe_cmd of
1687                   Just (_,_,ws,f) -> return (ws,f)
1688                   Nothing -> return (Just filenameWordBreakChars,
1689                                         completeFilename)
1690
1691
1692 completeCmd :: String -> IO [String]
1693 completeCmd w = do
1694   cmds <- readIORef macros_ref
1695   return (filter (w `isPrefixOf`) (map (':':) 
1696              (map cmdName (builtin_commands ++ cmds))))
1697
1698 completeMacro w = do
1699   cmds <- readIORef macros_ref
1700   return (filter (w `isPrefixOf`) (map cmdName cmds))
1701
1702 completeIdentifier w = do
1703   s <- restoreSession
1704   rdrs <- GHC.getRdrNamesInScope s
1705   return (filter (w `isPrefixOf`) (map (showSDoc.ppr) rdrs))
1706
1707 completeModule w = do
1708   s <- restoreSession
1709   dflags <- GHC.getSessionDynFlags s
1710   let pkg_mods = allExposedModules dflags
1711   return (filter (w `isPrefixOf`) (map (showSDoc.ppr) pkg_mods))
1712
1713 completeHomeModule w = do
1714   s <- restoreSession
1715   g <- GHC.getModuleGraph s
1716   let home_mods = map GHC.ms_mod_name g
1717   return (filter (w `isPrefixOf`) (map (showSDoc.ppr) home_mods))
1718
1719 completeSetOptions w = do
1720   return (filter (w `isPrefixOf`) options)
1721     where options = "args":"prog":allFlags
1722
1723 completeFilename w = do
1724     ws <- Readline.filenameCompletionFunction w
1725     case ws of
1726         -- If we only found one result, and it's a directory, 
1727         -- add a trailing slash.
1728         [file] -> do
1729                 isDir <- expandPathIO file >>= doesDirectoryExist
1730                 if isDir && last file /= '/'
1731                     then return [file ++ "/"]
1732                     else return [file]
1733         _ -> return ws
1734                 
1735
1736 completeHomeModuleOrFile = unionComplete completeHomeModule completeFilename
1737
1738 unionComplete :: (String -> IO [String]) -> (String -> IO [String]) -> String -> IO [String]
1739 unionComplete f1 f2 w = do
1740   s1 <- f1 w
1741   s2 <- f2 w
1742   return (s1 ++ s2)
1743
1744 wrapCompleter :: (String -> IO [String]) -> String -> IO (Maybe (String,[String]))
1745 wrapCompleter fun w =  do
1746   strs <- fun w
1747   case strs of
1748     []  -> Readline.setAttemptedCompletionOver True >> return Nothing
1749     [x] -> -- Add a trailing space, unless it already has an appended slash.
1750            let appended = if last x == '/' then x else x ++ " "
1751            in return (Just (appended,[]))
1752     xs  -> case getCommonPrefix xs of
1753                 ""   -> return (Just ("",xs))
1754                 pref -> return (Just (pref,xs))
1755
1756 getCommonPrefix :: [String] -> String
1757 getCommonPrefix [] = ""
1758 getCommonPrefix (s:ss) = foldl common s ss
1759   where common _s "" = ""
1760         common "" _s = ""
1761         common (c:cs) (d:ds)
1762            | c == d = c : common cs ds
1763            | otherwise = ""
1764
1765 allExposedModules :: DynFlags -> [ModuleName]
1766 allExposedModules dflags 
1767  = concat (map exposedModules (filter exposed (eltsUFM pkg_db)))
1768  where
1769   pkg_db = pkgIdMap (pkgState dflags)
1770 #else
1771 completeMacro      = completeNone
1772 completeIdentifier = completeNone
1773 completeModule     = completeNone
1774 completeHomeModule = completeNone
1775 completeSetOptions = completeNone
1776 completeFilename   = completeNone
1777 completeHomeModuleOrFile=completeNone
1778 #endif
1779
1780 -- ---------------------------------------------------------------------------
1781 -- User code exception handling
1782
1783 -- This is the exception handler for exceptions generated by the
1784 -- user's code and exceptions coming from children sessions; 
1785 -- it normally just prints out the exception.  The
1786 -- handler must be recursive, in case showing the exception causes
1787 -- more exceptions to be raised.
1788 --
1789 -- Bugfix: if the user closed stdout or stderr, the flushing will fail,
1790 -- raising another exception.  We therefore don't put the recursive
1791 -- handler arond the flushing operation, so if stderr is closed
1792 -- GHCi will just die gracefully rather than going into an infinite loop.
1793 handler :: Exception -> GHCi Bool
1794
1795 handler exception = do
1796   flushInterpBuffers
1797   io installSignalHandlers
1798   ghciHandle handler (showException exception >> return False)
1799
1800 showException :: Exception -> GHCi ()
1801 showException (DynException dyn) =
1802   case fromDynamic dyn of
1803     Nothing               -> io (putStrLn ("*** Exception: (unknown)"))
1804     Just Interrupted      -> io (putStrLn "Interrupted.")
1805     Just (CmdLineError s) -> io (putStrLn s)     -- omit the location for CmdLineError
1806     Just ph@PhaseFailed{} -> io (putStrLn (showGhcException ph "")) -- ditto
1807     Just other_ghc_ex     -> io (print other_ghc_ex)
1808
1809 showException other_exception
1810   = io (putStrLn ("*** Exception: " ++ show other_exception))
1811
1812 -----------------------------------------------------------------------------
1813 -- recursive exception handlers
1814
1815 -- Don't forget to unblock async exceptions in the handler, or if we're
1816 -- in an exception loop (eg. let a = error a in a) the ^C exception
1817 -- may never be delivered.  Thanks to Marcin for pointing out the bug.
1818
1819 ghciHandle :: (Exception -> GHCi a) -> GHCi a -> GHCi a
1820 ghciHandle h (GHCi m) = GHCi $ \s -> 
1821    Exception.catch (m s) 
1822         (\e -> unGHCi (ghciUnblock (h e)) s)
1823
1824 ghciUnblock :: GHCi a -> GHCi a
1825 ghciUnblock (GHCi a) = GHCi $ \s -> Exception.unblock (a s)
1826
1827
1828 -- ----------------------------------------------------------------------------
1829 -- Utils
1830
1831 expandPath :: String -> GHCi String
1832 expandPath path = io (expandPathIO path)
1833
1834 expandPathIO :: String -> IO String
1835 expandPathIO path = 
1836   case dropWhile isSpace path of
1837    ('~':d) -> do
1838         tilde <- getHomeDirectory -- will fail if HOME not defined
1839         return (tilde ++ '/':d)
1840    other -> 
1841         return other
1842
1843 wantInterpretedModule :: String -> GHCi Module
1844 wantInterpretedModule str = do
1845    session <- getSession
1846    modl <- lookupModule str
1847    is_interpreted <- io (GHC.moduleIsInterpreted session modl)
1848    when (not is_interpreted) $
1849        throwDyn (CmdLineError ("module '" ++ str ++ "' is not interpreted"))
1850    return modl
1851
1852 wantNameFromInterpretedModule :: (Name -> SDoc -> GHCi ()) -> String
1853                               -> (Name -> GHCi ())
1854                               -> GHCi ()
1855 wantNameFromInterpretedModule noCanDo str and_then = do
1856    session <- getSession
1857    names <- io $ GHC.parseName session str
1858    case names of
1859       []    -> return ()
1860       (n:_) -> do
1861             let modl = GHC.nameModule n
1862             if not (GHC.isExternalName n)
1863                then noCanDo n $ ppr n <>
1864                                 text " is not defined in an interpreted module"
1865                else do
1866             is_interpreted <- io (GHC.moduleIsInterpreted session modl)
1867             if not is_interpreted
1868                then noCanDo n $ text "module " <> ppr modl <>
1869                                 text " is not interpreted"
1870                else and_then n
1871
1872 -- -----------------------------------------------------------------------------
1873 -- commands for debugger
1874
1875 sprintCmd, printCmd, forceCmd :: String -> GHCi ()
1876 sprintCmd = pprintCommand False False
1877 printCmd  = pprintCommand True False
1878 forceCmd  = pprintCommand False True
1879
1880 pprintCommand :: Bool -> Bool -> String -> GHCi ()
1881 pprintCommand bind force str = do
1882   session <- getSession
1883   io $ pprintClosureCommand session bind force str
1884
1885 stepCmd :: String -> GHCi ()
1886 stepCmd []         = doContinue (const True) GHC.SingleStep
1887 stepCmd expression = do runStmt expression GHC.SingleStep; return ()
1888
1889 stepLocalCmd :: String -> GHCi ()
1890 stepLocalCmd  [] = do 
1891   mb_span <- getCurrentBreakSpan
1892   case mb_span of
1893     Nothing  -> stepCmd []
1894     Just loc -> do
1895        Just mod <- getCurrentBreakModule
1896        current_toplevel_decl <- enclosingTickSpan mod loc
1897        doContinue (`isSubspanOf` current_toplevel_decl) GHC.SingleStep
1898
1899 stepLocalCmd expression = stepCmd expression
1900
1901 stepModuleCmd :: String -> GHCi ()
1902 stepModuleCmd  [] = do 
1903   mb_span <- getCurrentBreakSpan
1904   case mb_span of
1905     Nothing  -> stepCmd []
1906     Just _ -> do
1907        Just span <- getCurrentBreakSpan
1908        let f some_span = optSrcSpanFileName span == optSrcSpanFileName some_span
1909        doContinue f GHC.SingleStep
1910
1911 stepModuleCmd expression = stepCmd expression
1912
1913 -- | Returns the span of the largest tick containing the srcspan given
1914 enclosingTickSpan :: Module -> SrcSpan -> GHCi SrcSpan
1915 enclosingTickSpan mod src = do
1916   ticks <- getTickArray mod
1917   let line = srcSpanStartLine src
1918   ASSERT (inRange (bounds ticks) line) do
1919   let enclosing_spans = [ span | (_,span) <- ticks ! line
1920                                , srcSpanEnd span >= srcSpanEnd src]
1921   return . head . sortBy leftmost_largest $ enclosing_spans
1922
1923 traceCmd :: String -> GHCi ()
1924 traceCmd []         = doContinue (const True) GHC.RunAndLogSteps
1925 traceCmd expression = do runStmt expression GHC.RunAndLogSteps; return ()
1926
1927 continueCmd :: String -> GHCi ()
1928 continueCmd = noArgs $ doContinue (const True) GHC.RunToCompletion
1929
1930 -- doContinue :: SingleStep -> GHCi ()
1931 doContinue :: (SrcSpan -> Bool) -> SingleStep -> GHCi ()
1932 doContinue pred step = do 
1933   session <- getSession
1934   runResult <- io $ GHC.resume session step
1935   afterRunStmt pred runResult
1936   return ()
1937
1938 abandonCmd :: String -> GHCi ()
1939 abandonCmd = noArgs $ do
1940   s <- getSession
1941   b <- io $ GHC.abandon s -- the prompt will change to indicate the new context
1942   when (not b) $ io $ putStrLn "There is no computation running."
1943   return ()
1944
1945 deleteCmd :: String -> GHCi ()
1946 deleteCmd argLine = do
1947    deleteSwitch $ words argLine
1948    where
1949    deleteSwitch :: [String] -> GHCi ()
1950    deleteSwitch [] = 
1951       io $ putStrLn "The delete command requires at least one argument."
1952    -- delete all break points
1953    deleteSwitch ("*":_rest) = discardActiveBreakPoints
1954    deleteSwitch idents = do
1955       mapM_ deleteOneBreak idents 
1956       where
1957       deleteOneBreak :: String -> GHCi ()
1958       deleteOneBreak str
1959          | all isDigit str = deleteBreak (read str)
1960          | otherwise = return ()
1961
1962 historyCmd :: String -> GHCi ()
1963 historyCmd arg
1964   | null arg        = history 20
1965   | all isDigit arg = history (read arg)
1966   | otherwise       = io $ putStrLn "Syntax:  :history [num]"
1967   where
1968   history num = do
1969     s <- getSession
1970     resumes <- io $ GHC.getResumeContext s
1971     case resumes of
1972       [] -> io $ putStrLn "Not stopped at a breakpoint"
1973       (r:_) -> do
1974         let hist = GHC.resumeHistory r
1975             (took,rest) = splitAt num hist
1976         case hist of
1977           [] -> io $ putStrLn $ 
1978                    "Empty history. Perhaps you forgot to use :trace?"
1979           _  -> do
1980                  spans <- mapM (io . GHC.getHistorySpan s) took
1981                  let nums  = map (printf "-%-3d:") [(1::Int)..]
1982                      names = map GHC.historyEnclosingDecl took
1983                  printForUser (vcat(zipWith3 
1984                                  (\x y z -> x <+> y <+> z) 
1985                                  (map text nums) 
1986                                  (map (bold . ppr) names)
1987                                  (map (parens . ppr) spans)))
1988                  io $ putStrLn $ if null rest then "<end of history>" else "..."
1989
1990 bold :: SDoc -> SDoc
1991 bold c | do_bold   = text start_bold <> c <> text end_bold
1992        | otherwise = c
1993
1994 backCmd :: String -> GHCi ()
1995 backCmd = noArgs $ do
1996   s <- getSession
1997   (names, _, span) <- io $ GHC.back s
1998   printForUser $ ptext SLIT("Logged breakpoint at") <+> ppr span
1999   printTypeOfNames s names
2000    -- run the command set with ":set stop <cmd>"
2001   st <- getGHCiState
2002   enqueueCommands [stop st]
2003
2004 forwardCmd :: String -> GHCi ()
2005 forwardCmd = noArgs $ do
2006   s <- getSession
2007   (names, ix, span) <- io $ GHC.forward s
2008   printForUser $ (if (ix == 0)
2009                     then ptext SLIT("Stopped at")
2010                     else ptext SLIT("Logged breakpoint at")) <+> ppr span
2011   printTypeOfNames s names
2012    -- run the command set with ":set stop <cmd>"
2013   st <- getGHCiState
2014   enqueueCommands [stop st]
2015
2016 -- handle the "break" command
2017 breakCmd :: String -> GHCi ()
2018 breakCmd argLine = do
2019    session <- getSession
2020    breakSwitch session $ words argLine
2021
2022 breakSwitch :: Session -> [String] -> GHCi ()
2023 breakSwitch _session [] = do
2024    io $ putStrLn "The break command requires at least one argument."
2025 breakSwitch session (arg1:rest) 
2026    | looksLikeModuleName arg1 = do
2027         mod <- wantInterpretedModule arg1
2028         breakByModule mod rest
2029    | all isDigit arg1 = do
2030         (toplevel, _) <- io $ GHC.getContext session 
2031         case toplevel of
2032            (mod : _) -> breakByModuleLine mod (read arg1) rest
2033            [] -> do 
2034               io $ putStrLn "Cannot find default module for breakpoint." 
2035               io $ putStrLn "Perhaps no modules are loaded for debugging?"
2036    | otherwise = do -- try parsing it as an identifier
2037         wantNameFromInterpretedModule noCanDo arg1 $ \name -> do
2038         let loc = GHC.srcSpanStart (GHC.nameSrcSpan name)
2039         if GHC.isGoodSrcLoc loc
2040                then findBreakAndSet (GHC.nameModule name) $ 
2041                          findBreakByCoord (Just (GHC.srcLocFile loc))
2042                                           (GHC.srcLocLine loc, 
2043                                            GHC.srcLocCol loc)
2044                else noCanDo name $ text "can't find its location: " <> ppr loc
2045        where
2046           noCanDo n why = printForUser $
2047                 text "cannot set breakpoint on " <> ppr n <> text ": " <> why
2048
2049 breakByModule :: Module -> [String] -> GHCi () 
2050 breakByModule mod (arg1:rest)
2051    | all isDigit arg1 = do  -- looks like a line number
2052         breakByModuleLine mod (read arg1) rest
2053 breakByModule _ _
2054    = breakSyntax
2055
2056 breakByModuleLine :: Module -> Int -> [String] -> GHCi ()
2057 breakByModuleLine mod line args
2058    | [] <- args = findBreakAndSet mod $ findBreakByLine line
2059    | [col] <- args, all isDigit col =
2060         findBreakAndSet mod $ findBreakByCoord Nothing (line, read col)
2061    | otherwise = breakSyntax
2062
2063 breakSyntax :: a
2064 breakSyntax = throwDyn (CmdLineError "Syntax: :break [<mod>] <line> [<column>]")
2065
2066 findBreakAndSet :: Module -> (TickArray -> Maybe (Int, SrcSpan)) -> GHCi ()
2067 findBreakAndSet mod lookupTickTree = do 
2068    tickArray <- getTickArray mod
2069    (breakArray, _) <- getModBreak mod
2070    case lookupTickTree tickArray of 
2071       Nothing  -> io $ putStrLn $ "No breakpoints found at that location."
2072       Just (tick, span) -> do
2073          success <- io $ setBreakFlag True breakArray tick 
2074          if success 
2075             then do
2076                (alreadySet, nm) <- 
2077                      recordBreak $ BreakLocation
2078                              { breakModule = mod
2079                              , breakLoc = span
2080                              , breakTick = tick
2081                              , onBreakCmd = ""
2082                              }
2083                printForUser $
2084                   text "Breakpoint " <> ppr nm <>
2085                   if alreadySet 
2086                      then text " was already set at " <> ppr span
2087                      else text " activated at " <> ppr span
2088             else do
2089             printForUser $ text "Breakpoint could not be activated at" 
2090                                  <+> ppr span
2091
2092 -- When a line number is specified, the current policy for choosing
2093 -- the best breakpoint is this:
2094 --    - the leftmost complete subexpression on the specified line, or
2095 --    - the leftmost subexpression starting on the specified line, or
2096 --    - the rightmost subexpression enclosing the specified line
2097 --
2098 findBreakByLine :: Int -> TickArray -> Maybe (BreakIndex,SrcSpan)
2099 findBreakByLine line arr
2100   | not (inRange (bounds arr) line) = Nothing
2101   | otherwise =
2102     listToMaybe (sortBy (leftmost_largest `on` snd)  complete)   `mplus`
2103     listToMaybe (sortBy (leftmost_smallest `on` snd) incomplete) `mplus`
2104     listToMaybe (sortBy (rightmost `on` snd) ticks)
2105   where 
2106         ticks = arr ! line
2107
2108         starts_here = [ tick | tick@(_,span) <- ticks,
2109                                GHC.srcSpanStartLine span == line ]
2110
2111         (complete,incomplete) = partition ends_here starts_here
2112             where ends_here (_,span) = GHC.srcSpanEndLine span == line
2113
2114 findBreakByCoord :: Maybe FastString -> (Int,Int) -> TickArray
2115                  -> Maybe (BreakIndex,SrcSpan)
2116 findBreakByCoord mb_file (line, col) arr
2117   | not (inRange (bounds arr) line) = Nothing
2118   | otherwise =
2119     listToMaybe (sortBy (rightmost `on` snd) contains ++
2120                  sortBy (leftmost_smallest `on` snd) after_here)
2121   where 
2122         ticks = arr ! line
2123
2124         -- the ticks that span this coordinate
2125         contains = [ tick | tick@(_,span) <- ticks, span `spans` (line,col),
2126                             is_correct_file span ]
2127
2128         is_correct_file span
2129                  | Just f <- mb_file = GHC.srcSpanFile span == f
2130                  | otherwise         = True
2131
2132         after_here = [ tick | tick@(_,span) <- ticks,
2133                               GHC.srcSpanStartLine span == line,
2134                               GHC.srcSpanStartCol span >= col ]
2135
2136 -- For now, use ANSI bold on terminals that we know support it.
2137 -- Otherwise, we add a line of carets under the active expression instead.
2138 -- In particular, on Windows and when running the testsuite (which sets
2139 -- TERM to vt100 for other reasons) we get carets.
2140 -- We really ought to use a proper termcap/terminfo library.
2141 do_bold :: Bool
2142 do_bold = (`isPrefixOf` unsafePerformIO mTerm) `any` ["xterm", "linux"]
2143     where mTerm = System.Environment.getEnv "TERM"
2144                   `Exception.catch` \_ -> return "TERM not set"
2145
2146 start_bold :: String
2147 start_bold = "\ESC[1m"
2148 end_bold :: String
2149 end_bold   = "\ESC[0m"
2150
2151 listCmd :: String -> GHCi ()
2152 listCmd "" = do
2153    mb_span <- getCurrentBreakSpan
2154    case mb_span of
2155       Nothing ->
2156           printForUser $ text "Not stopped at a breakpoint; nothing to list"
2157       Just span
2158        | GHC.isGoodSrcSpan span -> io $ listAround span True
2159        | otherwise ->
2160           do s <- getSession
2161              resumes <- io $ GHC.getResumeContext s
2162              case resumes of
2163                  [] -> panic "No resumes"
2164                  (r:_) ->
2165                      do let traceIt = case GHC.resumeHistory r of
2166                                       [] -> text "rerunning with :trace,"
2167                                       _ -> empty
2168                             doWhat = traceIt <+> text ":back then :list"
2169                         printForUser (text "Unable to list source for" <+>
2170                                       ppr span
2171                                    $$ text "Try" <+> doWhat)
2172 listCmd str = list2 (words str)
2173
2174 list2 :: [String] -> GHCi ()
2175 list2 [arg] | all isDigit arg = do
2176     session <- getSession
2177     (toplevel, _) <- io $ GHC.getContext session 
2178     case toplevel of
2179         [] -> io $ putStrLn "No module to list"
2180         (mod : _) -> listModuleLine mod (read arg)
2181 list2 [arg1,arg2] | looksLikeModuleName arg1, all isDigit arg2 = do
2182         mod <- wantInterpretedModule arg1
2183         listModuleLine mod (read arg2)
2184 list2 [arg] = do
2185         wantNameFromInterpretedModule noCanDo arg $ \name -> do
2186         let loc = GHC.srcSpanStart (GHC.nameSrcSpan name)
2187         if GHC.isGoodSrcLoc loc
2188                then do
2189                   tickArray <- getTickArray (GHC.nameModule name)
2190                   let mb_span = findBreakByCoord (Just (GHC.srcLocFile loc))
2191                                         (GHC.srcLocLine loc, GHC.srcLocCol loc)
2192                                         tickArray
2193                   case mb_span of
2194                     Nothing       -> io $ listAround (GHC.srcLocSpan loc) False
2195                     Just (_,span) -> io $ listAround span False
2196                else
2197                   noCanDo name $ text "can't find its location: " <>
2198                                  ppr loc
2199     where
2200         noCanDo n why = printForUser $
2201             text "cannot list source code for " <> ppr n <> text ": " <> why
2202 list2  _other = 
2203         io $ putStrLn "syntax:  :list [<line> | <module> <line> | <identifier>]"
2204
2205 listModuleLine :: Module -> Int -> GHCi ()
2206 listModuleLine modl line = do
2207    session <- getSession
2208    graph <- io (GHC.getModuleGraph session)
2209    let this = filter ((== modl) . GHC.ms_mod) graph
2210    case this of
2211      [] -> panic "listModuleLine"
2212      summ:_ -> do
2213            let filename = fromJust (ml_hs_file (GHC.ms_location summ))
2214                loc = GHC.mkSrcLoc (mkFastString (filename)) line 0
2215            io $ listAround (GHC.srcLocSpan loc) False
2216
2217 -- | list a section of a source file around a particular SrcSpan.
2218 -- If the highlight flag is True, also highlight the span using
2219 -- start_bold/end_bold.
2220 listAround :: SrcSpan -> Bool -> IO ()
2221 listAround span do_highlight = do
2222       contents <- BS.readFile (unpackFS file)
2223       let 
2224           lines = BS.split '\n' contents
2225           these_lines = take (line2 - line1 + 1 + pad_before + pad_after) $ 
2226                         drop (line1 - 1 - pad_before) $ lines
2227           fst_line = max 1 (line1 - pad_before)
2228           line_nos = [ fst_line .. ]
2229
2230           highlighted | do_highlight = zipWith highlight line_nos these_lines
2231                       | otherwise    = [\p -> BS.concat[p,l] | l <- these_lines]
2232
2233           bs_line_nos = [ BS.pack (show l ++ "  ") | l <- line_nos ]
2234           prefixed = zipWith ($) highlighted bs_line_nos
2235       --
2236       BS.putStrLn (BS.intercalate (BS.pack "\n") prefixed)
2237   where
2238         file  = GHC.srcSpanFile span
2239         line1 = GHC.srcSpanStartLine span
2240         col1  = GHC.srcSpanStartCol span
2241         line2 = GHC.srcSpanEndLine span
2242         col2  = GHC.srcSpanEndCol span
2243
2244         pad_before | line1 == 1 = 0
2245                    | otherwise  = 1
2246         pad_after = 1
2247
2248         highlight | do_bold   = highlight_bold
2249                   | otherwise = highlight_carets
2250
2251         highlight_bold no line prefix
2252           | no == line1 && no == line2
2253           = let (a,r) = BS.splitAt col1 line
2254                 (b,c) = BS.splitAt (col2-col1) r
2255             in
2256             BS.concat [prefix, a,BS.pack start_bold,b,BS.pack end_bold,c]
2257           | no == line1
2258           = let (a,b) = BS.splitAt col1 line in
2259             BS.concat [prefix, a, BS.pack start_bold, b]
2260           | no == line2
2261           = let (a,b) = BS.splitAt col2 line in
2262             BS.concat [prefix, a, BS.pack end_bold, b]
2263           | otherwise   = BS.concat [prefix, line]
2264
2265         highlight_carets no line prefix
2266           | no == line1 && no == line2
2267           = BS.concat [prefix, line, nl, indent, BS.replicate col1 ' ',
2268                                          BS.replicate (col2-col1) '^']
2269           | no == line1
2270           = BS.concat [indent, BS.replicate (col1 - 2) ' ', BS.pack "vv", nl, 
2271                                          prefix, line]
2272           | no == line2
2273           = BS.concat [prefix, line, nl, indent, BS.replicate col2 ' ',
2274                                          BS.pack "^^"]
2275           | otherwise   = BS.concat [prefix, line]
2276          where
2277            indent = BS.pack ("  " ++ replicate (length (show no)) ' ')
2278            nl = BS.singleton '\n'
2279
2280 -- --------------------------------------------------------------------------
2281 -- Tick arrays
2282
2283 getTickArray :: Module -> GHCi TickArray
2284 getTickArray modl = do
2285    st <- getGHCiState
2286    let arrmap = tickarrays st
2287    case lookupModuleEnv arrmap modl of
2288       Just arr -> return arr
2289       Nothing  -> do
2290         (_breakArray, ticks) <- getModBreak modl 
2291         let arr = mkTickArray (assocs ticks)
2292         setGHCiState st{tickarrays = extendModuleEnv arrmap modl arr}
2293         return arr
2294
2295 discardTickArrays :: GHCi ()
2296 discardTickArrays = do
2297    st <- getGHCiState
2298    setGHCiState st{tickarrays = emptyModuleEnv}
2299
2300 mkTickArray :: [(BreakIndex,SrcSpan)] -> TickArray
2301 mkTickArray ticks
2302   = accumArray (flip (:)) [] (1, max_line) 
2303         [ (line, (nm,span)) | (nm,span) <- ticks,
2304                               line <- srcSpanLines span ]
2305     where
2306         max_line = foldr max 0 (map GHC.srcSpanEndLine (map snd ticks))
2307         srcSpanLines span = [ GHC.srcSpanStartLine span .. 
2308                               GHC.srcSpanEndLine span ]
2309
2310 lookupModule :: String -> GHCi Module
2311 lookupModule modName
2312    = do session <- getSession 
2313         io (GHC.findModule session (GHC.mkModuleName modName) Nothing)
2314
2315 -- don't reset the counter back to zero?
2316 discardActiveBreakPoints :: GHCi ()
2317 discardActiveBreakPoints = do
2318    st <- getGHCiState
2319    mapM (turnOffBreak.snd) (breaks st)
2320    setGHCiState $ st { breaks = [] }
2321
2322 deleteBreak :: Int -> GHCi ()
2323 deleteBreak identity = do
2324    st <- getGHCiState
2325    let oldLocations    = breaks st
2326        (this,rest)     = partition (\loc -> fst loc == identity) oldLocations
2327    if null this 
2328       then printForUser (text "Breakpoint" <+> ppr identity <+>
2329                          text "does not exist")
2330       else do
2331            mapM (turnOffBreak.snd) this
2332            setGHCiState $ st { breaks = rest }
2333
2334 turnOffBreak :: BreakLocation -> GHCi Bool
2335 turnOffBreak loc = do
2336   (arr, _) <- getModBreak (breakModule loc)
2337   io $ setBreakFlag False arr (breakTick loc)
2338
2339 getModBreak :: Module -> GHCi (GHC.BreakArray, Array Int SrcSpan)
2340 getModBreak mod = do
2341    session <- getSession
2342    Just mod_info <- io $ GHC.getModuleInfo session mod
2343    let modBreaks  = GHC.modInfoModBreaks mod_info
2344    let array      = GHC.modBreaks_flags modBreaks
2345    let ticks      = GHC.modBreaks_locs  modBreaks
2346    return (array, ticks)
2347
2348 setBreakFlag :: Bool -> GHC.BreakArray -> Int -> IO Bool 
2349 setBreakFlag toggle array index
2350    | toggle    = GHC.setBreakOn array index 
2351    | otherwise = GHC.setBreakOff array index
2352