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
-
04ea3f83
by Cheng Shao at 2026-01-08T06:25:13-05:00
-
ba9fc0c2
by Cheng Shao at 2026-01-08T18:50:57+01:00
-
7b62e2d8
by Cheng Shao at 2026-01-08T18:50:57+01:00
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:
| ... | ... | @@ -181,52 +181,13 @@ runMergeForeign _pipe_env hsc_env input_fn foreign_os = do |
| 181 | 181 | |
| 182 | 182 | runLlvmLlcPhase :: PipeEnv -> HscEnv -> FilePath -> IO FilePath
|
| 183 | 183 | runLlvmLlcPhase pipe_env hsc_env input_fn = do
|
| 184 | - -- Note [Clamping of llc optimizations]
|
|
| 185 | - -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
| 186 | - -- See #13724
|
|
| 187 | - --
|
|
| 188 | - -- we clamp the llc optimization between [1,2]. This is because passing -O0
|
|
| 189 | - -- to llc 3.9 or llc 4.0, the naive register allocator can fail with
|
|
| 190 | - --
|
|
| 191 | - -- Error while trying to spill R1 from class GPR: Cannot scavenge register
|
|
| 192 | - -- without an emergency spill slot!
|
|
| 193 | - --
|
|
| 194 | - -- Observed at least with target 'arm-unknown-linux-gnueabihf'.
|
|
| 195 | - --
|
|
| 196 | - --
|
|
| 197 | - -- With LLVM4, llc -O3 crashes when ghc-stage1 tries to compile
|
|
| 198 | - -- rts/HeapStackCheck.cmm
|
|
| 199 | - --
|
|
| 200 | - -- 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
|
|
| 201 | - -- 0 llc 0x0000000102ae63e8 llvm::sys::PrintStackTrace(llvm::raw_ostream&) + 40
|
|
| 202 | - -- 1 llc 0x0000000102ae69a6 SignalHandler(int) + 358
|
|
| 203 | - -- 2 libsystem_platform.dylib 0x00007fffc23f4b3a _sigtramp + 26
|
|
| 204 | - -- 3 libsystem_c.dylib 0x00007fffc226498b __vfprintf + 17876
|
|
| 205 | - -- 4 llc 0x00000001029d5123 llvm::SelectionDAGISel::LowerArguments(llvm::Function const&) + 5699
|
|
| 206 | - -- 5 llc 0x0000000102a21a35 llvm::SelectionDAGISel::SelectAllBasicBlocks(llvm::Function const&) + 3381
|
|
| 207 | - -- 6 llc 0x0000000102a202b1 llvm::SelectionDAGISel::runOnMachineFunction(llvm::MachineFunction&) + 1457
|
|
| 208 | - -- 7 llc 0x0000000101bdc474 (anonymous namespace)::ARMDAGToDAGISel::runOnMachineFunction(llvm::MachineFunction&) + 20
|
|
| 209 | - -- 8 llc 0x00000001025573a6 llvm::MachineFunctionPass::runOnFunction(llvm::Function&) + 134
|
|
| 210 | - -- 9 llc 0x000000010274fb12 llvm::FPPassManager::runOnFunction(llvm::Function&) + 498
|
|
| 211 | - -- 10 llc 0x000000010274fd23 llvm::FPPassManager::runOnModule(llvm::Module&) + 67
|
|
| 212 | - -- 11 llc 0x00000001027501b8 llvm::legacy::PassManagerImpl::run(llvm::Module&) + 920
|
|
| 213 | - -- 12 llc 0x000000010195f075 compileModule(char**, llvm::LLVMContext&) + 12133
|
|
| 214 | - -- 13 llc 0x000000010195bf0b main + 491
|
|
| 215 | - -- 14 libdyld.dylib 0x00007fffc21e5235 start + 1
|
|
| 216 | - -- Stack dump:
|
|
| 217 | - -- 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
|
|
| 218 | - -- 1. Running pass 'Function Pass Manager' on module '/var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_6.bc'.
|
|
| 219 | - -- 2. Running pass 'ARM Instruction Selection' on function '@"stg_gc_f1$def"'
|
|
| 220 | - --
|
|
| 221 | - -- Observed at least with -mtriple=arm-unknown-linux-gnueabihf -enable-tbaa
|
|
| 222 | - --
|
|
| 223 | 184 | llvm_config <- readLlvmConfigCache (hsc_llvm_config hsc_env)
|
| 224 | 185 | let dflags = hsc_dflags hsc_env
|
| 225 | 186 | logger = hsc_logger hsc_env
|
| 226 | 187 | llvmOpts = case llvmOptLevel dflags of
|
| 227 | 188 | 0 -> "-O1" -- required to get the non-naive reg allocator. Passing -regalloc=greedy is not sufficient.
|
| 228 | 189 | 1 -> "-O1"
|
| 229 | - _ -> "-O2"
|
|
| 190 | + _ -> "-O3"
|
|
| 230 | 191 | |
| 231 | 192 | llvm_version <- figureLlvmVersion logger dflags
|
| 232 | 193 | let defaultOptions = map GHC.SysTools.Option . concatMap words . snd
|
| ... | ... | @@ -259,7 +220,7 @@ runLlvmOptPhase pipe_env hsc_env input_fn = do |
| 259 | 220 | llvm_config <- readLlvmConfigCache (hsc_llvm_config hsc_env)
|
| 260 | 221 | let -- we always (unless -optlo specified) run Opt since we rely on it to
|
| 261 | 222 | -- fix up some pretty big deficiencies in the code we generate
|
| 262 | - optIdx = max 0 $ min 2 $ llvmOptLevel dflags -- ensure we're in [0,2]
|
|
| 223 | + optIdx = max 0 $ min 3 $ llvmOptLevel dflags -- ensure we're in [0,3]
|
|
| 263 | 224 | llvmOpts = case lookup optIdx $ llvmPasses llvm_config of
|
| 264 | 225 | Just passes -> passes
|
| 265 | 226 | Nothing -> panic ("runPhase LlvmOpt: llvm-passes file "
|
| ... | ... | @@ -798,8 +798,11 @@ updOptLevelChanged n dfs |
| 798 | 798 | | not (gopt f dfs) = (dfs, changed)
|
| 799 | 799 | | otherwise = (gopt_unset dfs f, True)
|
| 800 | 800 | |
| 801 | + -- Use -O3 for llc/opt when we are compiling with -O2
|
|
| 802 | + llvm_n = if final_n == 2 then 3 else final_n
|
|
| 803 | + |
|
| 801 | 804 | setLlvmOptLevel dfs
|
| 802 | - | llvmOptLevel dfs /= final_n = (dfs{ llvmOptLevel = final_n }, True)
|
|
| 805 | + | llvmOptLevel dfs /= llvm_n = (dfs{ llvmOptLevel = llvm_n }, True)
|
|
| 803 | 806 | | otherwise = (dfs, False)
|
| 804 | 807 | |
| 805 | 808 | updOptLevel :: Int -> DynFlags -> DynFlags
|
| 1 | 1 | {-# LANGUAGE CPP #-}
|
| 2 | +{-# LANGUAGE MagicHash #-}
|
|
| 2 | 3 | {-# LANGUAGE UnboxedTuples #-}
|
| 3 | 4 | {-# LANGUAGE DerivingVia #-}
|
| 4 | 5 | |
| ... | ... | @@ -160,14 +161,17 @@ import qualified Data.Set as Set |
| 160 | 161 | import Data.Time
|
| 161 | 162 | import Data.List (unfoldr)
|
| 162 | 163 | import System.IO as IO
|
| 163 | -import System.IO.Unsafe ( unsafeInterleaveIO )
|
|
| 164 | 164 | import System.IO.Error ( mkIOError, eofErrorType )
|
| 165 | 165 | import Type.Reflection ( Typeable, SomeTypeRep(..) )
|
| 166 | 166 | import qualified Type.Reflection as Refl
|
| 167 | 167 | import GHC.Real ( Ratio(..) )
|
| 168 | 168 | import Data.IntMap (IntMap)
|
| 169 | 169 | import qualified Data.IntMap as IntMap
|
| 170 | +import GHC.ByteOrder
|
|
| 170 | 171 | import GHC.ForeignPtr ( unsafeWithForeignPtr )
|
| 172 | +import GHC.Exts
|
|
| 173 | +import GHC.IO
|
|
| 174 | +import GHC.Word
|
|
| 171 | 175 | |
| 172 | 176 | import Unsafe.Coerce (unsafeCoerce)
|
| 173 | 177 | |
| ... | ... | @@ -638,7 +642,7 @@ getPrim (ReadBinMem _ ix_r sz_r arr_r) size f = do |
| 638 | 642 | ix <- readFastMutInt ix_r
|
| 639 | 643 | when (ix + size > sz_r) $
|
| 640 | 644 | ioError (mkIOError eofErrorType "Data.Binary.getPrim" Nothing Nothing)
|
| 641 | - w <- unsafeWithForeignPtr arr_r $ \p -> f (p `plusPtr` ix)
|
|
| 645 | + !w <- unsafeWithForeignPtr arr_r $ \p -> f (p `plusPtr` ix)
|
|
| 642 | 646 | -- This is safe WRT #17760 as we we guarantee that the above line doesn't
|
| 643 | 647 | -- diverge
|
| 644 | 648 | writeFastMutInt ix_r (ix + size)
|
| ... | ... | @@ -651,71 +655,52 @@ getWord8 :: ReadBinHandle -> IO Word8 |
| 651 | 655 | getWord8 h = getPrim h 1 peek
|
| 652 | 656 | |
| 653 | 657 | putWord16 :: WriteBinHandle -> Word16 -> IO ()
|
| 654 | -putWord16 h w = putPrim h 2 (\op -> do
|
|
| 655 | - pokeElemOff op 0 (fromIntegral (w `shiftR` 8))
|
|
| 656 | - pokeElemOff op 1 (fromIntegral (w .&. 0xFF))
|
|
| 657 | - )
|
|
| 658 | +putWord16 h w = putPrim h 2 $ \(Ptr p#) ->
|
|
| 659 | + IO $ \s -> (# writeWord8OffAddrAsWord16# p# 0# x# s, () #)
|
|
| 660 | + where
|
|
| 661 | + !(W16# x#) = case targetByteOrder of
|
|
| 662 | + BigEndian -> w
|
|
| 663 | + LittleEndian -> byteSwap16 w
|
|
| 658 | 664 | |
| 659 | 665 | getWord16 :: ReadBinHandle -> IO Word16
|
| 660 | -getWord16 h = getPrim h 2 (\op -> do
|
|
| 661 | - w0 <- fromIntegral <$> peekElemOff op 0
|
|
| 662 | - w1 <- fromIntegral <$> peekElemOff op 1
|
|
| 663 | - return $! w0 `shiftL` 8 .|. w1
|
|
| 664 | - )
|
|
| 666 | +getWord16 h = getPrim h 2 $ \(Ptr p#) ->
|
|
| 667 | + IO $ \s -> case readWord8OffAddrAsWord16# p# 0# s of
|
|
| 668 | + (# s', w16# #) -> case targetByteOrder of
|
|
| 669 | + BigEndian -> (# s', W16# w16# #)
|
|
| 670 | + LittleEndian -> case byteSwap16 $ W16# w16# of
|
|
| 671 | + !w16 -> (# s', w16 #)
|
|
| 665 | 672 | |
| 666 | 673 | putWord32 :: WriteBinHandle -> Word32 -> IO ()
|
| 667 | -putWord32 h w = putPrim h 4 (\op -> do
|
|
| 668 | - pokeElemOff op 0 (fromIntegral (w `shiftR` 24))
|
|
| 669 | - pokeElemOff op 1 (fromIntegral ((w `shiftR` 16) .&. 0xFF))
|
|
| 670 | - pokeElemOff op 2 (fromIntegral ((w `shiftR` 8) .&. 0xFF))
|
|
| 671 | - pokeElemOff op 3 (fromIntegral (w .&. 0xFF))
|
|
| 672 | - )
|
|
| 674 | +putWord32 h w = putPrim h 4 $ \(Ptr p#) ->
|
|
| 675 | + IO $ \s -> (# writeWord8OffAddrAsWord32# p# 0# x# s, () #)
|
|
| 676 | + where
|
|
| 677 | + !(W32# x#) = case targetByteOrder of
|
|
| 678 | + BigEndian -> w
|
|
| 679 | + LittleEndian -> byteSwap32 w
|
|
| 673 | 680 | |
| 674 | 681 | getWord32 :: ReadBinHandle -> IO Word32
|
| 675 | -getWord32 h = getPrim h 4 (\op -> do
|
|
| 676 | - w0 <- fromIntegral <$> peekElemOff op 0
|
|
| 677 | - w1 <- fromIntegral <$> peekElemOff op 1
|
|
| 678 | - w2 <- fromIntegral <$> peekElemOff op 2
|
|
| 679 | - w3 <- fromIntegral <$> peekElemOff op 3
|
|
| 680 | - |
|
| 681 | - return $! (w0 `shiftL` 24) .|.
|
|
| 682 | - (w1 `shiftL` 16) .|.
|
|
| 683 | - (w2 `shiftL` 8) .|.
|
|
| 684 | - w3
|
|
| 685 | - )
|
|
| 682 | +getWord32 h = getPrim h 4 $ \(Ptr p#) ->
|
|
| 683 | + IO $ \s -> case readWord8OffAddrAsWord32# p# 0# s of
|
|
| 684 | + (# s', w32# #) -> case targetByteOrder of
|
|
| 685 | + BigEndian -> (# s', W32# w32# #)
|
|
| 686 | + LittleEndian -> case byteSwap32 $ W32# w32# of
|
|
| 687 | + !w32 -> (# s', w32 #)
|
|
| 686 | 688 | |
| 687 | 689 | putWord64 :: WriteBinHandle -> Word64 -> IO ()
|
| 688 | -putWord64 h w = putPrim h 8 (\op -> do
|
|
| 689 | - pokeElemOff op 0 (fromIntegral (w `shiftR` 56))
|
|
| 690 | - pokeElemOff op 1 (fromIntegral ((w `shiftR` 48) .&. 0xFF))
|
|
| 691 | - pokeElemOff op 2 (fromIntegral ((w `shiftR` 40) .&. 0xFF))
|
|
| 692 | - pokeElemOff op 3 (fromIntegral ((w `shiftR` 32) .&. 0xFF))
|
|
| 693 | - pokeElemOff op 4 (fromIntegral ((w `shiftR` 24) .&. 0xFF))
|
|
| 694 | - pokeElemOff op 5 (fromIntegral ((w `shiftR` 16) .&. 0xFF))
|
|
| 695 | - pokeElemOff op 6 (fromIntegral ((w `shiftR` 8) .&. 0xFF))
|
|
| 696 | - pokeElemOff op 7 (fromIntegral (w .&. 0xFF))
|
|
| 697 | - )
|
|
| 690 | +putWord64 h w = putPrim h 8 $ \(Ptr p#) ->
|
|
| 691 | + IO $ \s -> (# writeWord8OffAddrAsWord64# p# 0# x# s, () #)
|
|
| 692 | + where
|
|
| 693 | + !(W64# x#) = case targetByteOrder of
|
|
| 694 | + BigEndian -> w
|
|
| 695 | + LittleEndian -> byteSwap64 w
|
|
| 698 | 696 | |
| 699 | 697 | getWord64 :: ReadBinHandle -> IO Word64
|
| 700 | -getWord64 h = getPrim h 8 (\op -> do
|
|
| 701 | - w0 <- fromIntegral <$> peekElemOff op 0
|
|
| 702 | - w1 <- fromIntegral <$> peekElemOff op 1
|
|
| 703 | - w2 <- fromIntegral <$> peekElemOff op 2
|
|
| 704 | - w3 <- fromIntegral <$> peekElemOff op 3
|
|
| 705 | - w4 <- fromIntegral <$> peekElemOff op 4
|
|
| 706 | - w5 <- fromIntegral <$> peekElemOff op 5
|
|
| 707 | - w6 <- fromIntegral <$> peekElemOff op 6
|
|
| 708 | - w7 <- fromIntegral <$> peekElemOff op 7
|
|
| 709 | - |
|
| 710 | - return $! (w0 `shiftL` 56) .|.
|
|
| 711 | - (w1 `shiftL` 48) .|.
|
|
| 712 | - (w2 `shiftL` 40) .|.
|
|
| 713 | - (w3 `shiftL` 32) .|.
|
|
| 714 | - (w4 `shiftL` 24) .|.
|
|
| 715 | - (w5 `shiftL` 16) .|.
|
|
| 716 | - (w6 `shiftL` 8) .|.
|
|
| 717 | - w7
|
|
| 718 | - )
|
|
| 698 | +getWord64 h = getPrim h 8 $ \(Ptr p#) ->
|
|
| 699 | + IO $ \s -> case readWord8OffAddrAsWord64# p# 0# s of
|
|
| 700 | + (# s', w64# #) -> case targetByteOrder of
|
|
| 701 | + BigEndian -> (# s', W64# w64# #)
|
|
| 702 | + LittleEndian -> case byteSwap64 $ W64# w64# of
|
|
| 703 | + !w64 -> (# s', w64 #)
|
|
| 719 | 704 | |
| 720 | 705 | putByte :: WriteBinHandle -> Word8 -> IO ()
|
| 721 | 706 | putByte bh !w = putWord8 bh w
|
| 1 | -dir = docs
|
|
| 2 | -TOP = ..
|
|
| 3 | -include $(TOP)/mk/sub-makefile.mk
|
|
| 4 | - |
| 1 | -TOP = ../..
|
|
| 2 | -include $(TOP)/mk/boilerplate.mk
|
|
| 3 | - |
|
| 4 | -# General makefile for Latex stuff
|
|
| 5 | - |
|
| 6 | -dvi: sm.dvi rp.dvi ldv.dvi
|
|
| 7 | -ps: sm.ps rp.ps ldv.ps
|
|
| 8 | - |
|
| 9 | -######## General rules
|
|
| 10 | -.SUFFIXES:
|
|
| 11 | -.PRECIOUS: %.tex %.ps %.bbl
|
|
| 12 | - |
|
| 13 | -#%.dvi: %.tex $(addsuffix .tex, $(basename $(wildcard *.verb *.fig))) $(wildcard *.bib)
|
|
| 14 | -%.dvi: %.tex $(addsuffix .tex, $(basename $(wildcard *.verb))) $(wildcard *.bib)
|
|
| 15 | - latex $<
|
|
| 16 | - @if grep -s "\citation" $*.aux; then bibtex $*; fi
|
|
| 17 | - latex $<
|
|
| 18 | - latex $<
|
|
| 19 | - |
|
| 20 | -%.ps: %.dvi
|
|
| 21 | - dvips -f < $< > $@
|
|
| 22 | - |
|
| 23 | -clean:
|
|
| 24 | - $(RM) *.aux *.log
|
|
| 25 | - |
|
| 26 | -distclean: clean
|
|
| 27 | - $(RM) *.dvi *.ps *.bbl *.blg *.gz
|
|
| 28 | - |
|
| 29 | -maintainer-clean: distclean
|
|
| 30 | - |
|
| 31 | -include $(TOP)/mk/bindist.mk
|
|
| 32 | - |
|
| 33 | -# dummy targets
|
|
| 34 | -all:
|
|
| 35 | -boot:
|
|
| 36 | -install:
|
|
| 37 | -install-docs:
|
|
| 38 | -html:
|
|
| 39 | -chm:
|
|
| 40 | -HxS:
|
|
| 41 | - |
|
| 42 | -# End of file |
| 1 | -dir = docs/users_guide
|
|
| 2 | -TOP = ../..
|
|
| 3 | - |
|
| 4 | -include $(TOP)/mk/sub-makefile.mk |
| 1 | -# -----------------------------------------------------------------------------
|
|
| 2 | -#
|
|
| 3 | -# (c) 2009 The University of Glasgow
|
|
| 4 | -#
|
|
| 5 | -# This file is part of the GHC build system.
|
|
| 6 | -#
|
|
| 7 | -# To understand how the build system works and how to modify it, see
|
|
| 8 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
|
|
| 9 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
|
|
| 10 | -#
|
|
| 11 | -# -----------------------------------------------------------------------------
|
|
| 12 | - |
|
| 13 | -dir = driver
|
|
| 14 | -TOP = ..
|
|
| 15 | -include $(TOP)/mk/sub-makefile.mk |
| 1 | -dir=driver/ghc
|
|
| 2 | -TOP=../..
|
|
| 3 | -include $(TOP)/mk/sub-makefile.mk |
| 1 | -# -----------------------------------------------------------------------------
|
|
| 2 | -#
|
|
| 3 | -# (c) 2009 The University of Glasgow
|
|
| 4 | -#
|
|
| 5 | -# This file is part of the GHC build system.
|
|
| 6 | -#
|
|
| 7 | -# To understand how the build system works and how to modify it, see
|
|
| 8 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
|
|
| 9 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
|
|
| 10 | -#
|
|
| 11 | -# -----------------------------------------------------------------------------
|
|
| 12 | - |
|
| 13 | -dir = driver/ghci
|
|
| 14 | -TOP = ../..
|
|
| 15 | -include $(TOP)/mk/sub-makefile.mk |
| 1 | -dir=driver/haddock
|
|
| 2 | -TOP=../..
|
|
| 3 | -include $(TOP)/mk/sub-makefile.mk |
| 1 | -# -----------------------------------------------------------------------------
|
|
| 2 | -#
|
|
| 3 | -# (c) 2009 The University of Glasgow
|
|
| 4 | -#
|
|
| 5 | -# This file is part of the GHC build system.
|
|
| 6 | -#
|
|
| 7 | -# To understand how the build system works and how to modify it, see
|
|
| 8 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
|
|
| 9 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
|
|
| 10 | -#
|
|
| 11 | -# -----------------------------------------------------------------------------
|
|
| 12 | - |
|
| 13 | -dir = ghc
|
|
| 14 | - |
|
| 15 | -include ../mk/compiler-ghc.mk
|
|
| 16 | - |
| 1 | -dir = libraries
|
|
| 2 | -TOP = ..
|
|
| 3 | -SPEC_TARGETS = 1
|
|
| 4 | -include $(TOP)/mk/sub-makefile.mk
|
|
| 5 | - |
|
| 6 | -.PHONY: 1
|
|
| 7 | -1 :
|
|
| 8 | - +$(TOPMAKE) stage1_libs
|
|
| 9 | - |
|
| 10 | -.PHONY: extra-help
|
|
| 11 | -help : extra-help
|
|
| 12 | -extra-help :
|
|
| 13 | - @echo " make 1"
|
|
| 14 | - @echo
|
|
| 15 | - @echo " Build all libraries that are built by the stage1 GHC"
|
|
| 16 | - @echo |
| 1 | -TOP=..
|
|
| 2 | -include $(TOP)/mk/boilerplate.mk
|
|
| 3 | -XML_DOC=libraries
|
|
| 4 | -include $(TOP)/mk/target.mk |
| 1 | -# -----------------------------------------------------------------------------
|
|
| 2 | -#
|
|
| 3 | -# (c) 2009 The University of Glasgow
|
|
| 4 | -#
|
|
| 5 | -# This file is part of the GHC build system.
|
|
| 6 | -#
|
|
| 7 | -# To understand how the build system works and how to modify it, see
|
|
| 8 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
|
|
| 9 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
|
|
| 10 | -#
|
|
| 11 | -# -----------------------------------------------------------------------------
|
|
| 12 | - |
|
| 13 | -dir = linters/lint-codes
|
|
| 14 | -TOP = ../..
|
|
| 15 | -include $(TOP)/mk/sub-makefile.mk |
| 1 | -# -----------------------------------------------------------------------------
|
|
| 2 | -#
|
|
| 3 | -# (c) 2009 The University of Glasgow
|
|
| 4 | -#
|
|
| 5 | -# This file is part of the GHC build system.
|
|
| 6 | -#
|
|
| 7 | -# To understand how the build system works and how to modify it, see
|
|
| 8 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
|
|
| 9 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
|
|
| 10 | -#
|
|
| 11 | -# -----------------------------------------------------------------------------
|
|
| 12 | - |
|
| 13 | -dir = linters/lint-notes
|
|
| 14 | -TOP = ../..
|
|
| 15 | -include $(TOP)/mk/sub-makefile.mk
|
|
| 16 | - |
|
| 17 | -FAST_MAKE_OPTS += stage=none |
| 1 | 1 | [
|
| 2 | 2 | (0, "-passes=function(require<tbaa>),function(mem2reg),globalopt,function(lower-expect)"),
|
| 3 | 3 | (1, "-passes=default<O1>"),
|
| 4 | -(2, "-passes=default<O2>")
|
|
| 4 | +(2, "-passes=default<O2>"),
|
|
| 5 | +(3, "-passes=default<O3>")
|
|
| 5 | 6 | ] |
| 1 | -# -----------------------------------------------------------------------------
|
|
| 2 | -#
|
|
| 3 | -# (c) 2009 The University of Glasgow
|
|
| 4 | -#
|
|
| 5 | -# This file is part of the GHC build system.
|
|
| 6 | -#
|
|
| 7 | -# To understand how the build system works and how to modify it, see
|
|
| 8 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
|
|
| 9 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
|
|
| 10 | -#
|
|
| 11 | -# -----------------------------------------------------------------------------
|
|
| 12 | - |
|
| 13 | -dir = rts
|
|
| 14 | -TOP = ..
|
|
| 15 | -include $(TOP)/mk/sub-makefile.mk
|
|
| 16 | - |
|
| 17 | -FAST_MAKE_OPTS += stage=none |
| 1 | -# -----------------------------------------------------------------------------
|
|
| 2 | -#
|
|
| 3 | -# (c) 2009 The University of Glasgow
|
|
| 4 | -#
|
|
| 5 | -# This file is part of the GHC build system.
|
|
| 6 | -#
|
|
| 7 | -# To understand how the build system works and how to modify it, see
|
|
| 8 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
|
|
| 9 | -# https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
|
|
| 10 | -#
|
|
| 11 | -# -----------------------------------------------------------------------------
|
|
| 12 | - |
|
| 13 | -dir = rts/include
|
|
| 14 | -TOP = ../..
|
|
| 15 | -include $(TOP)/mk/sub-makefile.mk |