Skip to content

Commit 702b86f

Browse files
Stable Haskell TeamGHC GitLab CI
authored andcommitted
feat: Complete multi-target support and compiler enhancements
This commit completes the multi-target support infrastructure with comprehensive changes across the compiler, build system, and runtime components. These changes enable GHC to efficiently target multiple platforms including native, JavaScript, and cross-compilation scenarios. Core Compiler Changes: - GHC.Driver.DynFlags: Multi-target configuration support - GHC.Driver.Session: Enhanced session management for targets - GHC.Driver.Make: Updated build orchestration for stages - GHC.Driver.Downsweep: Improved module dependency handling - GHC.ByteCode.Asm: Cross-platform bytecode assembly - GHC.Iface.Load: Added Hooks parameter for interface loading - GHC.Unit.State: Multi-target package database handling LLVM Integration: - GHC.CmmToLlvm.*: Refactored LLVM backend configuration - Removed Version/Bounds.hs.in template - Dynamic LLVM version detection - Improved LLVM toolchain integration JavaScript Backend: - GHC.Driver.Config.StgToJS: JavaScript code generation config - Enhanced JavaScript runtime support - Integration with multi-stage build system Linker and Code Generation: - GHC.Linker.Dynamic: Cross-platform dynamic linking - GHC.Linker.Static: Static linking improvements - GHC.Linker.ExtraObj: Object file handling - GHC.Driver.CodeOutput: Multi-target code emission - CodeGen.Platform.h: Platform-specific code generation Build System: - ghc-pkg: Added --target flag support - deriveConstants: Cross-compilation aware - genprimopcode: Target-specific primop generation - Setup.hs files: Updated for new build infrastructure - packages: Updated submodule references Libraries: - system-cxx-std-lib: New C++ standard library wrapper - ghc-internal: Updated configuration - ghc-boot: Build system adjustments - ghc-prim: Cross-compilation support Testing Infrastructure: - Updated test driver for multi-target scenarios - Fixed platform-specific tests - Adjusted test expectations for new architecture - Added T10279h.hs test helper External Dependencies: - Removed libffi-tarballs (using system packages) - Updated Cabal submodule - Updated hsc2hs for cross-compilation Utilities: - unlit: Cross-platform compatibility - ghc-toolchain: Target detection improvements - config.guess/config.sub: GNU config files for RTS - Added .envrc for development environment - Added configure script for build configuration Contributors: - Moritz Angermann: Multi-target architecture and cross-compilation - Sylvain Henry: JavaScript backend integration - Andrea Bedini: Build system improvements - Julian Ospald: Testing infrastructure and utilities This completes the foundational work for GHC's multi-target support, enabling efficient compilation for diverse platforms while maintaining backward compatibility and build reproducibility.
1 parent 563799e commit 702b86f

File tree

102 files changed

+7724
-1012
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

102 files changed

+7724
-1012
lines changed

.envrc

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
# Check if nix-direnv is already loaded; if not, source it
2+
if ! has nix_direnv_reload; then
3+
source_url "https://raw.githubusercontent.com/nix-community/nix-direnv/3.0.7/direnvrc" "sha256-bn8WANE5a91RusFmRI7kS751ApelG02nMcwRekC/qzc="
4+
fi
5+
6+
# Use the specified flake to enter the Nix development environment
7+
use flake github:input-output-hk/devx#ghc98-minimal-ghc

.gitmodules

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -8,8 +8,9 @@
88
ignore = untracked
99
[submodule "libraries/Cabal"]
1010
path = libraries/Cabal
11-
url = https://gitlab.haskell.org/ghc/packages/Cabal.git
11+
url = https://github.com/stable-haskell/Cabal.git
1212
ignore = untracked
13+
branch = stable-haskell/feature/cross-compile
1314
[submodule "libraries/containers"]
1415
path = libraries/containers
1516
url = https://gitlab.haskell.org/ghc/packages/containers.git
@@ -99,10 +100,6 @@
99100
path = utils/hsc2hs
100101
url = https://gitlab.haskell.org/ghc/hsc2hs.git
101102
ignore = untracked
102-
[submodule "libffi-tarballs"]
103-
path = libffi-tarballs
104-
url = https://gitlab.haskell.org/ghc/libffi-tarballs.git
105-
ignore = untracked
106103
[submodule "gmp-tarballs"]
107104
path = libraries/ghc-internal/gmp/gmp-tarballs
108105
url = https://gitlab.haskell.org/ghc/gmp-tarballs.git

compiler/CodeGen.Platform.h

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ import GHC.Utils.Panic.Plain
77
#endif
88
import GHC.Platform.Reg
99

