X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FInteractiveEval.hs;h=8908022ba92126fd7e1c3e10066db3c06bcc25e1;hb=9ec44d592dac28c2fe6909f7cf3cf2199c34ed21;hp=1f3686186b28f4ee09131058b710cdc7c3da6bb1;hpb=27ebe4c5edb356cec5c9b12f357404ae998bc905;p=ghc-hetmet.git diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs index 1f36861..8908022 100644 --- a/compiler/main/InteractiveEval.hs +++ b/compiler/main/InteractiveEval.hs @@ -14,6 +14,7 @@ module InteractiveEval ( abandon, abandonAll, getResumeContext, getHistorySpan, + getHistoryModule, back, forward, setContext, getContext, nameSetToGlobalRdrEnv, @@ -28,7 +29,8 @@ module InteractiveEval ( isModuleInterpreted, compileExpr, dynCompileExpr, lookupName, - obtainTerm, obtainTerm1 + Term(..), obtainTerm, obtainTerm1, obtainTermB, reconstructType, + skolemiseSubst, skolemiseTy #endif ) where @@ -68,6 +70,7 @@ import BasicTypes import Outputable import Data.Dynamic +import Data.List (find) import Control.Monad import Foreign import Foreign.C @@ -75,6 +78,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 @@ -127,17 +131,43 @@ isStep _ = True data History = History { historyApStack :: HValue, - historyBreakInfo :: BreakInfo + historyBreakInfo :: BreakInfo, + historyEnclosingDecl :: Id + -- ^^ A cache of the enclosing top level declaration, for convenience } -getHistorySpan :: Session -> History -> IO SrcSpan -getHistorySpan s hist = withSession s $ \hsc_env -> do - let inf = historyBreakInfo hist +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 :: 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 +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 @@ -163,7 +193,7 @@ runStmt (Session ref) expr step let thing_to_run = unsafeCoerce# hval :: IO [HValue] status <- sandboxIO statusMVar thing_to_run - + let ic = hsc_IC hsc_env bindings = (ic_tmp_ids ic, ic_tyvars ic) @@ -205,8 +235,9 @@ handleRunStatus expr ref bindings final_ids breakMVar statusMVar status final_ids emptyVarSet -- the bound Ids never have any free TyVars final_names = map idName final_ids - writeIORef ref hsc_env{hsc_IC=final_ic} Linker.extendLinkEnv (zip final_names hvals) + hsc_env' <- rttiEnvironment hsc_env{hsc_IC=final_ic} + writeIORef ref hsc_env' return (RunOk final_names) @@ -221,7 +252,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' @@ -356,7 +387,7 @@ resume (Session ref) step when (isStep step) $ setStepFlag case r of Resume expr tid breakMVar statusMVar bindings - final_ids apStack info _ _ _ -> do + final_ids apStack info _ hist _ -> do withBreakAction (isStep step) (hsc_dflags hsc_env) breakMVar statusMVar $ do status <- withInterruptsSentTo @@ -364,14 +395,19 @@ resume (Session ref) step -- this awakens the stopped thread... return tid) (takeMVar statusMVar) - -- and wait for the result + -- and wait for the result + 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 - breakMVar statusMVar status emptyHistory + breakMVar statusMVar status hist' _other -> handleRunStatus expr ref bindings final_ids - breakMVar statusMVar status emptyHistory + breakMVar statusMVar status hist' back :: Session -> IO ([Name], Int, SrcSpan) @@ -415,12 +451,13 @@ 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) -- ----------------------------------------------------------------------------- -- After stopping at a breakpoint, add free variables to the environment - +result_fs = FSLIT("_result") + bindLocalsAtBreakpoint :: HscEnv -> HValue @@ -475,7 +512,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_ids = [ id | (id, Just _) <- 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" @@ -486,8 +523,7 @@ bindLocalsAtBreakpoint hsc_env apStack (Just info) = do -- make an Id for _result. We use the Unique of the FastString "_result"; -- we don't care about uniqueness here, because there will only be one -- _result in scope at any time. - let result_fs = FSLIT("_result") - result_name = mkInternalName (getUnique result_fs) + let result_name = mkInternalName (getUnique result_fs) (mkVarOccFS result_fs) span result_id = Id.mkGlobalId VanillaGlobal result_name result_ty vanillaIdInfo @@ -504,14 +540,13 @@ bindLocalsAtBreakpoint hsc_env apStack (Just info) = do (id_tys, tyvarss) = mapAndUnzip (skolemiseTy.idType) all_ids (_,tidy_tys) = tidyOpenTypes emptyTidyEnv id_tys new_tyvars = unionVarSets tyvarss - final_ids = zipWith setIdType all_ids tidy_tys - - let ictxt0 = hsc_IC hsc_env - ictxt1 = extendInteractiveContext ictxt0 final_ids new_tyvars - + let final_ids = zipWith setIdType all_ids tidy_tys + ictxt0 = hsc_IC hsc_env + ictxt1 = extendInteractiveContext ictxt0 final_ids new_tyvars Linker.extendLinkEnv [ (name,hval) | (name, Just hval) <- zip names mb_hValues ] Linker.extendLinkEnv [(result_name, unsafeCoerce# apStack)] - return (hsc_env{ hsc_IC = ictxt1 }, result_name:names, span) + hsc_env1 <- rttiEnvironment hsc_env{ hsc_IC = ictxt1 } + return (hsc_env1, result_name:names, span) where mkNewId :: OccName -> Id -> IO Id mkNewId occ id = do @@ -522,6 +557,26 @@ bindLocalsAtBreakpoint hsc_env apStack (Just info) = do new_id = Id.mkGlobalId VanillaGlobal name ty (idInfo id) return new_id +rttiEnvironment :: HscEnv -> IO HscEnv +rttiEnvironment hsc_env@HscEnv{hsc_IC=ic} = do + let InteractiveContext{ic_tmp_ids=tmp_ids} = ic + incompletelyTypedIds = + [id | id <- tmp_ids + , not $ null [v | v <- varSetElems$ tyVarsOfType (idType id) + , isSkolemTyVar v] + , (occNameFS.nameOccName.idName) id /= result_fs] + tys <- reconstructType hsc_env False `mapM` incompletelyTypedIds + -- map termType `fmap` (obtainTerm hsc_env False `mapM` incompletelyTypedIds) + + let substs = [computeRTTIsubst ty ty' + | (ty, Just ty') <- zip (map idType incompletelyTypedIds) tys] + ic' = foldr (flip substInteractiveContext) ic + (map skolemiseSubst $ catMaybes substs) + return hsc_env{hsc_IC=ic'} + +skolemiseSubst subst = subst `setTvSubstEnv` + mapVarEnv (fst.skolemiseTy) (getTvSubstEnv subst) + skolemiseTy :: Type -> (Type, TyVarSet) skolemiseTy ty = (substTy subst ty, mkVarSet new_tyvars) where env = mkVarEnv (zip tyvars new_tyvar_tys) @@ -610,6 +665,8 @@ consBL a (BL len bound left right) toListBL (BL _ _ left right) = left ++ reverse right +fromListBL bound l = BL (length l) bound l [] + -- lenBL (BL len _ _ _) = len -- ----------------------------------------------------------------------------- @@ -689,8 +746,29 @@ moduleIsInterpreted s modl = withSession s $ \h -> _not_a_home_module -> return False -- | Looks up an identifier in the current interactive context (for :info) +-- Filter the instances by the ones whose tycons (or clases resp) +-- are in scope (qualified or otherwise). Otherwise we list a whole lot too many! +-- The exact choice of which ones to show, and which to hide, is a judgement call. +-- (see Trac #1581) getInfo :: Session -> Name -> IO (Maybe (TyThing,Fixity,[Instance])) -getInfo s name = withSession s $ \hsc_env -> tcRnGetInfo hsc_env name +getInfo s name + = withSession s $ \hsc_env -> + do { mb_stuff <- tcRnGetInfo hsc_env name + ; case mb_stuff of + Nothing -> return Nothing + Just (thing, fixity, ispecs) -> do + { let rdr_env = ic_rn_gbl_env (hsc_IC hsc_env) + ; return (Just (thing, fixity, filter (plausible rdr_env) ispecs)) } } + where + plausible rdr_env ispec -- Dfun involving only names that are in ic_rn_glb_env + = all ok $ nameSetToList $ tyClsNamesOfType $ idType $ instanceDFunId ispec + where -- A name is ok if it's in the rdr_env, + -- whether qualified or not + ok n | n == name = True -- The one we looked for in the first place! + | isBuiltInSyntax n = True + | isExternalName n = any ((== n) . gre_name) + (lookupGRE_Name rdr_env n) + | otherwise = True -- | Returns all names in scope in the current interactive context getNamesInScope :: Session -> IO [Name] @@ -819,12 +897,26 @@ isModuleInterpreted s mod_summary = withSession s $ \hsc_env -> where obj_linkable = isObjectLinkable (expectJust "showModule" (hm_linkable mod_info)) -obtainTerm1 :: Session -> Bool -> Maybe Type -> a -> IO Term -obtainTerm1 sess force mb_ty x = withSession sess $ \hsc_env -> cvObtainTerm hsc_env force mb_ty (unsafeCoerce# x) +---------------------------------------------------------------------------- +-- RTTI primitives -obtainTerm :: Session -> Bool -> Id -> IO Term -obtainTerm sess force id = withSession sess $ \hsc_env -> do +obtainTerm1 :: HscEnv -> Bool -> Maybe Type -> a -> IO Term +obtainTerm1 hsc_env force mb_ty 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) +reconstructType hsc_env force id = do + hv <- Linker.getHValue hsc_env (varName id) + cvReconstructType hsc_env force (Just$ idType id) hv #endif /* GHCI */