1+ {-# LANGUAGE CPP #-}
12{-# LANGUAGE LambdaCase #-}
23{-# LANGUAGE NondecreasingIndentation #-}
34{-# LANGUAGE GADTs #-}
@@ -134,18 +135,24 @@ import GHC.Driver.Config.Stg.Pipeline (initStgPipelineOpts)
134135import GHC.Driver.Config.StgToCmm (initStgToCmmConfig )
135136import GHC.Driver.Config.Cmm (initCmmConfig )
136137import GHC.Driver.LlvmConfigCache (initLlvmConfigCache )
138+ #if !defined(MINIMAL)
137139import GHC.Driver.Config.StgToJS (initStgToJSConfig )
140+ #endif
138141import GHC.Driver.Config.Diagnostic
139142import GHC.Driver.Config.Tidy
140143import GHC.Driver.Hooks
141144import GHC.Driver.GenerateCgIPEStub (generateCgIPEStub , lookupEstimatedTicks )
142145
143146import GHC.Runtime.Context
144147import GHC.Runtime.Interpreter
148+ #if !defined(MINIMAL)
145149import GHC.Runtime.Interpreter.JS
150+ #endif
146151import GHC.Runtime.Loader ( initializePlugins )
147152import GHCi.RemoteTypes
153+ #if !defined(MINIMAL)
148154import GHC.ByteCode.Types
155+ #endif
149156
150157import GHC.Linker.Loader
151158import GHC.Linker.Types
@@ -157,11 +164,13 @@ import GHC.Hs.Stats ( ppSourceStats )
157164
158165import GHC.HsToCore
159166
167+ #if !defined(MINIMAL)
160168import GHC.StgToByteCode ( byteCodeGen )
161169import GHC.StgToJS ( stgToJS )
162170import GHC.StgToJS.Ids
163171import GHC.StgToJS.Types
164172import GHC.JS.Syntax
173+ #endif
165174
166175import GHC.IfaceToCore ( typecheckIface , typecheckWholeCoreBindings )
167176
@@ -693,9 +702,13 @@ hsc_typecheck keep_rn mod_summary mb_rdr_module = do
693702 Nothing -> hscParse' mod_summary
694703 tc_result0 <- tcRnModule' mod_summary keep_rn' hpm
695704 if hsc_src == HsigFile
705+ #if defined(MINIMAL)
706+ then panic " hscSimpleIface not available in MINIMAL build"
707+ #else
696708 then do (iface, _) <- liftIO $ hscSimpleIface hsc_env Nothing tc_result0 mod_summary
697709 ioMsgMaybe $ hoistTcRnMessage $
698710 tcRnMergeSignatures hsc_env hpm tc_result0 iface
711+ #endif
699712 else return tc_result0
700713 -- TODO are we extracting anything when we merely instantiate a signature?
701714 -- If not, try to move this into the "else" case above.
@@ -732,11 +745,19 @@ tcRnModule' sum save_rn_syntax mod = do
732745 if not (safeHaskellOn dflags)
733746 || (safeInferOn dflags && not allSafeOK)
734747 -- if safe Haskell off or safe infer failed, mark unsafe
748+ #if defined(MINIMAL)
749+ then return tcg_res
750+ #else
735751 then markUnsafeInfer tcg_res whyUnsafe
752+ #endif
736753
737754 -- module (could be) safe, throw warning if needed
738755 else do
756+ #if defined(MINIMAL)
757+ let tcg_res' = tcg_res
758+ #else
739759 tcg_res' <- hscCheckSafeImports tcg_res
760+ #endif
740761 safe <- liftIO $ readIORef (tcg_safe_infer tcg_res')
741762 when safe $
742763 case wopt Opt_WarnSafe dflags of
@@ -992,7 +1013,11 @@ initModDetails hsc_env iface =
9921013 -- in one-shot mode, since we're not going to do
9931014 -- any further typechecking. It's much more useful
9941015 -- in make mode, since this HMI will go into the HPT.
1016+ #if defined(MINIMAL)
1017+ return (panic " genModDetails not available in MINIMAL build" )
1018+ #else
9951019 genModDetails hsc_env iface
1020+ #endif
9961021
9971022-- | Modify flags such that objects are compiled for the interpreter's way.
9981023-- This is necessary when building foreign objects for Template Haskell, since
@@ -1046,6 +1071,9 @@ loadIfaceByteCode ::
10461071 ModLocation ->
10471072 TypeEnv ->
10481073 Maybe (IO Linkable )
1074+ #if defined(MINIMAL)
1075+ loadIfaceByteCode _ _ _ _ = Nothing
1076+ #else
10491077loadIfaceByteCode hsc_env iface location type_env =
10501078 compile <$> iface_core_bindings iface location
10511079 where
@@ -1057,13 +1085,17 @@ loadIfaceByteCode hsc_env iface location type_env =
10571085 if_time <- modificationTimeIfExists (ml_hi_file location)
10581086 time <- maybe getCurrentTime pure if_time
10591087 return $! Linkable time (mi_module iface) parts
1088+ #endif
10601089
10611090loadIfaceByteCodeLazy ::
10621091 HscEnv ->
10631092 ModIface ->
10641093 ModLocation ->
10651094 TypeEnv ->
10661095 IO (Maybe Linkable )
1096+ #if defined(MINIMAL)
1097+ loadIfaceByteCodeLazy _ _ _ _ = return Nothing
1098+ #else
10671099loadIfaceByteCodeLazy hsc_env iface location type_env =
10681100 case iface_core_bindings iface location of
10691101 Nothing -> return Nothing
@@ -1078,6 +1110,7 @@ loadIfaceByteCodeLazy hsc_env iface location type_env =
10781110 if_time <- modificationTimeIfExists (ml_hi_file location)
10791111 time <- maybe getCurrentTime pure if_time
10801112 return $! Linkable time (mi_module iface) parts
1113+ #endif
10811114
10821115-- | If the 'Linkable' contains Core bindings loaded from an interface, replace
10831116-- them with a lazy IO thunk that compiles them to bytecode and foreign objects,
@@ -1107,6 +1140,9 @@ initWholeCoreBindings ::
11071140 ModDetails ->
11081141 Linkable ->
11091142 IO Linkable
1143+ #if defined(MINIMAL)
1144+ initWholeCoreBindings _ _ _ l = return l
1145+ #else
11101146initWholeCoreBindings hsc_env iface details (Linkable utc_time this_mod uls) = do
11111147 Linkable utc_time this_mod <$> mapM (go hsc_env) uls
11121148 where
@@ -1119,6 +1155,7 @@ initWholeCoreBindings hsc_env iface details (Linkable utc_time this_mod uls) = d
11191155 l -> pure l
11201156
11211157 type_env = md_types details
1158+ #endif
11221159
11231160-- | Hydrate interface Core bindings and compile them to bytecode.
11241161--
@@ -1134,6 +1171,7 @@ initWholeCoreBindings hsc_env iface details (Linkable utc_time this_mod uls) = d
11341171--
11351172-- 3. Generating bytecode and foreign objects from the results of the previous
11361173-- steps using the usual pipeline actions.
1174+ #if !defined(MINIMAL)
11371175compileWholeCoreBindings ::
11381176 HscEnv ->
11391177 TypeEnv ->
@@ -1168,6 +1206,7 @@ compileWholeCoreBindings hsc_env type_env wcb = do
11681206 WholeCoreBindings {wcb_module, wcb_mod_location, wcb_foreign} = wcb
11691207
11701208 logger = hsc_logger hsc_env
1209+ #endif
11711210
11721211{-
11731212Note [ModDetails and --make mode]
@@ -1263,6 +1302,9 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h
12631302 case mb_desugar of
12641303 -- Just cause we desugared doesn't mean we are generating code, see above.
12651304 Just desugared_guts | backendGeneratesCode bcknd -> do
1305+ #if defined(MINIMAL)
1306+ panic " hscSimplify' not available in MINIMAL build"
1307+ #else
12661308 plugins <- liftIO $ readIORef (tcg_th_coreplugins tc_result)
12671309 simplified_guts <- hscSimplify' plugins desugared_guts
12681310
@@ -1280,12 +1322,16 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h
12801322 hscs_partial_iface = partial_iface,
12811323 hscs_old_iface_hash = mb_old_hash
12821324 }
1325+ #endif
12831326
12841327 Just desugared_guts | gopt Opt_WriteIfSimplifiedCore dflags -> do
12851328 -- If -fno-code is enabled (hence we fall through to this case)
12861329 -- Running the simplifier once is necessary before doing byte code generation
12871330 -- in order to inline data con wrappers but we honour whatever level of simplificication the
12881331 -- user requested. See #22008 for some discussion.
1332+ #if defined(MINIMAL)
1333+ panic " hscSimplify' not available in MINIMAL build"
1334+ #else
12891335 plugins <- liftIO $ readIORef (tcg_th_coreplugins tc_result)
12901336 simplified_guts <- hscSimplify' plugins desugared_guts
12911337 (cg_guts, _) <-
@@ -1301,11 +1347,15 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h
13011347 if ms_mod summary == gHC_PRIM
13021348 then return $ HscUpdate (getGhcPrimIface (hsc_hooks hsc_env))
13031349 else return $ HscUpdate iface
1350+ #endif
13041351
13051352
13061353 -- We are not generating code or writing an interface with simplified core so we can skip simplification
13071354 -- and generate a simple interface.
13081355 _ -> do
1356+ #if defined(MINIMAL)
1357+ panic " hscSimpleIface not available in MINIMAL build"
1358+ #else
13091359 (iface, _details) <- liftIO $
13101360 hscSimpleIface hsc_env Nothing tc_result summary
13111361
@@ -1316,6 +1366,7 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h
13161366 if ms_mod summary == gHC_PRIM
13171367 then return $ HscUpdate (getGhcPrimIface (hsc_hooks hsc_env))
13181368 else return $ HscUpdate iface
1369+ #endif
13191370
13201371{-
13211372Note [Writing interface files]
0 commit comments