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