Closure inspection in GHCi
[ghc-hetmet.git] / compiler / ghci / InteractiveUI.hs
index c38b376..980dcd9 100644 (file)
@@ -3,7 +3,7 @@
 --
 -- GHC Interactive User Interface
 --
--- (c) The GHC Team 2005
+-- (c) The GHC Team 2005-2006
 --
 -----------------------------------------------------------------------------
 module InteractiveUI ( 
@@ -13,52 +13,45 @@ module InteractiveUI (
 
 #include "HsVersions.h"
 
-#if defined(GHCI) && defined(BREAKPOINT)
-import GHC.Exts         ( Int(..), Ptr(..), int2Addr# )
-import Foreign.StablePtr ( deRefStablePtr, castPtrToStablePtr )
-import System.IO.Unsafe ( unsafePerformIO )
-import Var              ( Id, globaliseId, idName, idType )
-import HscTypes         ( Session(..), InteractiveContext(..), HscEnv(..)
-                        , extendTypeEnvWithIds )
-import RdrName          ( extendLocalRdrEnv, mkRdrUnqual, lookupLocalRdrEnv )
-import NameEnv          ( delListFromNameEnv )
-import TcType           ( tidyTopType )
-import qualified Id     ( setIdType )
-import IdInfo           ( GlobalIdDetails(..) )
-import Linker           ( HValue, extendLinkEnv, withExtendedLinkEnv,
-                          initDynLinker )
-import PrelNames        ( breakpointJumpName, breakpointCondJumpName )
-#endif
+import GhciMonad
 
 -- The GHC interface
 import qualified GHC
-import GHC             ( Session, dopt, DynFlag(..), Target(..),
-                         TargetId(..), DynFlags(..),
-                         pprModule, Type, Module, ModuleName, SuccessFlag(..),
-                         TyThing(..), Name, LoadHowMuch(..), Phase,
-                         GhcException(..), showGhcException,
-                         CheckedModule(..), SrcLoc )
-import DynFlags         ( allFlags )
-import Packages                ( PackageState(..) )
-import PackageConfig   ( InstalledPackageInfo(..) )
-import UniqFM          ( eltsUFM )
+import GHC              ( Session, LoadHowMuch(..), Target(..),  TargetId(..),
+                          Type, Module, ModuleName, TyThing(..), Phase )
+import DynFlags
+import Packages
+import PackageConfig
+import UniqFM
 import PprTyThing
 import Outputable
 
--- for createtags (should these come via GHC?)
-import Name            ( nameSrcLoc, nameModule, nameOccName )
-import OccName         ( pprOccName )
-import SrcLoc          ( isGoodSrcLoc, srcLocFile, srcLocLine, srcLocCol )
+-- for createtags
+import Name
+import OccName
+import SrcLoc
 
 -- Other random utilities
-import Digraph         ( flattenSCCs )
-import BasicTypes      ( failed, successIf )
-import Panic           ( panic, installSignalHandlers )
+import Digraph
+import BasicTypes hiding (isTopLevel)
+import Panic      hiding (showException)
 import Config
-import StaticFlags     ( opt_IgnoreDotGhci )
-import Linker          ( showLinkerState, linkPackages )
-import Util            ( removeSpaces, handle, global, toArgs,
-                         looksLikeModuleName, prefixMatch, sortLe )
+import StaticFlags
+import Linker
+import Util
+
+-- The debugger
+import Breakpoints
+import Debugger hiding  ( addModule )
+import HscTypes
+import Id
+import Var       ( globaliseId )
+import IdInfo
+import NameEnv
+import RdrName
+import Module
+import Type
+import TcType
 
 #ifndef mingw32_HOST_OS
 import System.Posix
@@ -68,6 +61,7 @@ import System.Posix
 #else
 import GHC.ConsoleHandler ( flushConsole )
 import System.Win32      ( setConsoleCP, setConsoleOutputCP )
+import qualified System.Win32
 #endif
 
 #ifdef USE_READLINE
@@ -78,7 +72,6 @@ import System.Console.Readline as Readline
 --import SystemExts
 
 import Control.Exception as Exception
-import Data.Dynamic
 -- import Control.Concurrent
 
 import Numeric
@@ -86,7 +79,6 @@ import Data.List
 import Data.Int                ( Int64 )
 import Data.Maybe      ( isJust, isNothing, fromMaybe, catMaybes )
 import System.Cmd
-import System.CPUTime
 import System.Environment
 import System.Exit     ( exitWith, ExitCode(..) )
 import System.Directory
@@ -119,9 +111,9 @@ GLOBAL_VAR(commands, builtin_commands, [Command])
 
 builtin_commands :: [Command]
 builtin_commands = [
-  ("add",      keepGoingPaths addModule,       False, completeFilename),
+  ("add",      tlC$ keepGoingPaths addModule,  False, completeFilename),
   ("browse",    keepGoing browseCmd,           False, completeModule),
-  ("cd",       keepGoing changeDirectory,      False, completeFilename),
+  ("cd",       keepGoing changeDirectory,      False, completeFilename),
   ("def",      keepGoing defineMacro,          False, completeIdentifier),
   ("e",        keepGoing editFile,             False, completeFilename),
        -- Hugs users are accustomed to :e, so make sure it doesn't overlap
@@ -129,16 +121,22 @@ builtin_commands = [
   ("help",     keepGoing help,                 False, completeNone),
   ("?",                keepGoing help,                 False, completeNone),
   ("info",      keepGoing info,                        False, completeIdentifier),
-  ("load",     keepGoingPaths loadModule_,     False, completeHomeModuleOrFile),
+  ("load",     tlC$ keepGoingPaths loadModule_,False, completeHomeModuleOrFile),
   ("module",   keepGoing setContext,           False, completeModule),
-  ("main",     keepGoing runMain,              False, completeIdentifier),
-  ("reload",   keepGoing reloadModule,         False, completeNone),
+  ("main",     tlC$ keepGoing runMain,         False, completeIdentifier),
+  ("reload",   tlC$ keepGoing reloadModule,    False, completeNone),
   ("check",    keepGoing checkModule,          False, completeHomeModule),
   ("set",      keepGoing setCmd,               True,  completeSetOptions),
   ("show",     keepGoing showCmd,              False, completeNone),
   ("etags",    keepGoing createETagsFileCmd,   False, completeFilename),
   ("ctags",    keepGoing createCTagsFileCmd,   False, completeFilename),
   ("type",     keepGoing typeOfExpr,           False, completeIdentifier),
+#if defined(GHCI)
+  ("print",     keepGoing (pprintClosureCommand True False), False, completeIdentifier),
+  ("sprint",    keepGoing (pprintClosureCommand False False),False, completeIdentifier),
+  ("force",     keepGoing (pprintClosureCommand False True), False, completeIdentifier),
+  ("breakpoint",keepGoing bkptOptions,          False, completeBkpt),
+#endif
   ("kind",     keepGoing kindOfType,           False, completeIdentifier),
   ("unset",    keepGoing unsetOptions,         True,  completeSetOptions),
   ("undef",     keepGoing undefineMacro,       False, completeMacro),
@@ -148,6 +146,14 @@ builtin_commands = [
 keepGoing :: (String -> GHCi ()) -> (String -> GHCi Bool)
 keepGoing a str = a str >> return False
 
+-- tlC: Top Level Command
+tlC ::  (String -> GHCi Bool) -> (String -> GHCi Bool)
+tlC a str = do 
+    top_level <- isTopLevel
+    if not top_level
+       then throwDyn (CmdLineError "Command only allowed at Top Level")
+       else a str
+
 keepGoingPaths :: ([FilePath] -> GHCi ()) -> (String -> GHCi Bool)
 keepGoingPaths a str = a (toArgs str) >> return False
 
@@ -159,6 +165,7 @@ helpText =
  "\n" ++
  "   <stmt>                      evaluate/run <stmt>\n" ++
  "   :add <filename> ...         add module(s) to the current target set\n" ++
+ "   :breakpoint <option>        commands for the GHCi debugger\n" ++
  "   :browse [*]<module>         display the names defined by <module>\n" ++
  "   :cd <dir>                   change directory to <dir>\n" ++
  "   :def <cmd> <expr>           define a command :<cmd>\n" ++
@@ -166,6 +173,8 @@ helpText =
  "   :edit                       edit last module\n" ++
  "   :help, :?                   display this list of commands\n" ++
  "   :info [<name> ...]          display information about the given names\n" ++
+ "   :print [<name> ...]         prints a value without forcing its computation\n" ++
+ "   :sprint [<name> ...]        prints a value without forcing its computation(simpler)\n" ++
  "   :load <filename> ...        load module(s) and their dependents\n" ++
  "   :module [+/-] [*]<mod> ...  set the context for expression evaluation\n" ++
  "   :main [<arguments> ...]     run the main function with the given arguments\n" ++
@@ -175,13 +184,13 @@ helpText =
  "   :set args <arg> ...         set the arguments returned by System.getArgs\n" ++
  "   :set prog <progname>        set the value returned by System.getProgName\n" ++
  "   :set prompt <prompt>        set the prompt used in GHCi\n" ++
- "   :set editor <cmd>           set the comand used for :edit\n" ++
+ "   :set editor <cmd>           set the command used for :edit\n" ++
  "\n" ++
  "   :show modules               show the currently loaded modules\n" ++
  "   :show bindings              show the current bindings made at the prompt\n" ++
  "\n" ++
  "   :ctags [<file>]             create tags file for Vi (default: \"tags\")\n" ++
- "   :etags [<file>]             create tags file for Emacs (defauilt: \"TAGS\")\n" ++
+ "   :etags [<file>]             create tags file for Emacs (default: \"TAGS\")\n" ++
  "   :type <expr>                show the type of <expr>\n" ++
  "   :kind <type>                show the kind of <type>\n" ++
  "   :undef <cmd>                undefine user-defined command :<cmd>\n" ++
@@ -195,90 +204,27 @@ helpText =
  "    +s            print timing/memory stats after each evaluation\n" ++
  "    +t            print type after evaluation\n" ++
  "    -<flags>      most GHC command line flags can also be set here\n" ++
- "                         (eg. -v2, -fglasgow-exts, etc.)\n"
-
-
-#if defined(GHCI) && defined(BREAKPOINT)
-globaliseAndTidy :: Id -> Id
-globaliseAndTidy id
--- Give the Id a Global Name, and tidy its type
-  = Id.setIdType (globaliseId VanillaGlobal id) tidy_type
-  where
-    tidy_type = tidyTopType (idType id)
-
-
-printScopeMsg :: Session -> String -> [Id] -> IO ()
-printScopeMsg session location ids
-    = GHC.getPrintUnqual session >>= \unqual ->
-      printForUser stdout unqual $
-        text "Local bindings in scope:" $$
-        nest 2 (pprWithCommas showId ids)
-    where showId id = ppr (idName id) <+> dcolon <+> ppr (idType id)
-
-jumpCondFunction :: Session -> Int -> [HValue] -> String -> Bool -> b -> b
-jumpCondFunction session ptr hValues location True b = b
-jumpCondFunction session ptr hValues location False b
-    = jumpFunction session ptr hValues location b
-
-jumpFunction :: Session -> Int -> [HValue] -> String -> b -> b
-jumpFunction session@(Session ref) (I# idsPtr) hValues location b
-    = unsafePerformIO $
-      do ids <- deRefStablePtr (castPtrToStablePtr (Ptr (int2Addr# idsPtr)))
-         let names = map idName ids
-         ASSERT (length names == length hValues) return ()
-         printScopeMsg session location ids
-         hsc_env <- readIORef ref
-
-         let ictxt = hsc_IC hsc_env
-             global_ids = map globaliseAndTidy ids
-             rn_env   = ic_rn_local_env ictxt
-             type_env = ic_type_env ictxt
-             bound_names = map idName global_ids
-             new_rn_env  = extendLocalRdrEnv rn_env bound_names
-               -- Remove any shadowed bindings from the type_env;
-               -- they are inaccessible but might, I suppose, cause 
-               -- a space leak if we leave them there
-             shadowed = [ n | name <- bound_names,
-                          let rdr_name = mkRdrUnqual (nameOccName name),
-                          Just n <- [lookupLocalRdrEnv rn_env rdr_name] ]
-             filtered_type_env = delListFromNameEnv type_env shadowed
-             new_type_env = extendTypeEnvWithIds filtered_type_env global_ids
-             new_ic = ictxt { ic_rn_local_env = new_rn_env, 
-                             ic_type_env     = new_type_env }
-         writeIORef ref (hsc_env { hsc_IC = new_ic })
-         is_tty <- hIsTerminalDevice stdin
-         prel_mod <- GHC.findModule session prel_name Nothing
-        default_editor <- findEditor
-         withExtendedLinkEnv (zip names hValues) $
-           startGHCi (interactiveLoop is_tty True)
-                     GHCiState{ progname = "<interactive>",
-                                args = [],
-                                prompt = location++"> ",
-                               editor = default_editor,
-                                session = session,
-                                options = [],
-                                prelude =  prel_mod }
-         writeIORef ref hsc_env
-         putStrLn $ "Returning to normal execution..."
-         return b
-#endif
+ "                         (eg. -v2, -fglasgow-exts, etc.)\n" ++
+ "\n" ++
+ " Options for ':breakpoint':\n" ++
+ "   list                                     list the current breakpoints\n" ++
+ "   add Module line [col]                    add a new breakpoint\n" ++
+ "   del (breakpoint# | Module line [col])    delete a breakpoint\n" ++
+ "   stop                   Stop a computation and return to the top level\n" ++
+ "   step [count]           Step by step execution (DISABLED)\n"
 
 findEditor = do
   getEnv "EDITOR" 
     `IO.catch` \_ -> do
-#ifdef mingw32_HOST_OS
-       GetWindowsDirectory ++ "\\notepad.exe", or something
+#if mingw32_HOST_OS
+       win <- System.Win32.getWindowsDirectory
+       return (win `joinFileName` "notepad.exe")
 #else
        return ""
 #endif
 
 interactiveUI :: Session -> [(FilePath, Maybe Phase)] -> Maybe String -> IO ()
 interactiveUI session srcs maybe_expr = do
-#if defined(GHCI) && defined(BREAKPOINT)
-   initDynLinker =<< GHC.getSessionDynFlags session
-   extendLinkEnv [(breakpointJumpName,unsafeCoerce# (jumpFunction session))
-                 ,(breakpointCondJumpName,unsafeCoerce# (jumpCondFunction session))]
-#endif
    -- HACK! If we happen to get into an infinite loop (eg the user
    -- types 'let x=x in x' at the prompt), then the thread will block
    -- on a blackhole, and become unreachable during GC.  The GC will
@@ -323,6 +269,8 @@ interactiveUI session srcs maybe_expr = do
    Readline.setCompleterWordBreakCharacters word_break_chars
 #endif
 
+   bkptTable <- newIORef emptyBkptTable
+   GHC.setBreakpointHandler session (instrumentationBkptHandler bkptTable)
    default_editor <- findEditor
 
    startGHCi (runGHCi srcs maybe_expr)
@@ -332,7 +280,10 @@ interactiveUI session srcs maybe_expr = do
                   editor = default_editor,
                   session = session,
                   options = [],
-                   prelude = prel_mod }
+                   prelude = prel_mod,
+                   bkptTable = bkptTable,
+                  topLevel  = True
+                 }
 
 #ifdef USE_READLINE
    Readline.resetTerminal Nothing
@@ -563,32 +514,6 @@ runCommandEval c = ghciHandle handleEval (doCommand c)
                  -- failure to run the command causes exit(1) for ghc -e.
                _       -> finishEvalExpr nms
 
--- This is the exception handler for exceptions generated by the
--- user's code; it normally just prints out the exception.  The
--- handler must be recursive, in case showing the exception causes
--- more exceptions to be raised.
---
--- Bugfix: if the user closed stdout or stderr, the flushing will fail,
--- raising another exception.  We therefore don't put the recursive
--- handler arond the flushing operation, so if stderr is closed
--- GHCi will just die gracefully rather than going into an infinite loop.
-handler :: Exception -> GHCi Bool
-handler exception = do
-  flushInterpBuffers
-  io installSignalHandlers
-  ghciHandle handler (showException exception >> return False)
-
-showException (DynException dyn) =
-  case fromDynamic dyn of
-    Nothing               -> io (putStrLn ("*** Exception: (unknown)"))
-    Just Interrupted      -> io (putStrLn "Interrupted.")
-    Just (CmdLineError s) -> io (putStrLn s)    -- omit the location for CmdLineError
-    Just ph@PhaseFailed{} -> io (putStrLn (showGhcException ph "")) -- ditto
-    Just other_ghc_ex     -> io (print other_ghc_ex)
-
-showException other_exception
-  = io (putStrLn ("*** Exception: " ++ show other_exception))
-
 runStmt :: String -> GHCi (Maybe [Name])
 runStmt stmt
  | null (filter (not.isSpace) stmt) = return (Just [])
@@ -623,12 +548,6 @@ showTypeOfName session n
          Nothing    -> return ()
          Just thing -> showTyThing thing
 
-showForUser :: SDoc -> GHCi String
-showForUser doc = do
-  session <- getSession
-  unqual <- io (GHC.getPrintUnqual session)
-  return $! showSDocForUser unqual doc
-
 specialCommand :: String -> GHCi Bool
 specialCommand ('!':str) = shellEscape (dropWhile isSpace str)
 specialCommand str = do
@@ -650,43 +569,6 @@ lookupCommand str = do
                c:_ -> return (Just c)
 
 -----------------------------------------------------------------------------
--- To flush buffers for the *interpreted* computation we need
--- to refer to *its* stdout/stderr handles
-
-GLOBAL_VAR(flush_interp,       error "no flush_interp", IO ())
-GLOBAL_VAR(turn_off_buffering, error "no flush_stdout", IO ())
-
-no_buf_cmd = "System.IO.hSetBuffering System.IO.stdout System.IO.NoBuffering" ++
-            " Prelude.>> System.IO.hSetBuffering System.IO.stderr System.IO.NoBuffering"
-flush_cmd  = "System.IO.hFlush System.IO.stdout Prelude.>> System.IO.hFlush IO.stderr"
-
-initInterpBuffering :: Session -> IO ()
-initInterpBuffering session
- = do maybe_hval <- GHC.compileExpr session no_buf_cmd
-       
-      case maybe_hval of
-       Just hval -> writeIORef turn_off_buffering (unsafeCoerce# hval :: IO ())
-       other     -> panic "interactiveUI:setBuffering"
-       
-      maybe_hval <- GHC.compileExpr session flush_cmd
-      case maybe_hval of
-       Just hval -> writeIORef flush_interp (unsafeCoerce# hval :: IO ())
-       _         -> panic "interactiveUI:flush"
-
-      return ()
-
-
-flushInterpBuffers :: GHCi ()
-flushInterpBuffers
- = io $ do Monad.join (readIORef flush_interp)
-           return ()
-
-turnOffBuffering :: IO ()
-turnOffBuffering
- = do Monad.join (readIORef turn_off_buffering)
-      return ()
-
------------------------------------------------------------------------------
 -- Commands
 
 help :: String -> GHCi ()
@@ -715,7 +597,8 @@ info s  = do { let names = words s
 filterOutChildren :: [Name] -> [Name]
 filterOutChildren names = filter (not . parent_is_there) names
  where parent_is_there n 
-        | Just p <- GHC.nameParent_maybe n = p `elem` names
+--      | Just p <- GHC.nameParent_maybe n = p `elem` names
+-- ToDo!!
         | otherwise                       = False
 
 pprInfo exts (thing, fixity, insts)
@@ -861,7 +744,7 @@ checkModule m = do
   case result of
     Nothing -> io $ putStrLn "Nothing"
     Just r  -> io $ putStrLn (showSDoc (
-       case checkedModuleInfo r of
+       case GHC.checkedModuleInfo r of
           Just cm | Just scope <- GHC.modInfoTopLevelScope cm -> 
                let
                    (local,global) = partition ((== modl) . GHC.moduleName . GHC.nameModule) scope
@@ -888,11 +771,8 @@ afterLoad ok session = do
   graph <- io (GHC.getModuleGraph session)
   graph' <- filterM (io . GHC.isLoaded session . GHC.ms_mod_name) graph
   setContextAfterLoad session graph'
+  refreshBkptTable graph'
   modulesLoadedMsg ok (map GHC.ms_mod_name graph')
-#if defined(GHCI) && defined(BREAKPOINT)
-  io (extendLinkEnv [(breakpointJumpName,unsafeCoerce# (jumpFunction session))
-                    ,(breakpointCondJumpName,unsafeCoerce# (jumpCondFunction session))])
-#endif
 
 setContextAfterLoad session [] = do
   prel_mod <- getPrelude
@@ -1324,6 +1204,7 @@ showCmd str =
        ["modules" ] -> showModules
        ["bindings"] -> showBindings
        ["linker"]   -> io showLinkerState
+        ["breakpoints"] -> showBkptTable
        _ -> throwDyn (CmdLineError "syntax:  :show [modules|bindings]")
 
 showModules = do
@@ -1354,6 +1235,14 @@ cleanType ty = do
        then return ty
        else return $! GHC.dropForAlls ty
 
+showBkptTable :: GHCi ()
+showBkptTable = do
+  bt     <- getBkptTable
+  msg <- showForUser . vcat $ 
+             [ ppr mod <> colon <+> fcat 
+                       [ parens(int row <> comma <> int col) | (row,col) <- sites]
+               | (mod, sites) <-  sitesList bt ]
+  io (putStrLn msg)
 -- -----------------------------------------------------------------------------
 -- Completion
 
@@ -1425,6 +1314,12 @@ completeSetOptions w = do
   return (filter (w `isPrefixOf`) options)
     where options = "args":"prog":allFlags
 
+completeBkpt = unionComplete completeModule completeBkptCmds
+
+completeBkptCmds w = do
+  return (filter (w `isPrefixOf`) options)
+    where options = ["add","del","list","stop"]
+
 completeFilename = Readline.filenameCompletionFunction
 
 completeHomeModuleOrFile = unionComplete completeHomeModule completeFilename
@@ -1468,135 +1363,9 @@ completeHomeModule = completeNone
 completeSetOptions = completeNone
 completeFilename   = completeNone
 completeHomeModuleOrFile=completeNone
+completeBkpt       = completeNone
 #endif
 
------------------------------------------------------------------------------
--- GHCi monad
-
-data GHCiState = GHCiState
-     { 
-       progname       :: String,
-       args           :: [String],
-        prompt         :: String,
-       editor         :: String,
-       session        :: GHC.Session,
-       options        :: [GHCiOption],
-        prelude        :: Module
-     }
-
-data GHCiOption 
-       = ShowTiming            -- show time/allocs after evaluation
-       | ShowType              -- show the type of expressions
-       | RevertCAFs            -- revert CAFs after every evaluation
-       deriving Eq
-
-newtype GHCi a = GHCi { unGHCi :: IORef GHCiState -> IO a }
-
-startGHCi :: GHCi a -> GHCiState -> IO a
-startGHCi g state = do ref <- newIORef state; unGHCi g ref
-
-instance Monad GHCi where
-  (GHCi m) >>= k  =  GHCi $ \s -> m s >>= \a -> unGHCi (k a) s
-  return a  = GHCi $ \s -> return a
-
-ghciHandleDyn :: Typeable t => (t -> GHCi a) -> GHCi a -> GHCi a
-ghciHandleDyn h (GHCi m) = GHCi $ \s -> 
-   Exception.catchDyn (m s) (\e -> unGHCi (h e) s)
-
-getGHCiState   = GHCi $ \r -> readIORef r
-setGHCiState s = GHCi $ \r -> writeIORef r s
-
--- for convenience...
-getSession = getGHCiState >>= return . session
-getPrelude = getGHCiState >>= return . prelude
-
-GLOBAL_VAR(saved_sess, no_saved_sess, Session)
-no_saved_sess = error "no saved_ses"
-saveSession = getSession >>= io . writeIORef saved_sess
-splatSavedSession = io (writeIORef saved_sess no_saved_sess)
-restoreSession = readIORef saved_sess
-
-getDynFlags = do
-  s <- getSession
-  io (GHC.getSessionDynFlags s)
-setDynFlags dflags = do 
-  s <- getSession 
-  io (GHC.setSessionDynFlags s dflags)
-
-isOptionSet :: GHCiOption -> GHCi Bool
-isOptionSet opt
- = do st <- getGHCiState
-      return (opt `elem` options st)
-
-setOption :: GHCiOption -> GHCi ()
-setOption opt
- = do st <- getGHCiState
-      setGHCiState (st{ options = opt : filter (/= opt) (options st) })
-
-unsetOption :: GHCiOption -> GHCi ()
-unsetOption opt
- = do st <- getGHCiState
-      setGHCiState (st{ options = filter (/= opt) (options st) })
-
-io :: IO a -> GHCi a
-io m = GHCi { unGHCi = \s -> m >>= return }
-
------------------------------------------------------------------------------
--- recursive exception handlers
-
--- Don't forget to unblock async exceptions in the handler, or if we're
--- in an exception loop (eg. let a = error a in a) the ^C exception
--- may never be delivered.  Thanks to Marcin for pointing out the bug.
-
-ghciHandle :: (Exception -> GHCi a) -> GHCi a -> GHCi a
-ghciHandle h (GHCi m) = GHCi $ \s -> 
-   Exception.catch (m s) 
-       (\e -> unGHCi (ghciUnblock (h e)) s)
-
-ghciUnblock :: GHCi a -> GHCi a
-ghciUnblock (GHCi a) = GHCi $ \s -> Exception.unblock (a s)
-
------------------------------------------------------------------------------
--- timing & statistics
-
-timeIt :: GHCi a -> GHCi a
-timeIt action
-  = do b <- isOptionSet ShowTiming
-       if not b 
-         then action 
-         else do allocs1 <- io $ getAllocations
-                 time1   <- io $ getCPUTime
-                 a <- action
-                 allocs2 <- io $ getAllocations
-                 time2   <- io $ getCPUTime
-                 io $ printTimes (fromIntegral (allocs2 - allocs1)) 
-                                 (time2 - time1)
-                 return a
-
-foreign import ccall unsafe "getAllocations" getAllocations :: IO Int64
-       -- defined in ghc/rts/Stats.c
-
-printTimes :: Integer -> Integer -> IO ()
-printTimes allocs psecs
-   = do let secs = (fromIntegral psecs / (10^12)) :: Float
-           secs_str = showFFloat (Just 2) secs
-       putStrLn (showSDoc (
-                parens (text (secs_str "") <+> text "secs" <> comma <+> 
-                        text (show allocs) <+> text "bytes")))
-
------------------------------------------------------------------------------
--- reverting CAFs
-       
-revertCAFs :: IO ()
-revertCAFs = do
-  rts_revertCAFs
-  turnOffBuffering
-       -- Have to turn off buffering again, because we just 
-       -- reverted stdout, stderr & stdin to their defaults.
-
-foreign import ccall "revertCAFs" rts_revertCAFs  :: IO ()  
-       -- Make it "safe", just in case
-
 -- ----------------------------------------------------------------------------
 -- Utils
 
@@ -1632,3 +1401,82 @@ setUpConsole = do
        setConsoleOutputCP 28591 -- ISO Latin-1
 #endif
        return ()
+
+
+instrumentationBkptHandler :: IORef (BkptTable Module) -> BkptHandler Module
+instrumentationBkptHandler ref_bkptTable = BkptHandler {
+    isAutoBkptEnabled = \sess bkptLoc -> do 
+      bktpTable <- readIORef ref_bkptTable
+      return$ isBkptEnabled bktpTable bkptLoc
+
+  , handleBreakpoint = doBreakpoint ref_bkptTable 
+  }
+
+doBreakpoint :: IORef (BkptTable Module)-> Session -> [(Id,HValue)] -> BkptLocation Module -> String -> b -> IO b
+doBreakpoint ref_bkptTable s@(Session ref) values _ locMsg b = do
+         let (ids, hValues) = unzip values
+             names = map idName ids
+         ASSERT (length names == length hValues) return ()
+         let global_ids = map globaliseAndTidy ids
+         printScopeMsg locMsg global_ids
+         typed_ids  <- mapM instantiateIdType global_ids
+         hsc_env <- readIORef ref
+         let ictxt = hsc_IC hsc_env
+             rn_env   = ic_rn_local_env ictxt
+             type_env = ic_type_env ictxt
+             bound_names = map idName typed_ids
+             new_rn_env  = extendLocalRdrEnv rn_env bound_names
+               -- Remove any shadowed bindings from the type_env;
+               -- they are inaccessible but might, I suppose, cause 
+               -- a space leak if we leave them there
+             shadowed = [ n | name <- bound_names,
+                          let rdr_name = mkRdrUnqual (nameOccName name),
+                          Just n <- [lookupLocalRdrEnv rn_env rdr_name] ]
+             filtered_type_env = delListFromNameEnv type_env shadowed
+             new_type_env = extendTypeEnvWithIds filtered_type_env (typed_ids)
+             new_ic = ictxt { ic_rn_local_env = new_rn_env, 
+                             ic_type_env     = new_type_env }
+         writeIORef ref (hsc_env { hsc_IC = new_ic })
+         is_tty <- hIsTerminalDevice stdin
+         prel_mod <- GHC.findModule s prel_name Nothing
+         withExtendedLinkEnv (zip names hValues) $ 
+           startGHCi (interactiveLoop is_tty True) GHCiState{ 
+                              progname = "<interactive>",
+                              args     = [],
+                              prompt   = locMsg ++ "> ",
+                              session  = s,
+                              options  = [],
+                              bkptTable= ref_bkptTable,
+                              prelude  = prel_mod,
+                             topLevel = False }
+             `catchDyn` (
+                 \StopChildSession -> evaluate$ 
+                     throwDyn (ChildSessionStopped "You may need to reload your modules")
+           ) `finally` do
+             writeIORef ref hsc_env
+             putStrLn $ "Returning to normal execution..."
+         return b
+  where 
+     printScopeMsg :: String -> [Id] -> IO ()
+     printScopeMsg location ids = do
+       unqual  <- GHC.getPrintUnqual s
+       printForUser stdout unqual $
+         text "Local bindings in scope:" $$
+         nest 2 (pprWithCommas showId ids)
+      where 
+           showId id = 
+                ppr (idName id) <+> dcolon <+> ppr (idType id) 
+
+-- | Give the Id a Global Name, and tidy its type
+     globaliseAndTidy :: Id -> Id
+     globaliseAndTidy id
+      = let tidied_type = tidyTopType$ idType id
+        in setIdType (globaliseId VanillaGlobal id) tidied_type
+
+-- | Instantiate the tyVars with GHC.Base.Unknown
+     instantiateIdType :: Id -> IO Id
+     instantiateIdType id = do
+       instantiatedType <- instantiateTyVarsToUnknown s (idType id)
+       return$ setIdType id instantiatedType
+
+