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