Add obtainTerm1 to the GHC api
[ghc-hetmet.git] / compiler / main / GHC.hs
index ef9fd02..6855f94 100644 (file)
@@ -82,11 +82,12 @@ module GHC (
        RunResult(..),
        runStmt,
        showModule,
+        isModuleInterpreted,
        compileExpr, HValue, dynCompileExpr,
        lookupName,
 
         getBreakpointHandler, setBreakpointHandler, 
-        obtainTerm,  
+        obtainTerm, obtainTerm1,
 #endif
 
        -- * Abstract syntax elements
@@ -142,7 +143,8 @@ module GHC (
        instanceDFunId, pprInstance, pprInstanceHdr,
 
        -- ** Types and Kinds
-       Type, dropForAlls, splitForAllTys, funResultTy, pprParendType,
+       Type, dropForAlls, splitForAllTys, funResultTy, 
+       pprParendType, pprTypeApp,
        Kind,
        PredType,
        ThetaType, pprThetaArrow,
@@ -180,6 +182,7 @@ module GHC (
 #include "HsVersions.h"
 
 #ifdef GHCI
+import RtClosureInspect ( cvObtainTerm, Term )
 import TcRnDriver      ( tcRnLookupRdrName, tcRnGetInfo,
                          tcRnLookupName, getModuleExports )
 import RdrName         ( plusGlobalRdrEnv, Provenance(..), 
@@ -188,6 +191,7 @@ import RdrName              ( plusGlobalRdrEnv, Provenance(..),
 import HscMain         ( hscParseIdentifier, hscStmt, hscTcExpr, hscKcType )
 import Name            ( nameOccName )
 import Type            ( tidyType )
+import Var             ( varName )
 import VarEnv          ( emptyTidyEnv )
 import GHC.Exts         ( unsafeCoerce# )
 
@@ -206,7 +210,6 @@ import Data.Maybe       ( fromMaybe)
 import qualified Linker
 
 import Data.Dynamic     ( Dynamic )
-import RtClosureInspect ( cvObtainTerm, Term )
 import Linker          ( HValue, getHValue, extendLinkEnv )
 #endif
 
@@ -218,14 +221,14 @@ import RdrName            ( GlobalRdrEnv, GlobalRdrElt(..), RdrName(..),
 import HsSyn 
 import Type            ( Kind, Type, dropForAlls, PredType, ThetaType,
                          pprThetaArrow, pprParendType, splitForAllTys,
-                         funResultTy )
+                         pprTypeApp, funResultTy )
 import Id              ( Id, idType, isImplicitId, isDeadBinder,
                           isExportedId, isLocalId, isGlobalId,
                           isRecordSelector, recordSelectorFieldLabel,
                           isPrimOpId, isFCallId, isClassOpId_maybe,
                           isDataConWorkId, idDataCon,
                           isBottomingId )
-import Var             ( TyVar, varName )
+import Var             ( TyVar )
 import TysPrim         ( alphaTyVars )
 import TyCon           ( TyCon, isClassTyCon, isSynTyCon, isNewTyCon,
                          isPrimTyCon, isFunTyCon, isOpenTyCon, tyConArity,
@@ -280,7 +283,6 @@ import System.Exit  ( exitWith, ExitCode(..) )
 import System.Time     ( ClockTime )
 import Control.Exception as Exception hiding (handle)
 import Data.IORef
-import Data.Traversable ( traverse )
 import System.IO
 import System.IO.Error ( isDoesNotExistError )
 import Prelude hiding (init)
@@ -1763,9 +1765,9 @@ data ModuleInfo = ModuleInfo {
        minf_type_env  :: TypeEnv,
        minf_exports   :: NameSet, -- ToDo, [AvailInfo] like ModDetails?
        minf_rdr_env   :: Maybe GlobalRdrEnv,   -- Nothing for a compiled/package mod
-       minf_instances :: [Instance],
+       minf_instances :: [Instance]
 #ifdef GHCI
-        minf_dbg_sites :: [(SiteNumber,Coord)] 
+        ,minf_dbg_sites :: [(SiteNumber,Coord)] 
 #endif
        -- ToDo: this should really contain the ModIface too
   }
@@ -2211,10 +2213,15 @@ foreign import "rts_evalStableIO"  {- safe -}
 -- show a module and it's source/object filenames
 
 showModule :: Session -> ModSummary -> IO String
-showModule s mod_summary = withSession s $ \hsc_env -> do
+showModule s mod_summary = withSession s $                        \hsc_env -> 
+                           isModuleInterpreted s mod_summary >>=  \interpreted -> 
+                           return (showModMsg (hscTarget(hsc_dflags hsc_env)) interpreted mod_summary)
+
+isModuleInterpreted :: Session -> ModSummary -> IO Bool
+isModuleInterpreted s mod_summary = withSession s $ \hsc_env -> 
   case lookupUFM (hsc_HPT hsc_env) (ms_mod_name mod_summary) of
        Nothing       -> panic "missing linkable"
-       Just mod_info -> return (showModMsg (hscTarget (hsc_dflags hsc_env)) (not obj_linkable) mod_summary)
+       Just mod_info -> return (not obj_linkable)
                      where
                         obj_linkable = isObjectLinkable (expectJust "showModule" (hm_linkable mod_info))
 
@@ -2285,6 +2292,9 @@ mkSite :: SiteInfo -> BkptLocation Module
 mkSite (pkgName, modName, sitenum) =
   (mkModule (stringToPackageId pkgName) (mkModuleName modName), sitenum)
 
+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)
+
 obtainTerm :: Session -> Bool -> Id -> IO (Maybe Term)
 obtainTerm sess force id = withSession sess $ \hsc_env -> do
               mb_v <- getHValue (varName id)