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