diff options
Diffstat (limited to 'compiler/main/Hooks.hs')
-rw-r--r-- | compiler/main/Hooks.hs | 33 |
1 files changed, 30 insertions, 3 deletions
diff --git a/compiler/main/Hooks.hs b/compiler/main/Hooks.hs index f75214b4f4..0b75bc599d 100644 --- a/compiler/main/Hooks.hs +++ b/compiler/main/Hooks.hs @@ -5,6 +5,7 @@ -- If you import too muchhere , then the revolting compiler_stage2_dll0_MODULES -- stuff in compiler/ghc.mk makes DynFlags link to too much stuff +{-# LANGUAGE CPP #-} module Hooks ( Hooks , emptyHooks , lookupHook @@ -14,13 +15,17 @@ module Hooks ( Hooks , tcForeignImportsHook , tcForeignExportsHook , hscFrontendHook +#ifdef GHCI , hscCompileCoreExprHook +#endif , ghcPrimIfaceHook , runPhaseHook , runMetaHook , linkHook , runRnSpliceHook +#ifdef GHCI , getValueSafelyHook +#endif ) where import DynFlags @@ -36,6 +41,9 @@ import TcRnTypes import Bag import RdrName import CoreSyn +#ifdef GHCI +import GHCi.RemoteTypes +#endif import BasicTypes import Type import SrcLoc @@ -55,21 +63,40 @@ import Data.Maybe -- uses the default built-in behaviour emptyHooks :: Hooks -emptyHooks = Hooks Nothing Nothing Nothing Nothing Nothing - Nothing Nothing Nothing Nothing Nothing Nothing +emptyHooks = Hooks + { dsForeignsHook = Nothing + , 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 +#endif + } data Hooks = Hooks { dsForeignsHook :: Maybe ([LForeignDecl Id] -> DsM (ForeignStubs, OrdList (Id, CoreExpr))) , 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) - , hscCompileCoreExprHook :: Maybe (HscEnv -> SrcSpan -> CoreExpr -> IO HValue) +#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)) +#endif } getHooked :: (Functor f, HasDynFlags f) => (Hooks -> Maybe a) -> a -> f a |