Cheng Shao pushed to branch wip/fast-binary at Glasgow Haskell Compiler / GHC
Commits:
ec3cf767 by Cheng Shao at 2026-01-08T06:24:31-05:00
make: remove unused Makefiles from legacy make build system
This patch removes unused Makefiles from legacy make build system; now
they are never used by hadrian in any way, and they already include
common boilerplate mk files that are long gone in the make build
system removal, hence the housecleaning.
Co-authored-by: Codex
- - - - -
04ea3f83 by Cheng Shao at 2026-01-08T06:25:13-05:00
compiler: use -O3 as LLVM optimization level for ghc -O2
The GHC driver clamps LLVM optimization level to `-O2` due to LLVM
crashes, but those were historical issues many years ago that are no
longer relevant for LLVM versions we support today. This patch changes
the driver to use `-O3` as LLVM optimization level when compiling with
`-O2`, which is a better default when we're willing to trade
compilation time for faster generated code.
- - - - -
ba9fc0c2 by Cheng Shao at 2026-01-08T18:50:57+01:00
compiler: make getPrim eagerly evaluate its result
This commit makes `GHC.Utils.Binary.getPrim` eagerly evaluate its
result, to avoid accidental laziness when future patches build other
binary parsers using `getPrim`.
- - - - -
7b62e2d8 by Cheng Shao at 2026-01-08T18:50:57+01:00
compiler: implement fast get/put for Word16/Word32/Word64
Previously, `GHC.Utils.Binary` contains `get`/`put` functions for
`Word16`/`Word32`/`Word64` which always loads and stores them as
big-endian words at a potentially unaligned address. The previous
implementation is based on loads/stores of individual bytes and
concatenating bytes with bitwise operations, which currently cannot be
fused to a single load/store operation by GHC.
This patch implements fast `get`/`put` functions for
`Word16`/`Word32`/`Word64` based on a single memory load/store, with
an additional `byteSwap` operation on little-endian hosts. It is based
on unaligned load/store primops added since GHC 9.10, and we already
require booting with at least 9.10, so it's about time to switch to
this faster path.
- - - - -
18 changed files:
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Utils/Binary.hs
- − docs/Makefile
- − docs/storage-mgt/Makefile
- − docs/users_guide/Makefile
- − driver/Makefile
- − driver/ghc/Makefile
- − driver/ghci/Makefile
- − driver/haddock/Makefile
- − ghc/Makefile
- − libraries/Makefile
- − libraries/doc/Makefile
- − linters/lint-codes/Makefile
- − linters/lint-notes/Makefile
- llvm-passes
- − rts/Makefile
- − rts/include/Makefile
Changes:
=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -181,52 +181,13 @@ runMergeForeign _pipe_env hsc_env input_fn foreign_os = do
runLlvmLlcPhase :: PipeEnv -> HscEnv -> FilePath -> IO FilePath
runLlvmLlcPhase pipe_env hsc_env input_fn = do
- -- Note [Clamping of llc optimizations]
- -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
- -- See #13724
- --
- -- we clamp the llc optimization between [1,2]. This is because passing -O0
- -- to llc 3.9 or llc 4.0, the naive register allocator can fail with
- --
- -- Error while trying to spill R1 from class GPR: Cannot scavenge register
- -- without an emergency spill slot!
- --
- -- Observed at least with target 'arm-unknown-linux-gnueabihf'.
- --
- --
- -- With LLVM4, llc -O3 crashes when ghc-stage1 tries to compile
- -- rts/HeapStackCheck.cmm
- --
- -- llc -O3 '-mtriple=arm-unknown-linux-gnueabihf' -enable-tbaa /var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_6.bc -o /var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_7.lm_s
- -- 0 llc 0x0000000102ae63e8 llvm::sys::PrintStackTrace(llvm::raw_ostream&) + 40
- -- 1 llc 0x0000000102ae69a6 SignalHandler(int) + 358
- -- 2 libsystem_platform.dylib 0x00007fffc23f4b3a _sigtramp + 26
- -- 3 libsystem_c.dylib 0x00007fffc226498b __vfprintf + 17876
- -- 4 llc 0x00000001029d5123 llvm::SelectionDAGISel::LowerArguments(llvm::Function const&) + 5699
- -- 5 llc 0x0000000102a21a35 llvm::SelectionDAGISel::SelectAllBasicBlocks(llvm::Function const&) + 3381
- -- 6 llc 0x0000000102a202b1 llvm::SelectionDAGISel::runOnMachineFunction(llvm::MachineFunction&) + 1457
- -- 7 llc 0x0000000101bdc474 (anonymous namespace)::ARMDAGToDAGISel::runOnMachineFunction(llvm::MachineFunction&) + 20
- -- 8 llc 0x00000001025573a6 llvm::MachineFunctionPass::runOnFunction(llvm::Function&) + 134
- -- 9 llc 0x000000010274fb12 llvm::FPPassManager::runOnFunction(llvm::Function&) + 498
- -- 10 llc 0x000000010274fd23 llvm::FPPassManager::runOnModule(llvm::Module&) + 67
- -- 11 llc 0x00000001027501b8 llvm::legacy::PassManagerImpl::run(llvm::Module&) + 920
- -- 12 llc 0x000000010195f075 compileModule(char**, llvm::LLVMContext&) + 12133
- -- 13 llc 0x000000010195bf0b main + 491
- -- 14 libdyld.dylib 0x00007fffc21e5235 start + 1
- -- Stack dump:
- -- 0. Program arguments: llc -O3 -mtriple=arm-unknown-linux-gnueabihf -enable-tbaa /var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_6.bc -o /var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_7.lm_s
- -- 1. Running pass 'Function Pass Manager' on module '/var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_6.bc'.
- -- 2. Running pass 'ARM Instruction Selection' on function '@"stg_gc_f1$def"'
- --
- -- Observed at least with -mtriple=arm-unknown-linux-gnueabihf -enable-tbaa
- --
llvm_config <- readLlvmConfigCache (hsc_llvm_config hsc_env)
let dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
llvmOpts = case llvmOptLevel dflags of
0 -> "-O1" -- required to get the non-naive reg allocator. Passing -regalloc=greedy is not sufficient.
1 -> "-O1"
- _ -> "-O2"
+ _ -> "-O3"
llvm_version <- figureLlvmVersion logger dflags
let defaultOptions = map GHC.SysTools.Option . concatMap words . snd
@@ -259,7 +220,7 @@ runLlvmOptPhase pipe_env hsc_env input_fn = do
llvm_config <- readLlvmConfigCache (hsc_llvm_config hsc_env)
let -- we always (unless -optlo specified) run Opt since we rely on it to
-- fix up some pretty big deficiencies in the code we generate
- optIdx = max 0 $ min 2 $ llvmOptLevel dflags -- ensure we're in [0,2]
+ optIdx = max 0 $ min 3 $ llvmOptLevel dflags -- ensure we're in [0,3]
llvmOpts = case lookup optIdx $ llvmPasses llvm_config of
Just passes -> passes
Nothing -> panic ("runPhase LlvmOpt: llvm-passes file "
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -798,8 +798,11 @@ updOptLevelChanged n dfs
| not (gopt f dfs) = (dfs, changed)
| otherwise = (gopt_unset dfs f, True)
+ -- Use -O3 for llc/opt when we are compiling with -O2
+ llvm_n = if final_n == 2 then 3 else final_n
+
setLlvmOptLevel dfs
- | llvmOptLevel dfs /= final_n = (dfs{ llvmOptLevel = final_n }, True)
+ | llvmOptLevel dfs /= llvm_n = (dfs{ llvmOptLevel = llvm_n }, True)
| otherwise = (dfs, False)
updOptLevel :: Int -> DynFlags -> DynFlags
=====================================
compiler/GHC/Utils/Binary.hs
=====================================
@@ -1,4 +1,5 @@
{-# LANGUAGE CPP #-}
+{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE DerivingVia #-}
@@ -160,14 +161,17 @@ import qualified Data.Set as Set
import Data.Time
import Data.List (unfoldr)
import System.IO as IO
-import System.IO.Unsafe ( unsafeInterleaveIO )
import System.IO.Error ( mkIOError, eofErrorType )
import Type.Reflection ( Typeable, SomeTypeRep(..) )
import qualified Type.Reflection as Refl
import GHC.Real ( Ratio(..) )
import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
+import GHC.ByteOrder
import GHC.ForeignPtr ( unsafeWithForeignPtr )
+import GHC.Exts
+import GHC.IO
+import GHC.Word
import Unsafe.Coerce (unsafeCoerce)
@@ -638,7 +642,7 @@ getPrim (ReadBinMem _ ix_r sz_r arr_r) size f = do
ix <- readFastMutInt ix_r
when (ix + size > sz_r) $
ioError (mkIOError eofErrorType "Data.Binary.getPrim" Nothing Nothing)
- w <- unsafeWithForeignPtr arr_r $ \p -> f (p `plusPtr` ix)
+ !w <- unsafeWithForeignPtr arr_r $ \p -> f (p `plusPtr` ix)
-- This is safe WRT #17760 as we we guarantee that the above line doesn't
-- diverge
writeFastMutInt ix_r (ix + size)
@@ -651,71 +655,52 @@ getWord8 :: ReadBinHandle -> IO Word8
getWord8 h = getPrim h 1 peek
putWord16 :: WriteBinHandle -> Word16 -> IO ()
-putWord16 h w = putPrim h 2 (\op -> do
- pokeElemOff op 0 (fromIntegral (w `shiftR` 8))
- pokeElemOff op 1 (fromIntegral (w .&. 0xFF))
- )
+putWord16 h w = putPrim h 2 $ \(Ptr p#) ->
+ IO $ \s -> (# writeWord8OffAddrAsWord16# p# 0# x# s, () #)
+ where
+ !(W16# x#) = case targetByteOrder of
+ BigEndian -> w
+ LittleEndian -> byteSwap16 w
getWord16 :: ReadBinHandle -> IO Word16
-getWord16 h = getPrim h 2 (\op -> do
- w0 <- fromIntegral <$> peekElemOff op 0
- w1 <- fromIntegral <$> peekElemOff op 1
- return $! w0 `shiftL` 8 .|. w1
- )
+getWord16 h = getPrim h 2 $ \(Ptr p#) ->
+ IO $ \s -> case readWord8OffAddrAsWord16# p# 0# s of
+ (# s', w16# #) -> case targetByteOrder of
+ BigEndian -> (# s', W16# w16# #)
+ LittleEndian -> case byteSwap16 $ W16# w16# of
+ !w16 -> (# s', w16 #)
putWord32 :: WriteBinHandle -> Word32 -> IO ()
-putWord32 h w = putPrim h 4 (\op -> do
- pokeElemOff op 0 (fromIntegral (w `shiftR` 24))
- pokeElemOff op 1 (fromIntegral ((w `shiftR` 16) .&. 0xFF))
- pokeElemOff op 2 (fromIntegral ((w `shiftR` 8) .&. 0xFF))
- pokeElemOff op 3 (fromIntegral (w .&. 0xFF))
- )
+putWord32 h w = putPrim h 4 $ \(Ptr p#) ->
+ IO $ \s -> (# writeWord8OffAddrAsWord32# p# 0# x# s, () #)
+ where
+ !(W32# x#) = case targetByteOrder of
+ BigEndian -> w
+ LittleEndian -> byteSwap32 w
getWord32 :: ReadBinHandle -> IO Word32
-getWord32 h = getPrim h 4 (\op -> do
- w0 <- fromIntegral <$> peekElemOff op 0
- w1 <- fromIntegral <$> peekElemOff op 1
- w2 <- fromIntegral <$> peekElemOff op 2
- w3 <- fromIntegral <$> peekElemOff op 3
-
- return $! (w0 `shiftL` 24) .|.
- (w1 `shiftL` 16) .|.
- (w2 `shiftL` 8) .|.
- w3
- )
+getWord32 h = getPrim h 4 $ \(Ptr p#) ->
+ IO $ \s -> case readWord8OffAddrAsWord32# p# 0# s of
+ (# s', w32# #) -> case targetByteOrder of
+ BigEndian -> (# s', W32# w32# #)
+ LittleEndian -> case byteSwap32 $ W32# w32# of
+ !w32 -> (# s', w32 #)
putWord64 :: WriteBinHandle -> Word64 -> IO ()
-putWord64 h w = putPrim h 8 (\op -> do
- pokeElemOff op 0 (fromIntegral (w `shiftR` 56))
- pokeElemOff op 1 (fromIntegral ((w `shiftR` 48) .&. 0xFF))
- pokeElemOff op 2 (fromIntegral ((w `shiftR` 40) .&. 0xFF))
- pokeElemOff op 3 (fromIntegral ((w `shiftR` 32) .&. 0xFF))
- pokeElemOff op 4 (fromIntegral ((w `shiftR` 24) .&. 0xFF))
- pokeElemOff op 5 (fromIntegral ((w `shiftR` 16) .&. 0xFF))
- pokeElemOff op 6 (fromIntegral ((w `shiftR` 8) .&. 0xFF))
- pokeElemOff op 7 (fromIntegral (w .&. 0xFF))
- )
+putWord64 h w = putPrim h 8 $ \(Ptr p#) ->
+ IO $ \s -> (# writeWord8OffAddrAsWord64# p# 0# x# s, () #)
+ where
+ !(W64# x#) = case targetByteOrder of
+ BigEndian -> w
+ LittleEndian -> byteSwap64 w
getWord64 :: ReadBinHandle -> IO Word64
-getWord64 h = getPrim h 8 (\op -> do
- w0 <- fromIntegral <$> peekElemOff op 0
- w1 <- fromIntegral <$> peekElemOff op 1
- w2 <- fromIntegral <$> peekElemOff op 2
- w3 <- fromIntegral <$> peekElemOff op 3
- w4 <- fromIntegral <$> peekElemOff op 4
- w5 <- fromIntegral <$> peekElemOff op 5
- w6 <- fromIntegral <$> peekElemOff op 6
- w7 <- fromIntegral <$> peekElemOff op 7
-
- return $! (w0 `shiftL` 56) .|.
- (w1 `shiftL` 48) .|.
- (w2 `shiftL` 40) .|.
- (w3 `shiftL` 32) .|.
- (w4 `shiftL` 24) .|.
- (w5 `shiftL` 16) .|.
- (w6 `shiftL` 8) .|.
- w7
- )
+getWord64 h = getPrim h 8 $ \(Ptr p#) ->
+ IO $ \s -> case readWord8OffAddrAsWord64# p# 0# s of
+ (# s', w64# #) -> case targetByteOrder of
+ BigEndian -> (# s', W64# w64# #)
+ LittleEndian -> case byteSwap64 $ W64# w64# of
+ !w64 -> (# s', w64 #)
putByte :: WriteBinHandle -> Word8 -> IO ()
putByte bh !w = putWord8 bh w
=====================================
docs/Makefile deleted
=====================================
@@ -1,4 +0,0 @@
-dir = docs
-TOP = ..
-include $(TOP)/mk/sub-makefile.mk
-
=====================================
docs/storage-mgt/Makefile deleted
=====================================
@@ -1,42 +0,0 @@
-TOP = ../..
-include $(TOP)/mk/boilerplate.mk
-
-# General makefile for Latex stuff
-
-dvi: sm.dvi rp.dvi ldv.dvi
-ps: sm.ps rp.ps ldv.ps
-
-######## General rules
-.SUFFIXES:
-.PRECIOUS: %.tex %.ps %.bbl
-
-#%.dvi: %.tex $(addsuffix .tex, $(basename $(wildcard *.verb *.fig))) $(wildcard *.bib)
-%.dvi: %.tex $(addsuffix .tex, $(basename $(wildcard *.verb))) $(wildcard *.bib)
- latex $<
- @if grep -s "\citation" $*.aux; then bibtex $*; fi
- latex $<
- latex $<
-
-%.ps: %.dvi
- dvips -f < $< > $@
-
-clean:
- $(RM) *.aux *.log
-
-distclean: clean
- $(RM) *.dvi *.ps *.bbl *.blg *.gz
-
-maintainer-clean: distclean
-
-include $(TOP)/mk/bindist.mk
-
-# dummy targets
-all:
-boot:
-install:
-install-docs:
-html:
-chm:
-HxS:
-
-# End of file
=====================================
docs/users_guide/Makefile deleted
=====================================
@@ -1,4 +0,0 @@
-dir = docs/users_guide
-TOP = ../..
-
-include $(TOP)/mk/sub-makefile.mk
=====================================
driver/Makefile deleted
=====================================
@@ -1,15 +0,0 @@
-# -----------------------------------------------------------------------------
-#
-# (c) 2009 The University of Glasgow
-#
-# This file is part of the GHC build system.
-#
-# To understand how the build system works and how to modify it, see
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
-#
-# -----------------------------------------------------------------------------
-
-dir = driver
-TOP = ..
-include $(TOP)/mk/sub-makefile.mk
=====================================
driver/ghc/Makefile deleted
=====================================
@@ -1,3 +0,0 @@
-dir=driver/ghc
-TOP=../..
-include $(TOP)/mk/sub-makefile.mk
=====================================
driver/ghci/Makefile deleted
=====================================
@@ -1,15 +0,0 @@
-# -----------------------------------------------------------------------------
-#
-# (c) 2009 The University of Glasgow
-#
-# This file is part of the GHC build system.
-#
-# To understand how the build system works and how to modify it, see
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
-#
-# -----------------------------------------------------------------------------
-
-dir = driver/ghci
-TOP = ../..
-include $(TOP)/mk/sub-makefile.mk
=====================================
driver/haddock/Makefile deleted
=====================================
@@ -1,3 +0,0 @@
-dir=driver/haddock
-TOP=../..
-include $(TOP)/mk/sub-makefile.mk
=====================================
ghc/Makefile deleted
=====================================
@@ -1,16 +0,0 @@
-# -----------------------------------------------------------------------------
-#
-# (c) 2009 The University of Glasgow
-#
-# This file is part of the GHC build system.
-#
-# To understand how the build system works and how to modify it, see
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
-#
-# -----------------------------------------------------------------------------
-
-dir = ghc
-
-include ../mk/compiler-ghc.mk
-
=====================================
libraries/Makefile deleted
=====================================
@@ -1,16 +0,0 @@
-dir = libraries
-TOP = ..
-SPEC_TARGETS = 1
-include $(TOP)/mk/sub-makefile.mk
-
-.PHONY: 1
-1 :
- +$(TOPMAKE) stage1_libs
-
-.PHONY: extra-help
-help : extra-help
-extra-help :
- @echo " make 1"
- @echo
- @echo " Build all libraries that are built by the stage1 GHC"
- @echo
=====================================
libraries/doc/Makefile deleted
=====================================
@@ -1,4 +0,0 @@
-TOP=..
-include $(TOP)/mk/boilerplate.mk
-XML_DOC=libraries
-include $(TOP)/mk/target.mk
=====================================
linters/lint-codes/Makefile deleted
=====================================
@@ -1,15 +0,0 @@
-# -----------------------------------------------------------------------------
-#
-# (c) 2009 The University of Glasgow
-#
-# This file is part of the GHC build system.
-#
-# To understand how the build system works and how to modify it, see
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
-#
-# -----------------------------------------------------------------------------
-
-dir = linters/lint-codes
-TOP = ../..
-include $(TOP)/mk/sub-makefile.mk
=====================================
linters/lint-notes/Makefile deleted
=====================================
@@ -1,17 +0,0 @@
-# -----------------------------------------------------------------------------
-#
-# (c) 2009 The University of Glasgow
-#
-# This file is part of the GHC build system.
-#
-# To understand how the build system works and how to modify it, see
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
-#
-# -----------------------------------------------------------------------------
-
-dir = linters/lint-notes
-TOP = ../..
-include $(TOP)/mk/sub-makefile.mk
-
-FAST_MAKE_OPTS += stage=none
=====================================
llvm-passes
=====================================
@@ -1,5 +1,6 @@
[
(0, "-passes=function(require<tbaa>),function(mem2reg),globalopt,function(lower-expect)"),
(1, "-passes=default<O1>"),
-(2, "-passes=default<O2>")
+(2, "-passes=default<O2>"),
+(3, "-passes=default<O3>")
]
=====================================
rts/Makefile deleted
=====================================
@@ -1,17 +0,0 @@
-# -----------------------------------------------------------------------------
-#
-# (c) 2009 The University of Glasgow
-#
-# This file is part of the GHC build system.
-#
-# To understand how the build system works and how to modify it, see
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
-#
-# -----------------------------------------------------------------------------
-
-dir = rts
-TOP = ..
-include $(TOP)/mk/sub-makefile.mk
-
-FAST_MAKE_OPTS += stage=none
=====================================
rts/include/Makefile deleted
=====================================
@@ -1,15 +0,0 @@
-# -----------------------------------------------------------------------------
-#
-# (c) 2009 The University of Glasgow
-#
-# This file is part of the GHC build system.
-#
-# To understand how the build system works and how to modify it, see
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
-# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
-#
-# -----------------------------------------------------------------------------
-
-dir = rts/include
-TOP = ../..
-include $(TOP)/mk/sub-makefile.mk
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/311361012c8cb15223b5075cf89167d...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/311361012c8cb15223b5075cf89167d...
You're receiving this email because of your account on gitlab.haskell.org.