Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
Show all changes
21 commits
Select commit Hold shift + click to select a range
cdad9bc
fix: add frontend-plugins flag to ghc-bin
angerman Nov 25, 2025
3e63c36
reduce size of stage1 compiler with flags
luite Nov 26, 2025
53051cf
refactor: replace broad CPP flags with granular topic-specific flags
angerman Nov 26, 2025
97d2210
refactor: consolidate CPP with record-based dispatch and remove redun…
angerman Nov 26, 2025
f285b65
refactor: centralize interpreter stub types into single module
angerman Nov 26, 2025
68d3566
fix: add missing CPP pragma to GHC/Runtime/Eval.hs
angerman Nov 26, 2025
979ab32
fix: remove incorrect CPP guard around hscCheckSafeImports
angerman Nov 27, 2025
4359a59
Address PR 118 review comments
angerman Dec 1, 2025
57be879
fix: use explicit import in PPC/CodeGen.hs to avoid ambiguity
angerman Dec 1, 2025
68fe2de
fix: address PR review comments
angerman Dec 2, 2025
27069ce
fix: add missing ghc-platform to cabal.project.stage1
angerman Dec 2, 2025
ffa470d
perf: split GHC.Hs.Instances for parallel compilation (#18254)
angerman Dec 10, 2025
f8c17a0
fix: add missing Interpreter.C and Interpreter.Init to ghc.cabal.in
angerman Dec 10, 2025
c53a969
fix: remove non-existent GHC.Linker.ExtraObj from ghc.cabal.in
angerman Dec 10, 2025
f12b01c
fix: guard HsModule Data instance with HAVE_INTERPRETER
angerman Dec 11, 2025
affadce
fix: make GHC.Hs.Instances modules unconditional
angerman Dec 11, 2025
da122e4
fix: add missing imports to split GHC.Hs.Instances modules
angerman Dec 11, 2025
8e0c6be
fix: reorganize GHC.Hs.Instances module split to respect NHsValBindsL…
angerman Dec 11, 2025
a5bddb0
fix: stub functions and imports for HAVE_INTERPRETER builds
angerman Dec 11, 2025
6e4113f
fix: guard Interpreter/Init.hs with HAVE_INTERPRETER
angerman Dec 11, 2025
f139792
fix: guard Config/Interpreter.hs with HAVE_INTERPRETER
angerman Dec 11, 2025
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -202,6 +202,7 @@ _darcs/
/testsuite*.xml
/testlog*
/utils/ghc-iserv/ghc-iserv.cabal
/utils/iserv/iserv.cabal
/utils/iserv-proxy/iserv-proxy.cabal
/utils/remote-iserv/remote-iserv.cabal
/utils/mkUserGuidePart/mkUserGuidePart.cabal
Expand Down
12 changes: 8 additions & 4 deletions cabal.project.stage1
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@ packages:
-- Internal libraries
libraries/ghc-boot
libraries/ghc-boot-th-next
libraries/ghci
libraries/ghc-platform
libraries/libffi-clib

Expand Down Expand Up @@ -67,9 +66,14 @@ package *

package ghc
flags: +bootstrap

package ghci
flags: +bootstrap
+x86-ncg +aarch64-ncg
-ppc-ncg -riscv64-ncg -loongarch64-ncg
-js-backend -wasm-backend
+llvm-backend
-interpreter -dynamic-linker
Comment on lines +69 to +73
Copy link
Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think we might want to disable llvm-backend by default. And only enable +x86-ncg with a conditionalif arch(x86), same for aarch64?


package ghc-bin
flags: -frontend-plugins

package ghc-boot
flags: +bootstrap
Expand Down
48 changes: 46 additions & 2 deletions compiler/GHC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,8 +39,10 @@ module GHC (
setUnitDynFlags,
getProgramDynFlags, setProgramDynFlags,
setProgramHUG, setProgramHUG_,
#if defined(HAVE_INTERPRETER)
getInteractiveDynFlags, setInteractiveDynFlags,
normaliseInteractiveDynFlags, initialiseInteractiveDynFlags,
#endif
interpretPackageEnv,

-- * Logging
Expand All @@ -61,7 +63,10 @@ module GHC (

-- * Loading\/compiling the program
depanal, depanalE,
load, loadWithCache, LoadHowMuch(..), InteractiveImport(..),
load, loadWithCache, LoadHowMuch(..),
#if defined(HAVE_INTERPRETER)
InteractiveImport(..),
#endif
SuccessFlag(..), succeeded, failed,
defaultWarnErrLogger, WarnErrLogger,
workingDirectoryChanged,
Expand Down Expand Up @@ -142,7 +147,7 @@ module GHC (
NamePprCtx, alwaysQualify,

-- * Interactive evaluation

#if defined(HAVE_INTERPRETER)
-- ** Executing statements
execStmt, execStmt', ExecOptions(..), execOptions, ExecResult(..),
resumeExec,
Expand All @@ -153,7 +158,9 @@ module GHC (
-- ** Get/set the current context
parseImportDecl,
setContext, getContext,
#if defined(HAVE_INTERPRETER)
setGHCiMonad, getGHCiMonad,
#endif

-- ** Inspecting the current context
getBindings, getInsts, getNamePprCtx,
Expand All @@ -164,7 +171,9 @@ module GHC (
isModuleTrusted, moduleTrustReqs,
getNamesInScope,
getRdrNamesInScope,
#if defined(HAVE_INTERPRETER)
getGRE,
#endif
moduleIsInterpreted,
getInfo,
showModule,
Expand All @@ -191,8 +200,10 @@ module GHC (
-- ** Other
runTcInteractive, -- Desired by some clients (#8878)
isStmt, hasImport, isImport, isDecl,
#endif

-- ** The debugger
#if defined(HAVE_INTERPRETER)
SingleStep(..),
Resume(..),
History(historyBreakpointId, historyEnclosingDecls),
Expand All @@ -206,6 +217,7 @@ module GHC (
GHC.Runtime.Eval.back,
GHC.Runtime.Eval.forward,
GHC.Runtime.Eval.setupBreakpoint,
#endif

-- * Abstract syntax elements

Expand Down Expand Up @@ -270,8 +282,10 @@ module GHC (
Kind,
PredType,
ThetaType, pprForAll, pprThetaArrowTy,
#if defined(HAVE_INTERPRETER)
parseInstanceHead,
getInstancesForType,
#endif

-- ** Entities
TyThing(..),
Expand Down Expand Up @@ -357,6 +371,8 @@ import GHC.Driver.Hooks
import GHC.Driver.Monad
import GHC.Driver.Ppr

#if defined(HAVE_INTERPRETER)
import GHC.Driver.Config.StgToJS (initStgToJSConfig)
import GHC.ByteCode.Types
import GHC.Runtime.Loader
import GHC.Runtime.Eval
Expand All @@ -365,6 +381,7 @@ import GHC.Runtime.Interpreter.Init
import GHC.Driver.Config.Interpreter
import GHC.Runtime.Context
import GHCi.RemoteTypes
#endif

import qualified GHC.Parser as Parser
import GHC.Parser.Lexer
Expand Down Expand Up @@ -575,7 +592,9 @@ withCleanupSession ghc = ghc `MC.finally` cleanup
unless (gopt Opt_KeepTmpFiles dflags) $ do
cleanTempFiles logger tmpfs
cleanTempDirs logger tmpfs
#if defined(HAVE_INTERPRETER)
traverse_ stopInterp (hsc_interp hsc_env)
#endif
-- exceptions will be blocked while we clean the temporary files,
-- so there shouldn't be any difficulty if we receive further
-- signals.
Expand Down Expand Up @@ -709,6 +728,8 @@ setTopSessionDynFlags :: GhcMonad m => DynFlags -> m ()
setTopSessionDynFlags dflags = do
hsc_env <- getSession
logger <- getLogger

#if defined(HAVE_INTERPRETER)
let platform = targetPlatform dflags
let unit_env = hsc_unit_env hsc_env
let tmpfs = hsc_tmpfs hsc_env
Expand All @@ -719,11 +740,19 @@ setTopSessionDynFlags dflags = do
}

interp <- liftIO $ initInterpreter tmpfs logger platform finder_cache unit_env interp_opts
#else
-- No interpreter support (HAVE_INTERPRETER not defined)
let interp = Nothing
#endif

modifySession $ \h -> hscSetFlags dflags
#if defined(HAVE_INTERPRETER)
h{ hsc_IC = (hsc_IC h){ ic_dflags = dflags }
, hsc_interp = hsc_interp h <|> interp
}
#else
h{ hsc_interp = hsc_interp h <|> interp }
#endif

invalidateModSummaryCache

Expand Down Expand Up @@ -923,6 +952,7 @@ getProgramDynFlags = getSessionDynFlags
-- Note: this cannot be used for changes to packages. Use
-- 'setSessionDynFlags', or 'setProgramDynFlags' and then copy the
-- 'unitState' into the interactive @DynFlags@.
#if defined(HAVE_INTERPRETER)
setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
setInteractiveDynFlags dflags = do
logger <- getLogger
Expand All @@ -932,6 +962,7 @@ setInteractiveDynFlags dflags = do
-- | Get the 'DynFlags' used to evaluate interactive expressions.
getInteractiveDynFlags :: GhcMonad m => m DynFlags
getInteractiveDynFlags = withSession $ \h -> return (ic_dflags (hsc_IC h))
#endif


parseDynamicFlags
Expand Down Expand Up @@ -1035,10 +1066,12 @@ normalise_hyp fp
-- | Normalise the 'DynFlags' for us in an interactive context.
--
-- Makes sure unsupported Flags and other incosistencies are reported and removed.
#if defined(HAVE_INTERPRETER)
normaliseInteractiveDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags
normaliseInteractiveDynFlags logger dflags = do
dflags' <- checkNewDynFlags logger dflags
checkNewInteractiveDynFlags logger dflags'
#endif

-- | Given a set of normalised 'DynFlags' (see 'normaliseInteractiveDynFlags')
-- for the interactive context, initialize the 'InteractiveContext'.
Expand All @@ -1049,6 +1082,7 @@ initialiseInteractiveDynFlags :: GhcMonad m => DynFlags -> HscEnv -> m HscEnv
initialiseInteractiveDynFlags dflags hsc_env0 = do
let ic0 = hsc_IC hsc_env0

#if defined(HAVE_INTERPRETER)
-- Initialise (load) plugins in the interactive environment with the new
-- DynFlags
plugin_env <- liftIO $ initializePlugins $ mkInteractiveHscEnv $
Expand All @@ -1061,6 +1095,10 @@ initialiseInteractiveDynFlags dflags hsc_env0 = do
, ic_dflags = hsc_dflags plugin_env
}
}
#else
-- No plugin support (HAVE_INTERPRETER not defined)
return hsc_env0
#endif

-- | Checks the set of new DynFlags for possibly erroneous option
-- combinations when invoking 'setSessionDynFlags' and friends, and if
Expand Down Expand Up @@ -1498,8 +1536,10 @@ findGlobalAnns deserialize target = withSession $ \hsc_env -> do
return (findAnns deserialize ann_env target)

-- | get the GlobalRdrEnv for a session
#if defined(HAVE_INTERPRETER)
getGRE :: GhcMonad m => m GlobalRdrEnv
getGRE = withSession $ \hsc_env-> return $ icReaderEnv (hsc_IC hsc_env)
#endif

-- | Retrieve all type and family instances in the environment, indexed
-- by 'Name'. Each name's lists will contain every instance in which that name
Expand Down Expand Up @@ -1794,6 +1834,7 @@ moduleTrustReqs :: GhcMonad m => Module -> m (Bool, Set UnitId)
moduleTrustReqs m = withSession $ \hsc_env ->
liftIO $ hscGetSafe hsc_env m noSrcSpan

#if defined(HAVE_INTERPRETER)
-- | Set the monad GHCi lifts user statements into.
--
-- Checks that a type (in string form) is an instance of the
Expand All @@ -1809,7 +1850,9 @@ setGHCiMonad name = withSession $ \hsc_env -> do
-- | Get the monad GHCi lifts user statements into.
getGHCiMonad :: GhcMonad m => m Name
getGHCiMonad = fmap (ic_monad . hsc_IC) getSession
#endif

#if defined(HAVE_INTERPRETER)
getHistorySpan :: GhcMonad m => History -> m SrcSpan
getHistorySpan h = withSession $ \hsc_env -> liftIO $ GHC.Runtime.Eval.getHistorySpan (hsc_HUG hsc_env) h

Expand All @@ -1824,6 +1867,7 @@ obtainTermFromId :: GhcMonad m
-> m Term
obtainTermFromId bound force id = withSession $ \hsc_env ->
liftIO $ GHC.Runtime.Eval.obtainTermFromId hsc_env bound force id
#endif


-- | Returns the 'TyThing' for a 'Name'. The 'Name' may refer to any
Expand Down
3 changes: 3 additions & 0 deletions compiler/GHC/ByteCode/Linker.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,8 @@
--
-- (c) The University of Glasgow 2002-2006
--
-- NOTE: This module is only compiled when flag(interpreter) is enabled
-- (see ghc.cabal.in). No CPP guards needed.

-- | Bytecode assembler and linker
module GHC.ByteCode.Linker
Expand Down Expand Up @@ -238,3 +240,4 @@ primopToCLabel primop suffix = concat
, zString (zEncodeFS (occNameFS (primOpOcc primop)))
, '_':suffix
]

35 changes: 32 additions & 3 deletions compiler/GHC/CmmToAsm.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE CPP #-}

-- -----------------------------------------------------------------------------
--
-- (c) The University of Glasgow 1993-2004
Expand Down Expand Up @@ -27,7 +29,7 @@
-- possible.
--
-- The machine-dependent bits are generally contained under
-- GHC/CmmToAsm/<Arch>/* and generally breaks down as follows:
-- GHC/CmmToAsm/<Arch> and generally breaks down as follows:
--
-- * "Regs": Everything about the target platform's machine
-- registers (and immediate operands, and addresses, which tend to
Expand Down Expand Up @@ -63,12 +65,25 @@ where

import GHC.Prelude hiding (head)

#if defined(HAVE_X86_NCG)
import qualified GHC.CmmToAsm.X86 as X86
import qualified GHC.CmmToAsm.PPC as PPC
#endif
#if defined(HAVE_AARCH64_NCG)
import qualified GHC.CmmToAsm.AArch64 as AArch64
import qualified GHC.CmmToAsm.Wasm as Wasm32
#endif
#if defined(HAVE_PPC_NCG)
import qualified GHC.CmmToAsm.PPC as PPC
#endif
#if defined(HAVE_RISCV64_NCG)
import qualified GHC.CmmToAsm.RV64 as RV64
#endif
#if defined(HAVE_LOONGARCH64_NCG)
import qualified GHC.CmmToAsm.LA64 as LA64
#endif
#if defined(HAVE_WASM_BACKEND)
import qualified GHC.CmmToAsm.Wasm as Wasm32
#endif


import GHC.CmmToAsm.Reg.Liveness
import qualified GHC.CmmToAsm.Reg.Linear as Linear
Expand Down Expand Up @@ -141,21 +156,35 @@ nativeCodeGen logger ts config modLoc h cmms
=> NcgImpl statics instr jumpDest -> UniqDSMT IO a
nCG' ncgImpl = nativeCodeGen' logger config modLoc ncgImpl h cmms
in case platformArch platform of
#if defined(HAVE_X86_NCG)
ArchX86 -> nCG' (X86.ncgX86 config)
ArchX86_64 -> nCG' (X86.ncgX86_64 config)
#endif
#if defined(HAVE_PPC_NCG)
ArchPPC -> nCG' (PPC.ncgPPC config)
ArchPPC_64 _ -> nCG' (PPC.ncgPPC config)
#endif
ArchS390X -> panic "nativeCodeGen: No NCG for S390X"
ArchARM {} -> panic "nativeCodeGen: No NCG for ARM"
#if defined(HAVE_AARCH64_NCG)
ArchAArch64 -> nCG' (AArch64.ncgAArch64 config)
#endif
ArchAlpha -> panic "nativeCodeGen: No NCG for Alpha"
ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb"
ArchMipsel -> panic "nativeCodeGen: No NCG for mipsel"
#if defined(HAVE_RISCV64_NCG)
ArchRISCV64 -> nCG' (RV64.ncgRV64 config)
#endif
#if defined(HAVE_LOONGARCH64_NCG)
ArchLoongArch64 -> nCG' (LA64.ncgLA64 config)
#endif
ArchUnknown -> panic "nativeCodeGen: No NCG for unknown arch"
ArchJavaScript-> panic "nativeCodeGen: No NCG for JavaScript"
#if defined(HAVE_WASM_BACKEND)
ArchWasm32 -> Wasm32.ncgWasm config logger platform ts modLoc h cmms
#endif
_ -> panic "nativeCodeGen: No NCG for this architecture"


-- | Data accumulated during code generation. Mostly about statistics,
-- but also collects debug data for DWARF generation.
Expand Down
Loading
Loading