Fix CodingStyle#Warnings URLs
[ghc-hetmet.git] / compiler / main / InteractiveEval.hs
index 069a829..939c20f 100644 (file)
@@ -6,6 +6,13 @@
 --
 -- -----------------------------------------------------------------------------
 
+{-# OPTIONS -w #-}
+-- The above warning supression flag is a temporary kludge.
+-- While working on this module you are encouraged to remove it and fix
+-- any warnings in the module. See
+--     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
+-- for details
+
 module InteractiveEval (
 #ifdef GHCI
         RunResult(..), Status(..), Resume(..), History(..),
@@ -29,7 +36,7 @@ module InteractiveEval (
         isModuleInterpreted,
        compileExpr, dynCompileExpr,
        lookupName,
-        obtainTerm, obtainTerm1, reconstructType,
+        Term(..), obtainTerm, obtainTerm1, obtainTermB, reconstructType,
         skolemiseSubst, skolemiseTy
 #endif
         ) where
@@ -70,6 +77,7 @@ import BasicTypes
 import Outputable
 
 import Data.Dynamic
+import Data.List (find)
 import Control.Monad
 import Foreign
 import Foreign.C
@@ -77,6 +85,7 @@ import GHC.Exts
 import Data.Array
 import Control.Exception as Exception
 import Control.Concurrent
+import Data.List (sortBy)
 import Data.IORef
 import Foreign.StablePtr
 
@@ -129,20 +138,46 @@ isStep _ = True
 data History
    = History {
         historyApStack   :: HValue,
-        historyBreakInfo :: BreakInfo
+        historyBreakInfo :: BreakInfo,
+        historyEnclosingDecl :: Id
+         -- ^^ A cache of the enclosing top level declaration, for convenience
    }
 
-getHistoryModule :: History -> Module 
+mkHistory :: HscEnv -> HValue -> BreakInfo -> History
+mkHistory hsc_env hval bi = let
+    h    = History hval bi decl
+    decl = findEnclosingDecl hsc_env (getHistoryModule h)
+                                     (getHistorySpan hsc_env h)
+    in h
+
+getHistoryModule :: History -> Module
 getHistoryModule = breakInfo_module . historyBreakInfo
 
-getHistorySpan :: Session -> History -> IO SrcSpan
-getHistorySpan s hist = withSession s $ \hsc_env -> do
-   let inf = historyBreakInfo hist 
+getHistorySpan :: HscEnv -> History -> SrcSpan
+getHistorySpan hsc_env hist =
+   let inf = historyBreakInfo hist
        num = breakInfo_number inf
-   case lookupUFM (hsc_HPT hsc_env) (moduleName (breakInfo_module inf)) of
-       Just hmi -> return (modBreaks_locs (md_modBreaks (hm_details hmi)) ! num)
+   in case lookupUFM (hsc_HPT hsc_env) (moduleName (breakInfo_module inf)) of
+       Just hmi -> modBreaks_locs (md_modBreaks (hm_details hmi)) ! num
        _ -> panic "getHistorySpan"
 
+{- | Finds the enclosing top level function name -}
+-- ToDo: a better way to do this would be to keep hold of the decl_path computed
+-- by the coverage pass, which gives the list of lexically-enclosing bindings
+-- for each tick.
+findEnclosingDecl :: HscEnv -> Module -> SrcSpan -> Id
+findEnclosingDecl hsc_env mod span =
+   case lookupUFM (hsc_HPT hsc_env) (moduleName mod) of
+         Nothing -> panic "findEnclosingDecl"
+         Just hmi -> let
+             globals   = typeEnvIds (md_types (hm_details hmi))
+             Just decl = 
+                 find (\id -> let n = idName id in 
+                               nameSrcSpan n < span && isExternalName n)
+                      (reverse$ sortBy (compare `on` (nameSrcSpan.idName))
+                                       globals)
+           in decl
+
 -- | Run a statement in the current interactive context.  Statement
 -- may bind multple values.
 runStmt :: Session -> String -> SingleStep -> IO RunResult
@@ -227,7 +262,7 @@ traceRunStatus expr ref bindings final_ids
         if b
            then handle_normally
            else do
-             let history' = consBL (History apStack info) history
+             let history' = mkHistory hsc_env apStack info `consBL` history
                 -- probably better make history strict here, otherwise
                 -- our BoundedList will be pointless.
              evaluate history'
@@ -371,10 +406,11 @@ resume (Session ref) step
                                  return tid)
                              (takeMVar statusMVar)
                                       -- and wait for the result 
-                let hist' = case info of 
-                              Nothing -> fromListBL 50 hist
-                              Just i -> History apStack i `consBL` 
-                                                     fromListBL 50 hist
+                let hist' = 
+                     case info of 
+                       Nothing -> fromListBL 50 hist
+                       Just i -> mkHistory hsc_env apStack i `consBL` 
+                                                        fromListBL 50 hist
                 case step of
                   RunAndLogSteps -> 
                         traceRunStatus expr ref bindings final_ids
@@ -425,7 +461,7 @@ moveHist fn (Session ref) = do
                             resumeBreakInfo = mb_info } ->
                           update_ic apStack mb_info
            else case history !! (new_ix - 1) of 
