summaryrefslogtreecommitdiff
path: root/compiler/main
diff options
context:
space:
mode:
authorShea Levy <shea@shealevy.com>2016-12-17 20:08:58 -0500
committerBen Gamari <ben@smart-cactus.org>2016-12-17 20:58:35 -0500
commit52ba9470a7e85d025dc84a6789aa809cdd68b566 (patch)
treeeedb856723fb2dc0101b946af3702e6c6aee18da /compiler/main
parente0fe7c3131c4a18ddd9dd9f2afdd46cafc8cd7ae (diff)
downloadhaskell-52ba9470a7e85d025dc84a6789aa809cdd68b566.tar.gz
Allow use of the external interpreter in stage1.
Now that we have -fexternal-interpreter, we can lose most of the GHCI ifdefs. Reviewers: simonmar, goldfire, austin, hvr, bgamari Reviewed By: simonmar Subscribers: RyanGlScott, mpickering, angerman, thomie Differential Revision: https://phabricator.haskell.org/D2826
Diffstat (limited to 'compiler/main')
-rw-r--r--compiler/main/DriverPipeline.hs4
-rw-r--r--compiler/main/DynFlags.hs29
-rw-r--r--compiler/main/GHC.hs38
-rw-r--r--compiler/main/GhcMake.hs8
-rw-r--r--compiler/main/Hooks.hs14
-rw-r--r--compiler/main/HscMain.hs24
-rw-r--r--compiler/main/HscTypes.hs28
-rw-r--r--compiler/main/InteractiveEval.hs7
-rw-r--r--compiler/main/InteractiveEvalTypes.hs9
9 files changed, 11 insertions, 150 deletions
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index ea0c6eded1..133bdde283 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -2054,11 +2054,7 @@ doCpp dflags raw input_fn output_fn = do
backend_defs <- getBackendDefs dflags
-#ifdef GHCI
let th_defs = [ "-D__GLASGOW_HASKELL_TH__" ]
-#else
- let th_defs = [ "-D__GLASGOW_HASKELL_TH__=0" ]
-#endif
-- Default CPP defines in Haskell source
ghcVersionH <- getGhcVersionPathName dflags
let hsSourceCppOpts = [ "-include", ghcVersionH ]
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index aee5edce85..6ecf8ca9a9 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -124,9 +124,7 @@ module DynFlags (
-- * Compiler configuration suitable for display to the user
compilerInfo,
-#ifdef GHCI
rtsIsProfiled,
-#endif
dynamicGhc,
#include "GHCConstantsHaskellExports.hs"
@@ -3613,12 +3611,6 @@ supportedExtensions :: [String]
supportedExtensions = concatMap toFlagSpecNamePair xFlags
where
toFlagSpecNamePair flg
-#ifndef GHCI
- -- make sure that `ghc --supported-extensions` omits
- -- "TemplateHaskell" when it's known to be unsupported. See also
- -- GHC #11102 for rationale
- | flagSpecFlag flg == LangExt.TemplateHaskell = [noName]
-#endif
| otherwise = [name, noName]
where
noName = "No" ++ name
@@ -4155,7 +4147,6 @@ foreign import ccall unsafe "rts_isProfiled" rtsIsProfiledIO :: IO CInt
rtsIsProfiled :: Bool
rtsIsProfiled = unsafeDupablePerformIO rtsIsProfiledIO /= 0
-#ifdef GHCI
-- Consult the RTS to find whether GHC itself has been built with
-- dynamic linking. This can't be statically known at compile-time,
-- because we build both the static and dynamic versions together with
@@ -4164,10 +4155,6 @@ foreign import ccall unsafe "rts_isDynamic" rtsIsDynamicIO :: IO CInt
dynamicGhc :: Bool
dynamicGhc = unsafeDupablePerformIO rtsIsDynamicIO /= 0
-#else
-dynamicGhc :: Bool
-dynamicGhc = False
-#endif
setWarnSafe :: Bool -> DynP ()
setWarnSafe True = getCurLoc >>= \l -> upd (\d -> d { warnSafeOnLoc = l })
@@ -4200,24 +4187,8 @@ setIncoherentInsts True = do
upd (\d -> d { incoherentOnLoc = l })
checkTemplateHaskellOk :: TurnOnFlag -> DynP ()
-#ifdef GHCI
checkTemplateHaskellOk _turn_on
= getCurLoc >>= \l -> upd (\d -> d { thOnLoc = l })
-#else
--- In stage 1, Template Haskell is simply illegal, except with -M
--- We don't bleat with -M because there's no problem with TH there,
--- and in fact GHC's build system does ghc -M of the DPH libraries
--- with a stage1 compiler
-checkTemplateHaskellOk turn_on
- | turn_on = do dfs <- liftEwM getCmdLineState
- case ghcMode dfs of
- MkDepend -> return ()
- _ -> addErr msg
- | otherwise = return ()
- where
- msg = "Template Haskell requires GHC with interpreter support\n " ++
- "Perhaps you are using a stage-1 compiler?"
-#endif
{- **********************************************************************
%* *
diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index cf066d0ea7..59e42f9c75 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -91,7 +91,6 @@ module GHC (
-- * Interactive evaluation
-#ifdef GHCI
-- ** Executing statements
execStmt, ExecOptions(..), execOptions, ExecResult(..),
resumeExec,
@@ -103,11 +102,10 @@ module GHC (
parseImportDecl,
setContext, getContext,
setGHCiMonad, getGHCiMonad,
-#endif
+
-- ** Inspecting the current context
getBindings, getInsts, getPrintUnqual,
findModule, lookupModule,
-#ifdef GHCI
isModuleTrusted, moduleTrustReqs,
getNamesInScope,
getRdrNamesInScope,
@@ -123,9 +121,8 @@ module GHC (
-- ** Looking up a Name
parseName,
-#endif
lookupName,
-#ifdef GHCI
+
-- ** Compiling expressions
HValue, parseExpr, compileParsedExpr,
InteractiveEval.compileExpr, dynCompileExpr,
@@ -154,7 +151,6 @@ module GHC (
RunResult(..),
runStmt, runStmtWithLocation,
resume,
-#endif
-- * Abstract syntax elements
@@ -290,14 +286,12 @@ module GHC (
#include "HsVersions.h"
-#ifdef GHCI
import ByteCodeTypes
import InteractiveEval
import InteractiveEvalTypes
import TcRnDriver ( runTcInteractive )
import GHCi
import GHCi.RemoteTypes
-#endif
import PprTyThing ( pprFamInst )
import HscMain
@@ -469,9 +463,7 @@ withCleanupSession ghc = ghc `gfinally` cleanup
liftIO $ do
cleanTempFiles dflags
cleanTempDirs dflags
-#ifdef GHCI
stopIServ hsc_env -- shut down the IServ
-#endif
-- exceptions will be blocked while we clean the temporary files,
-- so there shouldn't be any difficulty if we receive further
-- signals.
@@ -889,10 +881,8 @@ typecheckModule pmod = do
minf_rdr_env = Just (tcg_rdr_env tc_gbl_env),
minf_instances = fixSafeInstances safe $ md_insts details,
minf_iface = Nothing,
- minf_safe = safe
-#ifdef GHCI
- ,minf_modBreaks = emptyModBreaks
-#endif
+ minf_safe = safe,
+ minf_modBreaks = emptyModBreaks
}}
-- | Desugar a typechecked module.
@@ -1080,10 +1070,8 @@ data ModuleInfo = ModuleInfo {
minf_rdr_env :: Maybe GlobalRdrEnv, -- Nothing for a compiled/package mod
minf_instances :: [ClsInst],
minf_iface :: Maybe ModIface,
- minf_safe :: SafeHaskellMode
-#ifdef GHCI
- ,minf_modBreaks :: ModBreaks
-#endif
+ minf_safe :: SafeHaskellMode,
+ minf_modBreaks :: ModBreaks
}
-- We don't want HomeModInfo here, because a ModuleInfo applies
-- to package modules too.
@@ -1106,7 +1094,6 @@ getModuleInfo mdl = withSession $ \hsc_env -> do
-- exist... hence the isHomeModule test here. (ToDo: reinstate)
getPackageModuleInfo :: HscEnv -> Module -> IO (Maybe ModuleInfo)
-#ifdef GHCI
getPackageModuleInfo hsc_env mdl
= do eps <- hscEPS hsc_env
iface <- hscGetModuleInterface hsc_env mdl
@@ -1125,11 +1112,6 @@ getPackageModuleInfo hsc_env mdl
minf_safe = getSafeMode $ mi_trust iface,
minf_modBreaks = emptyModBreaks
}))
-#else
--- bogusly different for non-GHCI (ToDo)
-getPackageModuleInfo _hsc_env _mdl = do
- return Nothing
-#endif
getHomeModuleInfo :: HscEnv -> Module -> IO (Maybe ModuleInfo)
getHomeModuleInfo hsc_env mdl =
@@ -1145,9 +1127,7 @@ getHomeModuleInfo hsc_env mdl =
minf_instances = md_insts details,
minf_iface = Just iface,
minf_safe = getSafeMode $ mi_trust iface
-#ifdef GHCI
,minf_modBreaks = getModBreaks hmi
-#endif
}))
-- | The list of top-level entities defined in a module
@@ -1196,10 +1176,8 @@ modInfoIface = minf_iface
modInfoSafe :: ModuleInfo -> SafeHaskellMode
modInfoSafe = minf_safe
-#ifdef GHCI
modInfoModBreaks :: ModuleInfo -> ModBreaks
modInfoModBreaks = minf_modBreaks
-#endif
isDictonaryId :: Id -> Bool
isDictonaryId id
@@ -1219,11 +1197,9 @@ findGlobalAnns deserialize target = withSession $ \hsc_env -> do
ann_env <- liftIO $ prepareAnnotations hsc_env Nothing
return (findAnns deserialize ann_env target)
-#ifdef GHCI
-- | get the GlobalRdrEnv for a session
getGRE :: GhcMonad m => m GlobalRdrEnv
getGRE = withSession $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env)
-#endif
-- -----------------------------------------------------------------------------
@@ -1422,7 +1398,6 @@ lookupLoadedHomeModule mod_name = withSession $ \hsc_env ->
Just mod_info -> return (Just (mi_module (hm_iface mod_info)))
_not_a_home_module -> return Nothing
-#ifdef GHCI
-- | Check that a module is safe to import (according to Safe Haskell).
--
-- We return True to indicate the import is safe and False otherwise
@@ -1464,7 +1439,6 @@ obtainTermFromId :: GhcMonad m => Int -> Bool -> Id -> m Term
obtainTermFromId bound force id = withSession $ \hsc_env ->
liftIO $ InteractiveEval.obtainTermFromId hsc_env bound force id
-#endif
-- | Returns the 'TyThing' for a 'Name'. The 'Name' may refer to any
-- entity known to GHC, including 'Name's defined using 'runStmt'.
diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs
index 6b103c9e1b..be6510bcb2 100644
--- a/compiler/main/GhcMake.hs
+++ b/compiler/main/GhcMake.hs
@@ -31,9 +31,7 @@ module GhcMake(
#include "HsVersions.h"
-#ifdef GHCI
import qualified Linker ( unload )
-#endif
import DriverPhases
import DriverPipeline
@@ -563,13 +561,7 @@ findPartiallyCompletedCycles modsDone theGraph
unload :: HscEnv -> [Linkable] -> IO ()
unload hsc_env stable_linkables -- Unload everthing *except* 'stable_linkables'
= case ghcLink (hsc_dflags hsc_env) of
-#ifdef GHCI
LinkInMemory -> Linker.unload hsc_env stable_linkables
-#else
- LinkInMemory -> panic "unload: no interpreter"
- -- urgh. avoid warnings:
- hsc_env stable_linkables
-#endif
_other -> return ()
-- -----------------------------------------------------------------------------
diff --git a/compiler/main/Hooks.hs b/compiler/main/Hooks.hs
index 8d706d8fa5..eefdde4b88 100644
--- a/compiler/main/Hooks.hs
+++ b/compiler/main/Hooks.hs
@@ -15,18 +15,14 @@ module Hooks ( Hooks
, tcForeignImportsHook
, tcForeignExportsHook
, hscFrontendHook
-#ifdef GHCI
, hscCompileCoreExprHook
-#endif
, ghcPrimIfaceHook
, runPhaseHook
, runMetaHook
, linkHook
, runRnSpliceHook
-#ifdef GHCI
, getValueSafelyHook
, createIservProcessHook
-#endif
) where
import DynFlags
@@ -42,12 +38,10 @@ import TcRnTypes
import Bag
import RdrName
import CoreSyn
-#ifdef GHCI
import GHCi.RemoteTypes
import SrcLoc
import Type
import System.Process
-#endif
import BasicTypes
import Data.Maybe
@@ -70,18 +64,14 @@ emptyHooks = Hooks
, tcForeignImportsHook = Nothing
, tcForeignExportsHook = Nothing
, hscFrontendHook = Nothing
-#ifdef GHCI
, hscCompileCoreExprHook = Nothing
-#endif
, ghcPrimIfaceHook = Nothing
, runPhaseHook = Nothing
, runMetaHook = Nothing
, linkHook = Nothing
, runRnSpliceHook = Nothing
-#ifdef GHCI
, getValueSafelyHook = Nothing
, createIservProcessHook = Nothing
-#endif
}
data Hooks = Hooks
@@ -89,18 +79,14 @@ data Hooks = Hooks
, tcForeignImportsHook :: Maybe ([LForeignDecl Name] -> TcM ([Id], [LForeignDecl Id], Bag GlobalRdrElt))
, tcForeignExportsHook :: Maybe ([LForeignDecl Name] -> TcM (LHsBinds TcId, [LForeignDecl TcId], Bag GlobalRdrElt))
, hscFrontendHook :: Maybe (ModSummary -> Hsc FrontendResult)
-#ifdef GHCI
, hscCompileCoreExprHook :: Maybe (HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue)
-#endif
, ghcPrimIfaceHook :: Maybe ModIface
, runPhaseHook :: Maybe (PhasePlus -> FilePath -> DynFlags -> CompPipeline (PhasePlus, FilePath))
, runMetaHook :: Maybe (MetaHook TcM)
, linkHook :: Maybe (GhcLink -> DynFlags -> Bool -> HomePackageTable -> IO SuccessFlag)
, runRnSpliceHook :: Maybe (HsSplice Name -> RnM (HsSplice Name))
-#ifdef GHCI
, getValueSafelyHook :: Maybe (HscEnv -> Name -> Type -> IO (Maybe HValue))
, createIservProcessHook :: Maybe (CreateProcess -> IO ProcessHandle)
-#endif
}
getHooked :: (Functor f, HasDynFlags f) => (Hooks -> Maybe a) -> a -> f a
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 9a64794b77..7d809126bf 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -59,7 +59,6 @@ module HscMain
, hscParseIdentifier
, hscTcRcLookupName
, hscTcRnGetInfo
-#ifdef GHCI
, hscIsGHCiMonad
, hscGetModuleInterface
, hscRnImportDecls
@@ -71,7 +70,6 @@ module HscMain
, hscCompileCoreExpr
-- * Low-level exports for hooks
, hscCompileCoreExpr'
-#endif
-- We want to make sure that we export enough to be able to redefine
-- hscFileFrontEnd in client code
, hscParse', hscSimplify', hscDesugar', tcRnModule'
@@ -83,7 +81,6 @@ module HscMain
, showModuleIndex
) where
-#ifdef GHCI
import Id
import GHCi.RemoteTypes ( ForeignHValue )
import ByteCodeGen ( byteCodeGen, coreExprToBCOs )
@@ -96,7 +93,6 @@ import VarEnv ( emptyTidyEnv )
import Panic
import ConLike
import Control.Concurrent
-#endif
import Module
import Packages
@@ -178,9 +174,7 @@ newHscEnv dflags = do
us <- mkSplitUniqSupply 'r'
nc_var <- newIORef (initNameCache us knownKeyNames)
fc_var <- newIORef emptyInstalledModuleEnv
-#ifdef GHCI
iserv_mvar <- newMVar Nothing
-#endif
return HscEnv { hsc_dflags = dflags
, hsc_targets = []
, hsc_mod_graph = []
@@ -190,9 +184,7 @@ newHscEnv dflags = do
, hsc_NC = nc_var
, hsc_FC = fc_var
, hsc_type_env_var = Nothing
-#ifdef GHCI
, hsc_iserv = iserv_mvar
-#endif
}
-- -----------------------------------------------------------------------------
@@ -262,13 +254,11 @@ ioMsgMaybe' ioA = do
-- -----------------------------------------------------------------------------
-- | Lookup things in the compiler's environment
-#ifdef GHCI
hscTcRnLookupRdrName :: HscEnv -> Located RdrName -> IO [Name]
hscTcRnLookupRdrName hsc_env0 rdr_name
= runInteractiveHsc hsc_env0 $
do { hsc_env <- getHscEnv
; ioMsgMaybe $ tcRnLookupRdrName hsc_env rdr_name }
-#endif
hscTcRcLookupName :: HscEnv -> Name -> IO (Maybe TyThing)
hscTcRcLookupName hsc_env0 name = runInteractiveHsc hsc_env0 $ do
@@ -284,7 +274,6 @@ hscTcRnGetInfo hsc_env0 name
do { hsc_env <- getHscEnv
; ioMsgMaybe' $ tcRnGetInfo hsc_env name }
-#ifdef GHCI
hscIsGHCiMonad :: HscEnv -> String -> IO Name
hscIsGHCiMonad hsc_env name
= runHsc hsc_env $ ioMsgMaybe $ isGHCiMonad hsc_env name
@@ -300,7 +289,6 @@ hscRnImportDecls :: HscEnv -> [LImportDecl RdrName] -> IO GlobalRdrEnv
hscRnImportDecls hsc_env0 import_decls = runInteractiveHsc hsc_env0 $ do
hsc_env <- getHscEnv
ioMsgMaybe $ tcRnImportDecls hsc_env import_decls
-#endif
-- -----------------------------------------------------------------------------
-- | parse a file, returning the abstract syntax
@@ -1073,7 +1061,6 @@ hscCheckSafe' dflags m l = do
let pkgIfaceT = eps_PIT hsc_eps
homePkgT = hsc_HPT hsc_env
iface = lookupIfaceByModule dflags homePkgT pkgIfaceT m
-#ifdef GHCI
-- the 'lookupIfaceByModule' method will always fail when calling from GHCi
-- as the compiler hasn't filled in the various module tables
-- so we need to call 'getModuleInterface' to load from disk
@@ -1081,9 +1068,6 @@ hscCheckSafe' dflags m l = do
Just _ -> return iface
Nothing -> snd `fmap` (liftIO $ getModuleInterface hsc_env m)
return iface'
-#else
- return iface
-#endif
isHomePkg :: Module -> Bool
@@ -1320,7 +1304,6 @@ hscInteractive :: HscEnv
-> CgGuts
-> ModSummary
-> IO (Maybe FilePath, CompiledByteCode)
-#ifdef GHCI
hscInteractive hsc_env cgguts mod_summary = do
let dflags = hsc_dflags hsc_env
let CgGuts{ -- This is the last use of the ModGuts in a compilation.
@@ -1347,9 +1330,6 @@ hscInteractive hsc_env cgguts mod_summary = do
(_istub_h_exists, istub_c_exists)
<- outputForeignStubs dflags this_mod location foreign_stubs
return (istub_c_exists, comp_bc)
-#else
-hscInteractive _ _ = panic "GHC not compiled with interpreter"
-#endif
------------------------------
@@ -1472,7 +1452,6 @@ A naked expression returns a singleton Name [it]. The stmt is lifted into the
IO monad as explained in Note [Interactively-bound Ids in GHCi] in HscTypes
-}
-#ifdef GHCI
-- | Compile a stmt all the way to an HValue, but don't run it
--
-- We return Nothing to indicate an empty statement (or comment only), not a
@@ -1676,7 +1655,6 @@ hscParseStmtWithLocation source linenumber stmt =
hscParseType :: String -> Hsc (LHsType RdrName)
hscParseType = hscParseThing parseType
-#endif
hscParseIdentifier :: HscEnv -> String -> IO (Located RdrName)
hscParseIdentifier hsc_env str =
@@ -1713,7 +1691,6 @@ hscParseThingWithLocation source linenumber parser str
%* *
%********************************************************************* -}
-#ifdef GHCI
hscCompileCoreExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
hscCompileCoreExpr hsc_env =
lookupHook hscCompileCoreExprHook hscCompileCoreExpr' (hsc_dflags hsc_env) hsc_env
@@ -1742,7 +1719,6 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr
; hval <- linkExpr hsc_env srcspan bcos
; return hval }
-#endif
{- **********************************************************************
diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs
index e5f824f2e4..5b3c058d35 100644
--- a/compiler/main/HscTypes.hs
+++ b/compiler/main/HscTypes.hs
@@ -14,9 +14,7 @@ module HscTypes (
Target(..), TargetId(..), pprTarget, pprTargetId,
ModuleGraph, emptyMG,
HscStatus(..),
-#ifdef GHCI
IServ(..),
-#endif
-- * Hsc monad
Hsc(..), runHsc, runInteractiveHsc,
@@ -137,12 +135,10 @@ module HscTypes (
#include "HsVersions.h"
-#ifdef GHCI
import ByteCodeTypes
import InteractiveEvalTypes ( Resume )
import GHCi.Message ( Pipe )
import GHCi.RemoteTypes
-#endif
import UniqFM
import HsSyn
@@ -202,10 +198,8 @@ import Data.IORef
import Data.Time
import Exception
import System.FilePath
-#ifdef GHCI
import Control.Concurrent
import System.Process ( ProcessHandle )
-#endif
-- -----------------------------------------------------------------------------
-- Compilation state
@@ -403,11 +397,9 @@ data HscEnv
-- the 'IfGblEnv'. See 'TcRnTypes.tcg_type_env_var' for
-- 'TcRnTypes.TcGblEnv'. See also Note [hsc_type_env_var hack]
-#ifdef GHCI
, hsc_iserv :: MVar (Maybe IServ)
-- ^ interactive server process. Created the first
-- time it is needed.
-#endif
}
-- Note [hsc_type_env_var hack]
@@ -453,14 +445,12 @@ data HscEnv
-- another day.
-#ifdef GHCI
data IServ = IServ
{ iservPipe :: Pipe
, iservProcess :: ProcessHandle
, iservLookupSymbolCache :: IORef (UniqFM (Ptr ()))
, iservPendingFrees :: [HValueRef]
}
-#endif
-- | Retrieve the ExternalPackageState cache.
hscEPS :: HscEnv -> IO ExternalPackageState
@@ -1490,10 +1480,8 @@ data InteractiveContext
ic_default :: Maybe [Type],
-- ^ The current default types, set by a 'default' declaration
-#ifdef GHCI
ic_resume :: [Resume],
-- ^ The stack of breakpoint contexts
-#endif
ic_monad :: Name,
-- ^ The monad that GHCi is executing in
@@ -1531,9 +1519,7 @@ emptyInteractiveContext dflags
ic_monad = ioTyConName, -- IO monad by default
ic_int_print = printName, -- System.IO.print by default
ic_default = Nothing,
-#ifdef GHCI
ic_resume = [],
-#endif
ic_cwd = Nothing }
icInteractiveModule :: InteractiveContext -> Module
@@ -2950,25 +2936,11 @@ data Unlinked
| DotDLL FilePath -- ^ Dynamically linked library file (.so, .dll, .dylib)
| BCOs CompiledByteCode -- ^ A byte-code object, lives only in memory
-#ifndef GHCI
-data CompiledByteCode = CompiledByteCodeUndefined
-_unusedCompiledByteCode :: CompiledByteCode
-_unusedCompiledByteCode = CompiledByteCodeUndefined
-
-data ModBreaks = ModBreaksUndefined
-emptyModBreaks :: ModBreaks
-emptyModBreaks = ModBreaksUndefined
-#endif
-
instance Outputable Unlinked where
ppr (DotO path) = text "DotO" <+> text path
ppr (DotA path) = text "DotA" <+> text path
ppr (DotDLL path) = text "DotDLL" <+> text path
-#ifdef GHCI
ppr (BCOs bcos) = text "BCOs" <+> ppr bcos
-#else
- ppr (BCOs _) = text "No byte code"
-#endif
-- | Is this an actual file on disk we can link in somehow?
isObject :: Unlinked -> Bool
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index a421c72baf..3cb1856725 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -10,7 +10,6 @@
-- -----------------------------------------------------------------------------
module InteractiveEval (
-#ifdef GHCI
Resume(..), History(..),
execStmt, ExecOptions(..), execOptions, ExecResult(..), resumeExec,
runDecls, runDeclsWithLocation,
@@ -40,17 +39,14 @@ module InteractiveEval (
Term(..), obtainTermFromId, obtainTermFromVal, reconstructType,
-- * Depcreated API (remove in GHC 7.14)
RunResult(..), runStmt, runStmtWithLocation,
-#endif
) where
-#ifdef GHCI
-
#include "HsVersions.h"
import InteractiveEvalTypes
import GHCi
-import GHCi.Run
+import GHCi.Message
import GHCi.RemoteTypes
import GhcMonad
import HscMain
@@ -979,4 +975,3 @@ reconstructType hsc_env bound id = do
mkRuntimeUnkTyVar :: Name -> Kind -> TyVar
mkRuntimeUnkTyVar name kind = mkTcTyVar name kind RuntimeUnk
-#endif /* GHCI */
diff --git a/compiler/main/InteractiveEvalTypes.hs b/compiler/main/InteractiveEvalTypes.hs
index 34ae2ccaa0..cb0121950f 100644
--- a/compiler/main/InteractiveEvalTypes.hs
+++ b/compiler/main/InteractiveEvalTypes.hs
@@ -9,15 +9,11 @@
-- -----------------------------------------------------------------------------
module InteractiveEvalTypes (
-#ifdef GHCI
Resume(..), History(..), ExecResult(..),
SingleStep(..), isStep, ExecOptions(..),
BreakInfo(..)
-#endif
) where
-#ifdef GHCI
-
import GHCi.RemoteTypes
import GHCi.Message (EvalExpr, ResumeContext)
import Id
@@ -29,7 +25,11 @@ import SrcLoc
import Exception
import Data.Word
+#if MIN_VERSION_base(4,9,0)
import GHC.Stack.CCS
+#else
+import GHC.Stack as GHC.Stack.CCS
+#endif
data ExecOptions
= ExecOptions
@@ -91,4 +91,3 @@ data History
historyBreakInfo :: BreakInfo,
historyEnclosingDecls :: [String] -- declarations enclosing the breakpoint
}
-#endif