10-
#include "MachRegs.h"
10+
#include "stg/MachRegs.h"
1111

1212
#if defined(MACHREGS_i386) || defined(MACHREGS_x86_64)
1313

compiler/GHC/Builtin/PrimOps.hs

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,9 @@ module GHC.Builtin.PrimOps (
2525

2626
getPrimOpResultInfo, isComparisonPrimOp, PrimOpResultInfo(..),
2727

28-
PrimCall(..)
28+
PrimCall(..),
29+
30+
primOpPrimModule, primOpWrappersModule
2931
) where
3032

3133
import GHC.Prelude
@@ -171,6 +173,12 @@ primOpDocs :: [(FastString, String)]
171173
primOpDeprecations :: [(OccName, FastString)]
172174
#include "primop-deprecations.hs-incl"
173175

176+
primOpPrimModule :: String
177+
#include "primop-prim-module.hs-incl"
178+
179+
primOpWrappersModule :: String
180+
#include "primop-wrappers-module.hs-incl"
181+
174182
{-
175183
************************************************************************
176184
* *

compiler/GHC/ByteCode/Asm.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -532,7 +532,7 @@ countSmall big x = count big False x
532532

533533

534534
-- Bring in all the bci_ bytecode constants.
535-
#include "Bytecodes.h"
535+
#include "rts/Bytecodes.h"
536536

537537
largeArgInstr :: Word16 -> Word16
538538
largeArgInstr bci = bci_FLAG_LARGE_ARGS .|. bci

compiler/GHC/CmmToLlvm.hs

Lines changed: 3 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -38,8 +38,8 @@ import GHC.Utils.Panic
3838
import GHC.Utils.Logger
3939
import qualified GHC.Data.Stream as Stream
4040

41-
import Control.Monad ( when, forM_ )
42-
import Data.Maybe ( fromMaybe, catMaybes, isNothing )
41+
import Control.Monad ( forM_ )
42+
import Data.Maybe ( catMaybes )
4343
import System.IO
4444

4545
-- -----------------------------------------------------------------------------
@@ -57,36 +57,8 @@ llvmCodeGen logger cfg h dus cmm_stream
5757
-- Pass header
5858
showPass logger "LLVM CodeGen"
5959

60-
-- get llvm version, cache for later use
61-
let mb_ver = llvmCgLlvmVersion cfg
62-
63-
-- warn if unsupported
64-
forM_ mb_ver $ \ver -> do
65-
debugTraceMsg logger 2
66-
(text "Using LLVM version:" <+> text (llvmVersionStr ver))
67-
let doWarn = llvmCgDoWarn cfg
68-
when (not (llvmVersionSupported ver) && doWarn) $ putMsg logger $
69-
"You are using an unsupported version of LLVM!" $$
70-
"Currently only" <+> text (llvmVersionStr supportedLlvmVersionLowerBound) <+>
71-
"up to" <+> text (llvmVersionStr supportedLlvmVersionUpperBound) <+> "(non inclusive) is supported." <+>
72-
"System LLVM version: " <> text (llvmVersionStr ver) $$
73-
"We will try though..."
74-
75-
when (isNothing mb_ver) $ do
76-
let doWarn = llvmCgDoWarn cfg
77-
when doWarn $ putMsg logger $
78-
"Failed to detect LLVM version!" $$
79-
"Make sure LLVM is installed correctly." $$
80-
"We will try though..."
81-
82-
-- HACK: the Nothing case here is potentially wrong here but we
83-
-- currently don't use the LLVM version to guide code generation
84-
-- so this is okay.
85-
let llvm_ver :: LlvmVersion
86-
llvm_ver = fromMaybe supportedLlvmVersionLowerBound mb_ver
87-
8860
-- run code generation
89-
(a, _) <- runLlvm logger cfg llvm_ver bufh dus $
61+
(a, _) <- runLlvm logger cfg bufh dus $
9062
llvmCodeGen' cfg cmm_stream
9163

9264
bFlush bufh

compiler/GHC/CmmToLlvm/Base.hs

Lines changed: 4 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ module GHC.CmmToLlvm.Base (
1818
LlvmM,
1919
runLlvm, withClearVars, varLookup, varInsert,
2020
markStackReg, checkStackReg,
21-
funLookup, funInsert, getLlvmVer,
21+
funLookup, funInsert,
2222
dumpIfSetLlvm, renderLlvm, markUsedVar, getUsedVars,
2323
ghcInternalFunctions, getPlatform, getConfig,
2424

@@ -277,8 +277,7 @@ llvmPtrBits platform = widthInBits $ typeWidth $ gcWord platform
277277
--
278278

279279
data LlvmEnv = LlvmEnv
280-
{ envVersion :: LlvmVersion -- ^ LLVM version
281-
, envConfig :: !LlvmCgConfig -- ^ Configuration for LLVM code gen
280+
{ envConfig :: !LlvmCgConfig -- ^ Configuration for LLVM code gen
282281
, envLogger :: !Logger -- ^ Logger
283282
, envOutput :: BufHandle -- ^ Output buffer
284283
, envTag :: !Char -- ^ Tag for creating unique values
@@ -331,16 +330,15 @@ liftUDSMT m = LlvmM $ \env -> do x <- m
331330
return (x, env)
332331

333332
-- | Get initial Llvm environment.
334-
runLlvm :: Logger -> LlvmCgConfig -> LlvmVersion -> BufHandle -> DSM.DUniqSupply -> LlvmM a -> IO (a, DSM.DUniqSupply)
335-
runLlvm logger cfg ver out us m = do
333+
runLlvm :: Logger -> LlvmCgConfig -> BufHandle -> DSM.DUniqSupply -> LlvmM a -> IO (a, DSM.DUniqSupply)
334+
runLlvm logger cfg out us m = do
336335
((a, _), us') <- DSM.runUDSMT us $ runLlvmM m env
337336
return (a, us')
338337
where env = LlvmEnv { envFunMap = emptyUFM
339338
, envVarMap = emptyUFM
340339
, envStackRegs = []
341340
, envUsedVars = []
342341
, envAliases = emptyUniqSet
343-
, envVersion = ver
344342
, envConfig = cfg
345343
, envLogger = logger
346344
, envOutput = out
@@ -388,10 +386,6 @@ getMetaUniqueId :: LlvmM MetaId
388386
getMetaUniqueId = LlvmM $ \env ->
389387
return (envFreshMeta env, env { envFreshMeta = succ $ envFreshMeta env })
390388

391-
-- | Get the LLVM version we are generating code for
392-
getLlvmVer :: LlvmM LlvmVersion
393-
getLlvmVer = getEnv envVersion
394-
395389
-- | Dumps the document if the corresponding flag has been set by the user
396390
dumpIfSetLlvm :: DumpFlag -> String -> DumpFormat -> Outp.SDoc -> LlvmM ()
397391
dumpIfSetLlvm flag hdr fmt doc = do

compiler/GHC/CmmToLlvm/Config.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,6 @@ data LlvmCgConfig = LlvmCgConfig
2525
, llvmCgAvxEnabled :: !Bool
2626
, llvmCgBmiVersion :: Maybe BmiVersion -- ^ (x86) BMI instructions
2727
, llvmCgLlvmVersion :: Maybe LlvmVersion -- ^ version of Llvm we're using
28-
, llvmCgDoWarn :: !Bool -- ^ True ==> warn unsupported Llvm version
2928
, llvmCgLlvmTarget :: !String -- ^ target triple passed to LLVM
3029
, llvmCgLlvmConfig :: !LlvmConfig -- ^ Supported LLVM configurations.
3130
-- see Note [LLVM configuration]

compiler/GHC/CmmToLlvm/Version.hs

Lines changed: 0 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,6 @@
11
module GHC.CmmToLlvm.Version
22
( LlvmVersion(..)
3-
, supportedLlvmVersionLowerBound
4-
, supportedLlvmVersionUpperBound
53
, parseLlvmVersion
6-
, llvmVersionSupported
74
, llvmVersionStr
85
, llvmVersionList
96
)
@@ -12,7 +9,6 @@ where
129
import GHC.Prelude
1310

1411
import GHC.CmmToLlvm.Version.Type
15-
import GHC.CmmToLlvm.Version.Bounds
1612

1713
import Data.Char (isDigit)
1814
import Data.List (intercalate)
@@ -32,10 +28,6 @@ parseLlvmVersion =
3228
where
3329
(ver_str, rest) = span isDigit s
3430

35-
llvmVersionSupported :: LlvmVersion -> Bool
36-
llvmVersionSupported v =
37-
v >= supportedLlvmVersionLowerBound && v < supportedLlvmVersionUpperBound
38-
3931
llvmVersionStr :: LlvmVersion -> String
4032
llvmVersionStr = intercalate "." . map show . llvmVersionList
4133

compiler/GHC/CmmToLlvm/Version/Bounds.hs.in

Lines changed: 0 additions & 19 deletions
This file was deleted.

0 commit comments

Comments
 (0)