-                   History apStack info ->
+                   History apStack info _ ->
                           update_ic apStack (Just info)
 
 -- -----------------------------------------------------------------------------
@@ -486,8 +522,7 @@ bindLocalsAtBreakpoint hsc_env apStack (Just info) = do
    -- So that we don't fall over in a heap when this happens, just don't
    -- bind any free variables instead, and we emit a warning.
    mb_hValues <- mapM (getIdValFromApStack apStack) offsets
-   let (filtered_hvs, filtered_ids) = 
-                       unzip [ (hv, id) | (id, Just hv) <- zip ids mb_hValues ]
+   let filtered_ids = [ id | (id, Just hv) <- zip ids mb_hValues ]
    when (any isNothing mb_hValues) $
       debugTraceMsg (hsc_dflags hsc_env) 1 $
          text "Warning: _result has been evaluated, some bindings have been lost"
@@ -534,7 +569,7 @@ bindLocalsAtBreakpoint hsc_env apStack (Just info) = do
 
 rttiEnvironment :: HscEnv -> IO HscEnv 
 rttiEnvironment hsc_env@HscEnv{hsc_IC=ic} = do
-   let InteractiveContext{ic_tmp_ids=tmp_ids, ic_tyvars = tyvars} = ic
+   let InteractiveContext{ic_tmp_ids=tmp_ids} = ic
        incompletelyTypedIds = 
            [id | id <- tmp_ids
                , not $ null [v | v <- varSetElems$ tyVarsOfType (idType id)
@@ -877,12 +912,17 @@ isModuleInterpreted s mod_summary = withSession s $ \hsc_env ->
 
 obtainTerm1 :: HscEnv -> Bool -> Maybe Type -> a -> IO Term
 obtainTerm1 hsc_env force mb_ty x = 
-              cvObtainTerm hsc_env force mb_ty (unsafeCoerce# x)
+              cvObtainTerm hsc_env maxBound force mb_ty (unsafeCoerce# x)
+
+obtainTermB :: HscEnv -> Int -> Bool -> Id -> IO Term
+obtainTermB hsc_env bound force id =  do
+              hv <- Linker.getHValue hsc_env (varName id) 
+              cvObtainTerm hsc_env bound force (Just$ idType id) hv
 
 obtainTerm :: HscEnv -> Bool -> Id -> IO Term
 obtainTerm hsc_env force id =  do
               hv <- Linker.getHValue hsc_env (varName id) 
-              cvObtainTerm hsc_env force (Just$ idType id) hv
+              cvObtainTerm hsc_env maxBound force (Just$ idType id) hv
 
 -- Uses RTTI to reconstruct the type of an Id, making it less polymorphic
 reconstructType :: HscEnv -> Bool -> Id -> IO (Maybe Type)