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