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