1{
2 version,
3 rev ? null,
4 sha256,
5 url ?
6 if rev != null then
7 "https://gitlab.haskell.org/ghc/ghc.git"
8 else
9 "https://downloads.haskell.org/ghc/${version}/ghc-${version}-src.tar.xz",
10 postFetch ? null,
11}:
12
13{
14 lib,
15 stdenv,
16 stdenvNoCC,
17 pkgsBuildTarget,
18 pkgsHostTarget,
19 buildPackages,
20 targetPackages,
21 fetchpatch,
22
23 # build-tools
24 bootPkgs,
25 autoreconfHook,
26 coreutils,
27 fetchurl,
28 fetchgit,
29 perl,
30 python3,
31 sphinx,
32 xattr,
33 autoSignDarwinBinariesHook,
34 bash,
35 srcOnly,
36
37 libiconv ? null,
38 ncurses,
39
40 # GHC can be built with system libffi or a bundled one.
41 libffi ? null,
42
43 useLLVM ? !(import ./common-have-ncg.nix { inherit lib stdenv version; }),
44 # LLVM is conceptually a run-time-only dependency, but for
45 # non-x86, we need LLVM to bootstrap later stages, so it becomes a
46 # build-time dependency too.
47 buildTargetLlvmPackages,
48 llvmPackages,
49
50 # If enabled, GHC will be built with the GPL-free but slightly slower native
51 # bignum backend instead of the faster but GPLed gmp backend.
52 enableNativeBignum ?
53 !(lib.meta.availableOn stdenv.hostPlatform gmp && lib.meta.availableOn stdenv.targetPlatform gmp)
54 || stdenv.targetPlatform.isGhcjs,
55 gmp,
56
57 # If enabled, use -fPIC when compiling static libs.
58 enableRelocatedStaticLibs ? stdenv.targetPlatform != stdenv.hostPlatform,
59
60 # Exceeds Hydra output limit (at the time of writing ~3GB) when cross compiled to riscv64.
61 # A riscv64 cross-compiler fits into the limit comfortably.
62 enableProfiledLibs ? !stdenv.hostPlatform.isRiscV64,
63
64 # Whether to build dynamic libs for the standard library (on the target
65 # platform). Static libs are always built.
66 enableShared ? with stdenv.targetPlatform; !isWindows && !useiOSPrebuilt && !isStatic && !isGhcjs,
67
68 # Whether to build terminfo.
69 # FIXME(@sternenseemann): This actually doesn't influence what hadrian does,
70 # just what buildInputs etc. looks like. It would be best if we could actually
71 # tell it what to do like it was possible with make.
72 enableTerminfo ?
73 !(
74 stdenv.targetPlatform.isWindows
75 || stdenv.targetPlatform.isGhcjs
76 # terminfo can't be built for cross
77 || (stdenv.buildPlatform != stdenv.hostPlatform)
78 || (stdenv.hostPlatform != stdenv.targetPlatform)
79 ),
80
81 # Libdw.c only supports x86_64, i686 and s390x as of 2022-08-04
82 enableDwarf ?
83 (stdenv.targetPlatform.isx86 || (stdenv.targetPlatform.isS390 && stdenv.targetPlatform.is64bit))
84 && lib.meta.availableOn stdenv.hostPlatform elfutils
85 && lib.meta.availableOn stdenv.targetPlatform elfutils
86 &&
87 # HACK: elfutils is marked as broken on static platforms
88 # which availableOn can't tell.
89 !stdenv.targetPlatform.isStatic
90 && !stdenv.hostPlatform.isStatic,
91 elfutils,
92
93 # Enable NUMA support in RTS
94 enableNuma ? lib.meta.availableOn stdenv.targetPlatform numactl,
95 numactl,
96
97 # What flavour to build. Flavour string may contain a flavour and flavour
98 # transformers as accepted by hadrian.
99 ghcFlavour ?
100 let
101 # TODO(@sternenseemann): does using the static flavour make sense?
102 baseFlavour = "release";
103 # Note: in case hadrian's flavour transformers cease being expressive
104 # enough for us, we'll need to resort to defining a "nixpkgs" flavour
105 # in hadrianUserSettings and using that instead.
106 transformers =
107 lib.optionals useLLVM [ "llvm" ]
108 ++ lib.optionals (!enableShared) [
109 "no_dynamic_libs"
110 "no_dynamic_ghc"
111 ]
112 ++ lib.optionals (!enableProfiledLibs) [ "no_profiled_libs" ]
113 # While split sections are now enabled by default in ghc 8.8 for windows,
114 # they seem to lead to `too many sections` errors when building base for
115 # profiling.
116 ++ (if stdenv.targetPlatform.isWindows then [ "no_split_sections" ] else [ "split_sections" ]);
117 in
118 baseFlavour + lib.concatMapStrings (t: "+${t}") transformers,
119
120 # Contents of the UserSettings.hs file to use when compiling hadrian.
121 hadrianUserSettings ? ''
122 module UserSettings (
123 userFlavours, userPackages, userDefaultFlavour,
124 verboseCommand, buildProgressColour, successColour, finalStage
125 ) where
126
127 import Flavour.Type
128 import Expression
129 import {-# SOURCE #-} Settings.Default
130
131 -- no way to set this via the command line
132 finalStage :: Stage
133 finalStage = ${
134 # Always build the stage 2 compiler if possible.
135 # TODO(@sternensemann): unify condition with make-built GHCs
136 if stdenv.hostPlatform.canExecute stdenv.targetPlatform then
137 "Stage2" # native compiler or “native” cross e.g. pkgsStatic
138 else
139 "Stage1" # cross compiler
140 }
141
142 userDefaultFlavour :: String
143 userDefaultFlavour = "release"
144
145 userFlavours :: [Flavour]
146 userFlavours = []
147
148 -- Disable Colours
149 buildProgressColour :: BuildProgressColour
150 buildProgressColour = mkBuildProgressColour (Dull Reset)
151 successColour :: SuccessColour
152 successColour = mkSuccessColour (Dull Reset)
153
154 -- taken from src/UserSettings.hs unchanged, need to be there
155 userPackages :: [Package]
156 userPackages = []
157 verboseCommand :: Predicate
158 verboseCommand = do
159 verbosity <- expr getVerbosity
160 return $ verbosity >= Verbose
161 '',
162
163 ghcSrc ? srcOnly {
164 name = "ghc-${version}"; # -source appended by srcOnly
165 src = (if rev != null then fetchgit else fetchurl) (
166 {
167 inherit url sha256;
168 }
169 // lib.optionalAttrs (rev != null) {
170 inherit rev;
171 }
172 // lib.optionalAttrs (postFetch != null) {
173 inherit postFetch;
174 }
175 );
176
177 patches =
178 let
179 enableHyperlinkedSource =
180 # Disable haddock generating pretty source listings to stay under 3GB on aarch64-linux
181 !(stdenv.hostPlatform.isAarch64 && stdenv.hostPlatform.isLinux)
182 # 9.8 and 9.10 don't run into this problem for some reason
183 || (lib.versionAtLeast version "9.8" && lib.versionOlder version "9.11");
184 in
185
186 # Fix docs build with Sphinx >= 7 https://gitlab.haskell.org/ghc/ghc/-/issues/24129
187 lib.optionals (lib.versionOlder version "9.6.7") [
188 ./docs-sphinx-7.patch
189 ]
190 ++ lib.optionals (lib.versionAtLeast version "9.6" && lib.versionOlder version "9.6.5") [
191 # Fix aarch64-linux builds of 9.6.0 - 9.6.4.
192 # Fixes a pointer type mismatch in the RTS.
193 # https://gitlab.haskell.org/ghc/ghc/-/issues/24348
194 (fetchpatch {
195 name = "fix-incompatible-pointer-types.patch";
196 url = "https://gitlab.haskell.org/ghc/ghc/-/commit/1e48c43483693398001bfb0ae644a3558bf6a9f3.diff";
197 hash = "sha256-zUlzpX7J1n+MCEv9AWpj69FTy2uzJH8wrQDkTexGbgM=";
198 })
199 ]
200 ++
201 lib.optionals
202 (
203 # 2025-01-16: unix >= 2.8.6.0 is unaffected which is shipped by GHC 9.12.1 and 9.8.4
204 lib.versionOlder version "9.11"
205 && !(lib.versionAtLeast version "9.6.7" && lib.versionOlder version "9.8")
206 && !(lib.versionAtLeast version "9.8.4" && lib.versionOlder version "9.9")
207 && !(lib.versionAtLeast version "9.10.2" && lib.versionOlder version "9.11")
208 )
209 [
210 # Determine size of time related types using hsc2hs instead of assuming CLong.
211 # Prevents failures when e.g. stat(2)ing on 32bit systems with 64bit time_t etc.
212 # https://github.com/haskell/ghcup-hs/issues/1107
213 # https://gitlab.haskell.org/ghc/ghc/-/issues/25095
214 # Note that in normal situations this shouldn't be the case since nixpkgs
215 # doesn't set -D_FILE_OFFSET_BITS=64 and friends (yet).
216 (fetchpatch {
217 name = "unix-fix-ctimeval-size-32-bit.patch";
218 url = "https://github.com/haskell/unix/commit/8183e05b97ce870dd6582a3677cc82459ae566ec.patch";
219 sha256 = "17q5yyigqr5kxlwwzb95sx567ysfxlw6bp3j4ji20lz0947aw6gv";
220 stripLen = 1;
221 extraPrefix = "libraries/unix/";
222 })
223 ]
224 ++ lib.optionals (lib.versionAtLeast version "9.6" && lib.versionOlder version "9.6.6") [
225 (fetchpatch {
226 name = "fix-fully_static.patch";
227 url = "https://gitlab.haskell.org/ghc/ghc/-/commit/1bb24432ff77e11a0340a7d8586e151e15bba2a1.diff";
228 hash = "sha256-MpvTmFFsNiPDoOp9BhZyWeapeibQ77zgEV+xzZ1UAXs=";
229 })
230 ]
231 ++ lib.optionals (lib.versionAtLeast version "9.6" && lib.versionOlder version "9.8") [
232 # Fix unlit being installed under a different name than is used in the
233 # settings file: https://gitlab.haskell.org/ghc/ghc/-/issues/23317
234 (fetchpatch {
235 name = "ghc-9.6-fix-unlit-path.patch";
236 url = "https://gitlab.haskell.org/ghc/ghc/-/commit/8fde4ac84ec7b1ead238cb158bbef48555d12af9.patch";
237 hash = "sha256-3+CyRBpebEZi8YpS22SsdGQHqi0drR7cCKPtKbR3zyE=";
238 })
239 ]
240 ++ lib.optionals (stdenv.targetPlatform.isDarwin && stdenv.targetPlatform.isAarch64) [
241 # Prevent the paths module from emitting symbols that we don't use
242 # when building with separate outputs.
243 #
244 # These cause problems as they're not eliminated by GHC's dead code
245 # elimination on aarch64-darwin. (see
246 # https://github.com/NixOS/nixpkgs/issues/140774 for details).
247 (
248 if lib.versionOlder version "9.10" then
249 ./Cabal-at-least-3.6-paths-fix-cycle-aarch64-darwin.patch
250 else
251 ./Cabal-3.12-paths-fix-cycle-aarch64-darwin.patch
252 )
253 ]
254 ++ lib.optionals stdenv.targetPlatform.isWindows [
255 # https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13919
256 (fetchpatch {
257 name = "include-modern-utimbuf.patch";
258 url = "https://gitlab.haskell.org/ghc/ghc/-/commit/7e75928ed0f1c4654de6ddd13d0b00bf4b5c6411.patch";
259 hash = "sha256-sb+AHdkGkCu8MW0xoQIpD5kEc0zYX8udAMDoC+TWc0Q=";
260 })
261 ]
262 # Prevents passing --hyperlinked-source to haddock. Note that this can
263 # be configured via a user defined flavour now. Unfortunately, it is
264 # impossible to import an existing flavour in UserSettings, so patching
265 # the defaults is actually simpler and less maintenance intensive
266 # compared to keeping an entire flavour definition in sync with upstream
267 # manually. See also https://gitlab.haskell.org/ghc/ghc/-/issues/23625
268 ++ lib.optionals (!enableHyperlinkedSource) [
269 (
270 if lib.versionOlder version "9.8" then
271 ../../tools/haskell/hadrian/disable-hyperlinked-source-pre-9.8.patch
272 else
273 ../../tools/haskell/hadrian/disable-hyperlinked-source-extra-args.patch
274 )
275 ]
276 ++ lib.optionals (lib.versionAtLeast version "9.8" && lib.versionOlder version "9.12") [
277 (fetchpatch {
278 name = "enable-ignore-build-platform-mismatch.patch";
279 url = "https://gitlab.haskell.org/ghc/ghc/-/commit/4ee094d46effd06093090fcba70f0a80d2a57e6c.patch";
280 includes = [ "configure.ac" ];
281 hash = "sha256-L3FQvcm9QB59BOiR2g5/HACAufIG08HiT53EIOjj64g=";
282 })
283 ]
284 # Fixes stack overrun in rts which crashes an process whenever
285 # freeHaskellFunPtr is called with nixpkgs' hardening flags.
286 # https://gitlab.haskell.org/ghc/ghc/-/issues/25485
287 # https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13599
288 ++ lib.optionals (lib.versionOlder version "9.13") [
289 (fetchpatch {
290 name = "ghc-rts-adjustor-fix-i386-stack-overrun.patch";
291 url = "https://gitlab.haskell.org/ghc/ghc/-/commit/39bb6e583d64738db51441a556d499aa93a4fc4a.patch";
292 sha256 = "0w5fx413z924bi2irsy1l4xapxxhrq158b5gn6jzrbsmhvmpirs0";
293 })
294 ]
295
296 # Missing ELF symbols
297 ++ lib.optionals stdenv.targetPlatform.isAndroid [
298 ./ghc-define-undefined-elf-st-visibility.patch
299 ];
300
301 stdenv = stdenvNoCC;
302 },
303
304 # GHC's build system hadrian built from the GHC-to-build's source tree
305 # using our bootstrap GHC.
306 hadrian ? import ../../tools/haskell/hadrian/make-hadrian.nix { inherit bootPkgs lib; } {
307 inherit ghcSrc;
308 ghcVersion = version;
309 userSettings = hadrianUserSettings;
310 },
311
312 # Whether to build sphinx documentation.
313 # TODO(@sternenseemann): Hadrian ignores the --docs flag if finalStage = Stage1
314 enableDocs ? (
315 # Docs disabled if we are building on musl because it's a large task to keep
316 # all `sphinx` dependencies building in this environment.
317 !stdenv.buildPlatform.isMusl
318 ),
319
320 # Whether to disable the large address space allocator
321 # necessary fix for iOS: https://www.reddit.com/r/haskell/comments/4ttdz1/building_an_osxi386_to_iosarm64_cross_compiler/d5qvd67/
322 disableLargeAddressSpace ? stdenv.targetPlatform.isiOS,
323
324 # Whether to build an unregisterised version of GHC.
325 # GHC will normally auto-detect whether it can do a registered build, but this
326 # option will force it to do an unregistered build when set to true.
327 # See https://gitlab.haskell.org/ghc/ghc/-/wikis/building/unregisterised
328 enableUnregisterised ? false,
329}:
330
331assert !enableNativeBignum -> gmp != null;
332
333# GHC does not support building when all 3 platforms are different.
334assert stdenv.buildPlatform == stdenv.hostPlatform || stdenv.hostPlatform == stdenv.targetPlatform;
335
336# It is currently impossible to cross-compile GHC with Hadrian.
337assert lib.assertMsg (stdenv.buildPlatform == stdenv.hostPlatform)
338 "GHC >= 9.6 can't be cross-compiled. If you meant to build a GHC cross-compiler, use `buildPackages`.";
339
340let
341 inherit (stdenv) buildPlatform hostPlatform targetPlatform;
342
343 # TODO(@Ericson2314) Make unconditional
344 targetPrefix = lib.optionalString (targetPlatform != hostPlatform) "${targetPlatform.config}-";
345
346 hadrianSettings =
347 # -fexternal-dynamic-refs apparently (because it's not clear from the
348 # documentation) makes the GHC RTS able to load static libraries, which may
349 # be needed for TemplateHaskell. This solution was described in
350 # https://www.tweag.io/blog/2020-09-30-bazel-static-haskell
351 lib.optionals enableRelocatedStaticLibs [
352 "*.*.ghc.*.opts += -fPIC -fexternal-dynamic-refs"
353 ]
354 ++ lib.optionals targetPlatform.useAndroidPrebuilt [
355 "*.*.ghc.c.opts += -optc-std=gnu99"
356 ];
357
358 # Splicer will pull out correct variations
359 libDeps =
360 platform:
361 lib.optional enableTerminfo ncurses
362 ++ lib.optionals (!targetPlatform.isGhcjs) [ libffi ]
363 # Bindist configure script fails w/o elfutils in linker search path
364 # https://gitlab.haskell.org/ghc/ghc/-/issues/22081
365 ++ lib.optional enableDwarf elfutils
366 ++ lib.optional (!enableNativeBignum) gmp
367 ++ lib.optional (
368 platform.libc != "glibc"
369 && !targetPlatform.isWindows
370 && !targetPlatform.isGhcjs
371 && !targetPlatform.useAndroidPrebuilt
372 ) libiconv;
373
374 # TODO(@sternenseemann): is buildTarget LLVM unnecessary?
375 # GHC doesn't seem to have {LLC,OPT}_HOST
376 toolsForTarget = [
377 (
378 if targetPlatform.isGhcjs then
379 pkgsBuildTarget.emscripten
380 else
381 pkgsBuildTarget.targetPackages.stdenv.cc
382 )
383 ]
384 ++ lib.optional useLLVM buildTargetLlvmPackages.llvm;
385
386 buildCC = buildPackages.stdenv.cc;
387 targetCC = builtins.head toolsForTarget;
388 installCC =
389 if targetPlatform.isGhcjs then
390 pkgsHostTarget.emscripten
391 else
392 pkgsHostTarget.targetPackages.stdenv.cc;
393
394 # toolPath calculates the absolute path to the name tool associated with a
395 # given `stdenv.cc` derivation, i.e. it picks the correct derivation to take
396 # the tool from (cc, cc.bintools, cc.bintools.bintools) and adds the correct
397 # subpath of the tool.
398 toolPath =
399 name: cc:
400 let
401 tools =
402 {
403 "cc" = cc;
404 "c++" = cc;
405 as = cc.bintools;
406
407 ar = cc.bintools;
408 ranlib = cc.bintools;
409 nm = cc.bintools;
410 readelf = cc.bintools;
411 objdump = cc.bintools;
412
413 ld = cc.bintools;
414 "ld.gold" = cc.bintools;
415
416 windres = cc.bintools;
417
418 otool = cc.bintools.bintools;
419
420 # GHC needs install_name_tool on all darwin platforms. The same one can
421 # be used on both platforms. It is safe to use with linker-generated
422 # signatures because it will update the signatures automatically after
423 # modifying the target binary.
424 install_name_tool = cc.bintools.bintools;
425
426 # strip on darwin is wrapped to enable deterministic mode.
427 strip =
428 # TODO(@sternenseemann): also use wrapper if linker == "bfd" or "gold"
429 if stdenv.targetPlatform.isDarwin then cc.bintools else cc.bintools.bintools;
430
431 # clang is used as an assembler on darwin with the LLVM backend
432 clang = cc;
433 }
434 .${name};
435 in
436 getToolExe tools name;
437
438 # targetPrefix aware lib.getExe'
439 getToolExe = drv: name: lib.getExe' drv "${drv.targetPrefix or ""}${name}";
440
441 # Use gold either following the default, or to avoid the BFD linker due to some bugs / perf issues.
442 # But we cannot avoid BFD when using musl libc due to https://sourceware.org/bugzilla/show_bug.cgi?id=23856
443 # see #84670 and #49071 for more background.
444 useLdGold =
445 targetPlatform.linker == "gold"
446 || (
447 targetPlatform.linker == "bfd"
448 && (targetCC.bintools.bintools.hasGold or false)
449 && !targetPlatform.isMusl
450 );
451
452 # Makes debugging easier to see which variant is at play in `nix-store -q --tree`.
453 variantSuffix = lib.concatStrings [
454 (lib.optionalString stdenv.hostPlatform.isMusl "-musl")
455 (lib.optionalString enableNativeBignum "-native-bignum")
456 ];
457
458 # These libraries are library dependencies of the standard libraries bundled
459 # by GHC (core libs) users will link their compiled artifacts again. Thus,
460 # they should be taken from targetPackages.
461 #
462 # We need to use pkgsHostTarget if we are cross compiling a native GHC compiler,
463 # though (when native compiling GHC, pkgsHostTarget == targetPackages):
464 #
465 # 1. targetPackages would be empty(-ish) in this situation since we can't
466 # execute cross compiled compilers in order to obtain the libraries
467 # that would be in targetPackages.
468 # 2. pkgsHostTarget is fine to use since hostPlatform == targetPlatform in this
469 # situation.
470 # 3. The core libs used by the final GHC (stage 2) for user artifacts are also
471 # used to build stage 2 GHC itself, i.e. the core libs are both host and
472 # target.
473 targetLibs = {
474 inherit (if hostPlatform != targetPlatform then targetPackages else pkgsHostTarget)
475 elfutils
476 gmp
477 libffi
478 ncurses
479 numactl
480 ;
481 };
482
483 # Our Cabal compiler name
484 haskellCompilerName = "ghc-${version}";
485
486in
487
488stdenv.mkDerivation (
489 {
490 pname = "${targetPrefix}ghc${variantSuffix}";
491 inherit version;
492
493 src = ghcSrc;
494
495 enableParallelBuilding = true;
496
497 postPatch = ''
498 patchShebangs --build .
499 '';
500
501 # GHC needs the locale configured during the Haddock phase.
502 LANG = "en_US.UTF-8";
503
504 # GHC is a bit confused on its cross terminology.
505 # TODO(@sternenseemann): investigate coreutils dependencies and pass absolute paths
506 preConfigure = ''
507 for env in $(env | grep '^TARGET_' | sed -E 's|\+?=.*||'); do
508 export "''${env#TARGET_}=''${!env}"
509 done
510 # No need for absolute paths since these tools only need to work during the build
511 export CC_STAGE0="$CC_FOR_BUILD"
512 export LD_STAGE0="$LD_FOR_BUILD"
513 export AR_STAGE0="$AR_FOR_BUILD"
514
515 # Stage0 (build->build) which builds stage 1
516 export GHC="${bootPkgs.ghc}/bin/ghc"
517 # GHC is a bit confused on its cross terminology, as these would normally be
518 # the *host* tools.
519 export CC="${toolPath "cc" targetCC}"
520 export CXX="${toolPath "c++" targetCC}"
521 # Use gold to work around https://sourceware.org/bugzilla/show_bug.cgi?id=16177
522 export LD="${toolPath "ld${lib.optionalString useLdGold ".gold"}" targetCC}"
523 export AS="${toolPath "as" targetCC}"
524 export AR="${toolPath "ar" targetCC}"
525 export NM="${toolPath "nm" targetCC}"
526 export RANLIB="${toolPath "ranlib" targetCC}"
527 export READELF="${toolPath "readelf" targetCC}"
528 export STRIP="${toolPath "strip" targetCC}"
529 export OBJDUMP="${toolPath "objdump" targetCC}"
530 ''
531 + lib.optionalString (stdenv.targetPlatform.linker == "cctools") ''
532 export OTOOL="${toolPath "otool" targetCC}"
533 export INSTALL_NAME_TOOL="${toolPath "install_name_tool" targetCC}"
534 ''
535 + lib.optionalString useLLVM ''
536 export LLC="${getToolExe buildTargetLlvmPackages.llvm "llc"}"
537 export OPT="${getToolExe buildTargetLlvmPackages.llvm "opt"}"
538 ''
539 # LLVMAS should be a "specific LLVM compatible assembler" which needs to understand
540 # assembly produced by LLVM. The easiest way to be sure is to use clang from the same
541 # version as llc and opt. Note that the naming chosen by GHC is misleading, clang can
542 # be used as an assembler, llvm-as converts IR into machine code.
543 + lib.optionalString (useLLVM && lib.versionAtLeast version "9.10") ''
544 export LLVMAS="${getToolExe buildTargetLlvmPackages.clang "clang"}"
545 ''
546 + lib.optionalString (useLLVM && stdenv.targetPlatform.isDarwin) ''
547 # LLVM backend on Darwin needs clang: https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/codegens.html#llvm-code-generator-fllvm
548 # The executable we specify via $CLANG is used as an assembler (exclusively, it seems, but this isn't
549 # clarified in any user facing documentation). As such, it'll be called on assembly produced by $CC
550 # which usually comes from the darwin stdenv. To prevent a situation where $CLANG doesn't understand
551 # the assembly it is given, we need to make sure that it matches the LLVM version of $CC if possible.
552 # It is unclear (at the time of writing 2024-09-01) whether $CC should match the LLVM version we use
553 # for llc and opt which would require using a custom darwin stdenv for targetCC.
554 # 2025-09-06: The existence of LLVMAS suggests that matching $CC is fine (correct?) here.
555 export CLANG="${
556 if targetCC.isClang then
557 toolPath "clang" targetCC
558 else
559 getToolExe buildTargetLlvmPackages.clang "clang"
560 }"
561 ''
562 + lib.optionalString (stdenv.buildPlatform.libc == "glibc") ''
563 export LOCALE_ARCHIVE="${buildPackages.glibcLocales}/lib/locale/locale-archive"
564 ''
565 + lib.optionalString (!stdenv.hostPlatform.isDarwin) ''
566 export NIX_LDFLAGS+=" -rpath $out/lib/ghc-${version}"
567 ''
568 + lib.optionalString stdenv.hostPlatform.isDarwin ''
569 export NIX_LDFLAGS+=" -no_dtrace_dof"
570
571 # GHC tries the host xattr /usr/bin/xattr by default which fails since it expects python to be 2.7
572 export XATTR=${lib.getBin xattr}/bin/xattr
573 ''
574 # If we are not using release tarballs, some files need to be generated using
575 # the boot script.
576 + lib.optionalString (rev != null) ''
577 echo ${version} > VERSION
578 echo ${rev} > GIT_COMMIT_ID
579 ./boot
580 ''
581 + lib.optionalString targetPlatform.useAndroidPrebuilt ''
582 sed -i -e '5i ,("armv7a-unknown-linux-androideabi", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "cortex-a8", ""))' llvm-targets
583 ''
584 + lib.optionalString targetPlatform.isMusl ''
585 echo "patching llvm-targets for musl targets..."
586 echo "Cloning these existing '*-linux-gnu*' targets:"
587 grep linux-gnu llvm-targets | sed 's/^/ /'
588 echo "(go go gadget sed)"
589 sed -i 's,\(^.*linux-\)gnu\(.*\)$,\0\n\1musl\2,' llvm-targets
590 echo "llvm-targets now contains these '*-linux-musl*' targets:"
591 grep linux-musl llvm-targets | sed 's/^/ /'
592
593 echo "And now patching to preserve '-musleabi' as done with '-gnueabi'"
594 # (aclocal.m4 is actual source, but patch configure as well since we don't re-gen)
595 for x in configure aclocal.m4; do
596 substituteInPlace $x \
597 --replace '*-android*|*-gnueabi*)' \
598 '*-android*|*-gnueabi*|*-musleabi*)'
599 done
600 ''
601 # Need to make writable EM_CACHE for emscripten. The path in EM_CACHE must be absolute.
602 # https://gitlab.haskell.org/ghc/ghc/-/wikis/javascript-backend#configure-fails-with-sub-word-sized-atomic-operations-not-available
603 + lib.optionalString targetPlatform.isGhcjs ''
604 export EM_CACHE="$(realpath $(mktemp -d emcache.XXXXXXXXXX))"
605 cp -Lr ${
606 targetCC # == emscripten
607 }/share/emscripten/cache/* "$EM_CACHE/"
608 chmod u+rwX -R "$EM_CACHE"
609 ''
610 # Create bash array hadrianFlagsArray for use in buildPhase. Do it in
611 # preConfigure, so overrideAttrs can be used to modify it effectively.
612 # hadrianSettings are passed via the command line so they are more visible
613 # in the build log.
614 + ''
615 hadrianFlagsArray=(
616 "-j$NIX_BUILD_CORES"
617 ${lib.escapeShellArgs hadrianSettings}
618 )
619 '';
620
621 ${if targetPlatform.isGhcjs then "configureScript" else null} = "emconfigure ./configure";
622 # GHC currently ships an edited config.sub so ghcjs is accepted which we can not rollback
623 ${if targetPlatform.isGhcjs then "dontUpdateAutotoolsGnuConfigScripts" else null} = true;
624
625 # TODO(@Ericson2314): Always pass "--target" and always prefix.
626 configurePlatforms = [
627 "build"
628 "host"
629 ]
630 ++ lib.optional (targetPlatform != hostPlatform) "target";
631
632 # `--with` flags for libraries needed for RTS linker
633 configureFlags = [
634 "--datadir=$doc/share/doc/ghc"
635 ]
636 ++ lib.optionals enableTerminfo [
637 "--with-curses-includes=${lib.getDev targetLibs.ncurses}/include"
638 "--with-curses-libraries=${lib.getLib targetLibs.ncurses}/lib"
639 ]
640 ++ lib.optionals (libffi != null && !targetPlatform.isGhcjs) [
641 "--with-system-libffi"
642 "--with-ffi-includes=${targetLibs.libffi.dev}/include"
643 "--with-ffi-libraries=${targetLibs.libffi.out}/lib"
644 ]
645 ++ lib.optionals (targetPlatform == hostPlatform && !enableNativeBignum) [
646 "--with-gmp-includes=${targetLibs.gmp.dev}/include"
647 "--with-gmp-libraries=${targetLibs.gmp.out}/lib"
648 ]
649 ++
650 lib.optionals
651 (targetPlatform == hostPlatform && hostPlatform.libc != "glibc" && !targetPlatform.isWindows)
652 [
653 "--with-iconv-includes=${libiconv}/include"
654 "--with-iconv-libraries=${libiconv}/lib"
655 ]
656 ++ lib.optionals (targetPlatform != hostPlatform) [
657 "--enable-bootstrap-with-devel-snapshot"
658 ]
659 ++ lib.optionals useLdGold [
660 "CFLAGS=-fuse-ld=gold"
661 "CONF_GCC_LINKER_OPTS_STAGE1=-fuse-ld=gold"
662 "CONF_GCC_LINKER_OPTS_STAGE2=-fuse-ld=gold"
663 ]
664 ++ lib.optionals (disableLargeAddressSpace) [
665 "--disable-large-address-space"
666 ]
667 ++ lib.optionals enableDwarf [
668 "--enable-dwarf-unwind"
669 "--with-libdw-includes=${lib.getDev targetLibs.elfutils}/include"
670 "--with-libdw-libraries=${lib.getLib targetLibs.elfutils}/lib"
671 ]
672 ++ lib.optionals enableNuma [
673 "--enable-numa"
674 "--with-libnuma-includes=${lib.getDev targetLibs.numactl}/include"
675 "--with-libnuma-libraries=${lib.getLib targetLibs.numactl}/lib"
676 ]
677 ++ lib.optionals targetPlatform.isDarwin [
678 # Darwin uses llvm-ar. GHC will try to use `-L` with `ar` when it is `llvm-ar`
679 # but it doesn’t currently work because Cabal never uses `-L` on Darwin. See:
680 # https://gitlab.haskell.org/ghc/ghc/-/issues/23188
681 # https://github.com/haskell/cabal/issues/8882
682 "fp_cv_prog_ar_supports_dash_l=no"
683 ]
684 ++ lib.optionals enableUnregisterised [
685 "--enable-unregisterised"
686 ]
687 ++
688 lib.optionals
689 (stdenv.buildPlatform.isAarch64 && stdenv.buildPlatform.isMusl && lib.versionOlder version "9.12")
690 [
691 # The bootstrap binaries for aarch64 musl were built for the wrong triple.
692 # https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13182
693 "--enable-ignore-build-platform-mismatch"
694 ];
695
696 # Make sure we never relax`$PATH` and hooks support for compatibility.
697 strictDeps = true;
698
699 # Don’t add -liconv to LDFLAGS automatically so that GHC will add it itself.
700 dontAddExtraLibs = true;
701
702 nativeBuildInputs = [
703 autoreconfHook
704 perl
705 hadrian
706 bootPkgs.alex
707 bootPkgs.happy
708 bootPkgs.hscolour
709 # Python is used in a few scripts invoked by hadrian to generate e.g. rts headers.
710 python3
711 # Tool used to update GHC's settings file in postInstall
712 bootPkgs.ghc-settings-edit
713 ]
714 ++ lib.optionals (stdenv.hostPlatform.isDarwin && stdenv.hostPlatform.isAarch64) [
715 autoSignDarwinBinariesHook
716 ]
717 ++ lib.optionals enableDocs [
718 sphinx
719 ];
720
721 # For building runtime libs
722 depsBuildTarget = toolsForTarget;
723 # Everything the stage0 compiler needs to build stage1: CC, bintools, extra libs.
724 # See also GHC, {CC,LD,AR}_STAGE0 in preConfigure.
725 depsBuildBuild = [
726 # N.B. We do not declare bootPkgs.ghc in any of the stdenv.mkDerivation
727 # dependency lists to prevent the bintools setup hook from adding ghc's
728 # lib directory to the linker flags. Instead we tell configure about it
729 # via the GHC environment variable.
730 buildCC
731 # stage0 builds terminfo unconditionally, so we always need ncurses
732 ncurses
733 ];
734
735 # Prevent stage0 ghc from leaking into the final result. This was an issue
736 # with GHC 9.6.
737 disallowedReferences = [
738 bootPkgs.ghc
739 ];
740
741 buildInputs = [ bash ] ++ (libDeps hostPlatform);
742
743 # stage0:ghc (i.e. stage1) doesn't need to link against libnuma, so it's target specific
744 depsTargetTarget = map lib.getDev (
745 libDeps targetPlatform ++ lib.optionals enableNuma [ targetLibs.numactl ]
746 );
747 depsTargetTargetPropagated = map (lib.getOutput "out") (
748 libDeps targetPlatform ++ lib.optionals enableNuma [ targetLibs.numactl ]
749 );
750
751 hadrianFlags = [
752 "--flavour=${ghcFlavour}"
753 "--bignum=${if enableNativeBignum then "native" else "gmp"}"
754 "--docs=${if enableDocs then "no-sphinx-pdfs" else "no-sphinx"}"
755 ]
756 ++ lib.optionals (lib.versionAtLeast version "9.8") [
757 # In 9.14 this will be default with release flavour.
758 # See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13444
759 "--hash-unit-ids"
760 ];
761
762 buildPhase = ''
763 runHook preBuild
764
765 # hadrianFlagsArray is created in preConfigure
766 echo "hadrianFlags: $hadrianFlags ''${hadrianFlagsArray[@]}"
767
768 # We need to go via the bindist for installing
769 hadrian $hadrianFlags "''${hadrianFlagsArray[@]}" binary-dist-dir
770
771 runHook postBuild
772 '';
773
774 # required, because otherwise all symbols from HSffi.o are stripped, and
775 # that in turn causes GHCi to abort
776 stripDebugFlags = [ "-S" ] ++ lib.optional (!targetPlatform.isDarwin) "--keep-file-symbols";
777
778 checkTarget = "test";
779
780 # GHC cannot currently produce outputs that are ready for `-pie` linking.
781 # Thus, disable `pie` hardening, otherwise `recompile with -fPIE` errors appear.
782 # See:
783 # * https://github.com/NixOS/nixpkgs/issues/129247
784 # * https://gitlab.haskell.org/ghc/ghc/-/issues/19580
785 hardeningDisable = [
786 "format"
787 "pie"
788 ];
789
790 # big-parallel allows us to build with more than 2 cores on
791 # Hydra which already warrants a significant speedup
792 requiredSystemFeatures = [ "big-parallel" ];
793
794 outputs = [
795 "out"
796 "doc"
797 ];
798
799 # We need to configure the bindist *again* before installing
800 # https://gitlab.haskell.org/ghc/ghc/-/issues/22058
801 # TODO(@sternenseemann): it would be nice if the bindist could be an intermediate
802 # derivation, but since it is > 2GB even on x86_64-linux, not a good idea?
803 preInstall = ''
804 pushd _build/bindist/*
805
806 ''
807 # the bindist configure script uses different env variables than the GHC configure script
808 # see https://github.com/NixOS/nixpkgs/issues/267250 and https://gitlab.haskell.org/ghc/ghc/-/issues/24211
809 + lib.optionalString (stdenv.targetPlatform.linker == "cctools") ''
810 export InstallNameToolCmd=$INSTALL_NAME_TOOL
811 export OtoolCmd=$OTOOL
812 ''
813 + ''
814 $configureScript $configureFlags "''${configureFlagsArray[@]}"
815 '';
816
817 postInstall = ''
818 # leave bindist directory
819 popd
820
821 settingsFile="$out/lib/${targetPrefix}${haskellCompilerName}/lib/settings"
822
823 # Make the installed GHC use the host->target tools.
824 ghc-settings-edit "$settingsFile" \
825 "C compiler command" "${toolPath "cc" installCC}" \
826 "Haskell CPP command" "${toolPath "cc" installCC}" \
827 "C++ compiler command" "${toolPath "c++" installCC}" \
828 "ld command" "${toolPath "ld${lib.optionalString useLdGold ".gold"}" installCC}" \
829 "Merge objects command" "${toolPath "ld${lib.optionalString useLdGold ".gold"}" installCC}" \
830 "ar command" "${toolPath "ar" installCC}" \
831 "ranlib command" "${toolPath "ranlib" installCC}"
832 ''
833 + lib.optionalString (stdenv.targetPlatform.linker == "cctools") ''
834 ghc-settings-edit "$settingsFile" \
835 "otool command" "${toolPath "otool" installCC}" \
836 "install_name_tool command" "${toolPath "install_name_tool" installCC}"
837 ''
838 + lib.optionalString useLLVM ''
839 ghc-settings-edit "$settingsFile" \
840 "LLVM llc command" "${getToolExe llvmPackages.llvm "llc"}" \
841 "LLVM opt command" "${getToolExe llvmPackages.llvm "opt"}"
842 ''
843 # See comment for LLVMAS in preConfigure
844 + lib.optionalString (useLLVM && lib.versionAtLeast version "9.10") ''
845 ghc-settings-edit "$settingsFile" \
846 "LLVM llvm-as command" "${getToolExe llvmPackages.clang "clang"}"
847 ''
848 + lib.optionalString (useLLVM && stdenv.targetPlatform.isDarwin) ''
849 ghc-settings-edit "$settingsFile" \
850 "LLVM clang command" "${
851 # See comment for CLANG in preConfigure
852 if installCC.isClang then toolPath "clang" installCC else getToolExe llvmPackages.clang "clang"
853 }"
854 ''
855 + lib.optionalString stdenv.targetPlatform.isWindows ''
856 ghc-settings-edit "$settingsFile" \
857 "windres command" "${toolPath "windres" installCC}"
858 ''
859 + ''
860
861 # Install the bash completion file.
862 install -Dm 644 utils/completion/ghc.bash $out/share/bash-completion/completions/${targetPrefix}ghc
863 '';
864
865 passthru = {
866 inherit bootPkgs targetPrefix haskellCompilerName;
867
868 inherit llvmPackages;
869 inherit enableShared;
870
871 # Expose hadrian used for bootstrapping, for debugging purposes
872 inherit hadrian;
873
874 # TODO(@sternenseemann): there's no stage0:exe:haddock target by default,
875 # so haddock isn't available for GHC cross-compilers. Can we fix that?
876 hasHaddock = stdenv.hostPlatform == stdenv.targetPlatform;
877
878 bootstrapAvailable = lib.meta.availableOn stdenv.buildPlatform bootPkgs.ghc;
879 };
880
881 meta = {
882 homepage = "http://haskell.org/ghc";
883 description = "Glasgow Haskell Compiler";
884 maintainers = with lib.maintainers; [
885 guibou
886 ];
887 teams = [ lib.teams.haskell ];
888 timeout = 24 * 3600;
889 platforms = lib.platforms.all;
890 inherit (bootPkgs.ghc.meta) license;
891 # To be fixed by <https://github.com/NixOS/nixpkgs/pull/440774>.
892 broken = useLLVM;
893 };
894
895 dontStrip = targetPlatform.useAndroidPrebuilt || targetPlatform.isWasm;
896 }
897 // lib.optionalAttrs targetPlatform.useAndroidPrebuilt {
898 dontPatchELF = true;
899 noAuditTmpdir = true;
900 }
901)