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