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