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