diff options
-rw-r--r-- | aclocal.m4 | 7 | ||||
-rw-r--r-- | compiler/llvmGen/LlvmCodeGen.hs | 11 | ||||
-rw-r--r-- | compiler/llvmGen/LlvmCodeGen/Ppr.hs | 63 | ||||
-rw-r--r-- | compiler/main/DriverPipeline.hs | 237 | ||||
-rw-r--r-- | compiler/main/DynFlags.hs | 36 | ||||
-rw-r--r-- | compiler/main/GHC.hs | 3 | ||||
-rw-r--r-- | compiler/main/SysTools.hs | 21 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Linear/Main.hs | 2 | ||||
-rw-r--r-- | configure.ac | 7 | ||||
-rw-r--r-- | ghc.mk | 7 | ||||
-rw-r--r-- | ghc/GHCi/UI.hs | 4 | ||||
-rw-r--r-- | ghc/ghc.mk | 5 | ||||
-rw-r--r-- | llvm-targets | 22 | ||||
-rw-r--r-- | mk/config.mk.in | 1 | ||||
-rw-r--r-- | settings.in | 3 | ||||
-rw-r--r-- | testsuite/mk/ghc-config.hs | 1 | ||||
-rw-r--r-- | testsuite/tests/perf/compiler/all.T | 6 | ||||
-rwxr-xr-x | utils/llvm-targets/gen-data-layout.sh | 80 |
18 files changed, 342 insertions, 174 deletions
diff --git a/aclocal.m4 b/aclocal.m4 index 6a732d08ee..d365dba0e2 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -519,6 +519,12 @@ AC_DEFUN([FP_SETTINGS], else SettingsLibtoolCommand="$LibtoolCmd" fi + if test -z "$ClangCmd" + then + SettingsClangCommand="clang" + else + SettingsClangCommand="$ClangCmd" + fi if test -z "$LlcCmd" then SettingsLlcCommand="llc" @@ -549,6 +555,7 @@ AC_DEFUN([FP_SETTINGS], AC_SUBST(SettingsWindresCommand) AC_SUBST(SettingsLibtoolCommand) AC_SUBST(SettingsTouchCommand) + AC_SUBST(SettingsClangCommand) AC_SUBST(SettingsLlcCommand) AC_SUBST(SettingsOptCommand) ]) diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs index 71b9996ceb..c11252aa10 100644 --- a/compiler/llvmGen/LlvmCodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen.hs @@ -72,7 +72,7 @@ llvmCodeGen dflags h us cmm_stream llvmCodeGen' :: Stream.Stream LlvmM RawCmmGroup () -> LlvmM () llvmCodeGen' cmm_stream = do -- Preamble - renderLlvm pprLlvmHeader + renderLlvm header ghcInternalFunctions cmmMetaLlvmPrelude @@ -85,6 +85,15 @@ llvmCodeGen' cmm_stream -- Postamble cmmUsedLlvmGens + where + header :: SDoc + header = sdocWithDynFlags $ \dflags -> + let target = LLVM_TARGET + layout = case lookup target (llvmTargets dflags) of + Just (LlvmTarget dl _ _) -> dl + Nothing -> error $ "Failed to lookup the datalayout for " ++ target ++ "; available targets: " ++ show (map fst $ llvmTargets dflags) + in text ("target datalayout = \"" ++ layout ++ "\"") + $+$ text ("target triple = \"" ++ target ++ "\"") llvmGroupLlvmGens :: RawCmmGroup -> LlvmM () llvmGroupLlvmGens cmm = do diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index 8614084f0c..ef32d41d7c 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -4,7 +4,7 @@ -- | Pretty print helpers for the LLVM Code generator. -- module LlvmCodeGen.Ppr ( - pprLlvmHeader, pprLlvmCmmDecl, pprLlvmData, infoSection + pprLlvmCmmDecl, pprLlvmData, infoSection ) where #include "HsVersions.h" @@ -15,7 +15,6 @@ import LlvmCodeGen.Data import CLabel import Cmm -import Platform import FastString import Outputable @@ -25,66 +24,6 @@ import Unique -- * Top level -- --- | Header code for LLVM modules -pprLlvmHeader :: SDoc -pprLlvmHeader = moduleLayout - - --- | LLVM module layout description for the host target -moduleLayout :: SDoc -moduleLayout = sdocWithPlatform $ \platform -> - case platform of - Platform { platformArch = ArchX86, platformOS = OSDarwin } -> - text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:32:64-f32:32:32-f64:32:64-v64:64:64-v128:128:128-a0:0:64-f80:128:128-n8:16:32\"" - $+$ text "target triple = \"i386-apple-darwin9.8\"" - Platform { platformArch = ArchX86, platformOS = OSMinGW32 } -> - text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-f80:128:128-v64:64:64-v128:128:128-a0:0:64-f80:32:32-n8:16:32\"" - $+$ text "target triple = \"i686-pc-win32\"" - Platform { platformArch = ArchX86, platformOS = OSLinux } -> - text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:32:64-f32:32:32-f64:32:64-v64:64:64-v128:128:128-a0:0:64-f80:32:32-n8:16:32\"" - $+$ text "target triple = \"i386-pc-linux-gnu\"" - Platform { platformArch = ArchX86_64, platformOS = OSDarwin } -> - text "target datalayout = \"e-p:64:64:64-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:128:128-a0:0:64-s0:64:64-f80:128:128-n8:16:32:64\"" - $+$ text "target triple = \"x86_64-apple-darwin10.0.0\"" - Platform { platformArch = ArchX86_64, platformOS = OSLinux } -> - text "target datalayout = \"e-p:64:64:64-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:128:128-a0:0:64-s0:64:64-f80:128:128-n8:16:32:64\"" - $+$ text "target triple = \"x86_64-linux-gnu\"" - Platform { platformArch = ArchARM {}, platformOS = OSLinux } -> - text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:64:128-a0:0:64-n32\"" - $+$ text "target triple = \"armv6-unknown-linux-gnueabihf\"" - Platform { platformArch = ArchARM {}, platformOS = OSAndroid } -> - text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:64:128-a0:0:64-n32\"" - $+$ text "target triple = \"arm-unknown-linux-androideabi\"" - Platform { platformArch = ArchARM {}, platformOS = OSQNXNTO } -> - text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:64:128-a0:0:64-n32\"" - $+$ text "target triple = \"arm-unknown-nto-qnx8.0.0eabi\"" - Platform { platformArch = ArchARM {}, platformOS = OSiOS } -> - text "target datalayout = \"e-m:o-p:32:32-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32\"" - $+$ text "target triple = \"thumbv7-apple-ios7.0.0\"" - Platform { platformArch = ArchARM64, platformOS = OSiOS } -> - text "target datalayout = \"e-m:o-i64:64-i128:128-n32:64-S128\"" - $+$ text "target triple = \"arm64-apple-ios7.0.0\"" - Platform { platformArch = ArchX86, platformOS = OSiOS } -> - text "target datalayout = \"e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128\"" - $+$ text "target triple = \"i386-apple-ios7.0.0\"" - Platform { platformArch = ArchX86_64, platformOS = OSiOS } -> - text "target datalayout = \"e-m:o-i64:64-f80:128-n8:16:32:64-S128\"" - $+$ text "target triple = \"x86_64-apple-ios7.0.0\"" - Platform { platformArch = ArchARM64, platformOS = OSLinux } -> - text "target datalayout = \"e-m:e-i64:64-i128:128-n32:64-S128\"" - $+$ text "target triple = \"aarch64-unknown-linux-gnu\"" - _ -> - if platformIsCrossCompiling platform - then panic "LlvmCodeGen.Ppr: Cross compiling without valid target info." - else empty - -- If you see the above panic, GHC is missing the required target datalayout - -- and triple information. You can obtain this info by compiling a simple - -- 'hello world' C program with the clang C compiler eg: - -- clang -S hello.c -emit-llvm -o - - -- and the first two lines of hello.ll should provide the 'target datalayout' - -- and 'target triple' lines required. - - -- | Pretty print LLVM data code pprLlvmData :: LlvmData -> SDoc pprLlvmData (globals, types) = diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index d94cbb4eb7..ef3123896e 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -69,7 +69,7 @@ import System.Directory import System.FilePath import System.IO import Control.Monad -import Data.List ( isSuffixOf ) +import Data.List ( isSuffixOf, intercalate ) import Data.Maybe import Data.Version @@ -830,6 +830,63 @@ getOutputFilename stop_phase output basename dflags next_phase maybe_location | Just d <- odir = d </> persistent | otherwise = persistent + +-- | The fast LLVM Pipeline skips the mangler and assembler, +-- emiting object code dirctly from llc. +-- +-- slow: opt -> llc -> .s -> mangler -> as -> .o +-- fast: opt -> llc -> .o +-- +-- hidden flag: -ffast-llvm +-- +-- if keep-s-files is specified, we need to go through +-- the slow pipeline (Kavon Farvardin requested this). +fastLlvmPipeline :: DynFlags -> Bool +fastLlvmPipeline dflags + = not (gopt Opt_KeepSFiles dflags) && gopt Opt_FastLlvm dflags + +-- | LLVM Options. These are flags to be passed to opt and llc, to ensure +-- consistency we list them in pairs, so that they form groups. +llvmOptions :: DynFlags + -> [(String, String)] -- ^ pairs of (opt, llc) arguments +llvmOptions dflags = + [("-enable-tbaa -tbaa", "-enable-tbaa") | gopt Opt_LlvmTBAA dflags ] + ++ [("-relocation-model=" ++ rmodel + ,"-relocation-model=" ++ rmodel) | not (null rmodel)] + ++ [("-stack-alignment=" ++ (show align) + ,"-stack-alignment=" ++ (show align)) | align > 0 ] + ++ [("", "-filetype=obj") | fastLlvmPipeline dflags ] + + -- Additional llc flags + ++ [("", "-mcpu=" ++ mcpu) | not (null mcpu) ] + ++ [("", "-mattr=" ++ attrs) | not (null attrs) ] + + where target = LLVM_TARGET + Just (LlvmTarget _ mcpu mattr) = lookup target (llvmTargets dflags) + + -- Relocation models + rmodel | gopt Opt_PIC dflags = "pic" + | positionIndependent dflags = "pic" + | WayDyn `elem` ways dflags = "dynamic-no-pic" + | otherwise = "static" + + align :: Int + align = case platformArch (targetPlatform dflags) of + ArchX86_64 | isAvxEnabled dflags -> 32 + _ -> 0 + + attrs :: String + attrs = intercalate "," $ mattr + ++ ["+sse42" | isSse4_2Enabled dflags ] + ++ ["+sse2" | isSse2Enabled dflags ] + ++ ["+sse" | isSseEnabled dflags ] + ++ ["+avx512f" | isAvx512fEnabled dflags ] + ++ ["+avx2" | isAvx2Enabled dflags ] + ++ ["+avx" | isAvxEnabled dflags ] + ++ ["+avx512cd"| isAvx512cdEnabled dflags ] + ++ ["+avx512er"| isAvx512erEnabled dflags ] + ++ ["+avx512pf"| isAvx512pfEnabled dflags ] + -- ----------------------------------------------------------------------------- -- | Each phase in the pipeline returns the next phase to execute, and the -- name of the file in which the output was placed. @@ -1427,121 +1484,115 @@ runPhase (RealPhase SplitAs) _input_fn dflags ----------------------------------------------------------------------------- -- LlvmOpt phase - runPhase (RealPhase LlvmOpt) input_fn dflags = do - let opt_lvl = max 0 (min 2 $ optLevel dflags) - -- don't specify anything if user has specified commands. We do this - -- for opt but not llc since opt is very specifically for optimisation - -- passes only, so if the user is passing us extra options we assume - -- they know what they are doing and don't get in the way. - optFlag = if null (getOpts dflags opt_lo) - then map SysTools.Option $ words (llvmOpts !! opt_lvl) - else [] - tbaa | gopt Opt_LlvmTBAA dflags = "--enable-tbaa=true" - | otherwise = "--enable-tbaa=false" - - output_fn <- phaseOutputFilename LlvmLlc liftIO $ SysTools.runLlvmOpt dflags - ([ SysTools.FileOption "" input_fn, - SysTools.Option "-o", - SysTools.FileOption "" output_fn] - ++ optFlag - ++ [SysTools.Option tbaa]) + ( optFlag + ++ defaultOptions ++ + [ SysTools.FileOption "" input_fn + , SysTools.Option "-o" + , SysTools.FileOption "" output_fn] + ) return (RealPhase LlvmLlc, output_fn) where -- we always (unless -optlo specified) run Opt since we rely on it to -- fix up some pretty big deficiencies in the code we generate - llvmOpts = [ "-mem2reg -globalopt" - , "-O1 -globalopt" - , "-O2" - ] + llvmOpts = case optLevel dflags of + 0 -> "-mem2reg -globalopt" + 1 -> "-O1 -globalopt" + _ -> "-O2" + + -- don't specify anything if user has specified commands. We do this + -- for opt but not llc since opt is very specifically for optimisation + -- passes only, so if the user is passing us extra options we assume + -- they know what they are doing and don't get in the way. + optFlag = if null (getOpts dflags opt_lo) + then map SysTools.Option $ words llvmOpts + else [] + + defaultOptions = map SysTools.Option . concat . fmap words . fst + $ unzip (llvmOptions dflags) ----------------------------------------------------------------------------- -- LlvmLlc phase runPhase (RealPhase LlvmLlc) input_fn dflags = do - let opt_lvl = max 0 (min 2 $ optLevel dflags) - -- iOS requires external references to be loaded indirectly from the - -- DATA segment or dyld traps at runtime writing into TEXT: see #7722 - rmodel | platformOS (targetPlatform dflags) == OSiOS = "dynamic-no-pic" - | positionIndependent dflags = "pic" - | WayDyn `elem` ways dflags = "dynamic-no-pic" - | otherwise = "static" - tbaa | gopt Opt_LlvmTBAA dflags = "--enable-tbaa=true" - | otherwise = "--enable-tbaa=false" - - -- hidden debugging flag '-dno-llvm-mangler' to skip mangling - let next_phase = case gopt Opt_NoLlvmMangler dflags of - False -> LlvmMangle - True | gopt Opt_SplitObjs dflags -> Splitter - True -> As False + next_phase <- if fastLlvmPipeline dflags + then maybeMergeForeign + -- hidden debugging flag '-dno-llvm-mangler' to skip mangling + else case gopt Opt_NoLlvmMangler dflags of + False -> return LlvmMangle + True | gopt Opt_SplitObjs dflags -> return Splitter + True -> return (As False) output_fn <- phaseOutputFilename next_phase liftIO $ SysTools.runLlvmLlc dflags - ([ SysTools.Option (llvmOpts !! opt_lvl), - SysTools.Option $ "-relocation-model=" ++ rmodel, - SysTools.FileOption "" input_fn, - SysTools.Option "-o", SysTools.FileOption "" output_fn] - ++ [SysTools.Option tbaa] - ++ map SysTools.Option fpOpts - ++ map SysTools.Option abiOpts - ++ map SysTools.Option sseOpts - ++ map SysTools.Option avxOpts - ++ map SysTools.Option avx512Opts - ++ map SysTools.Option stackAlignOpts) + ( optFlag + ++ defaultOptions + ++ [ SysTools.FileOption "" input_fn + , SysTools.Option "-o" + , SysTools.FileOption "" output_fn + ] + ) return (RealPhase next_phase, output_fn) where - -- Bug in LLVM at O3 on OSX. - llvmOpts = if platformOS (targetPlatform dflags) == OSDarwin - then ["-O1", "-O2", "-O2"] - else ["-O1", "-O2", "-O3"] - -- On ARMv7 using LLVM, LLVM fails to allocate floating point registers - -- while compiling GHC source code. It's probably due to fact that it - -- does not enable VFP by default. Let's do this manually here - fpOpts = case platformArch (targetPlatform dflags) of - ArchARM ARMv7 ext _ -> if (elem VFPv3 ext) - then ["-mattr=+v7,+vfp3"] - else if (elem VFPv3D16 ext) - then ["-mattr=+v7,+vfp3,+d16"] - else [] - ArchARM ARMv6 ext _ -> if (elem VFPv2 ext) - then ["-mattr=+v6,+vfp2"] - else ["-mattr=+v6"] - _ -> [] - -- On Ubuntu/Debian with ARM hard float ABI, LLVM's llc still - -- compiles into soft-float ABI. We need to explicitly set abi - -- to hard - abiOpts = case platformArch (targetPlatform dflags) of - ArchARM _ _ HARD -> ["-float-abi=hard"] - ArchARM _ _ _ -> [] - _ -> [] - - sseOpts | isSse4_2Enabled dflags = ["-mattr=+sse42"] - | isSse2Enabled dflags = ["-mattr=+sse2"] - | isSseEnabled dflags = ["-mattr=+sse"] - | otherwise = [] - - avxOpts | isAvx512fEnabled dflags = ["-mattr=+avx512f"] - | isAvx2Enabled dflags = ["-mattr=+avx2"] - | isAvxEnabled dflags = ["-mattr=+avx"] - | otherwise = [] - - avx512Opts = - [ "-mattr=+avx512cd" | isAvx512cdEnabled dflags ] ++ - [ "-mattr=+avx512er" | isAvx512erEnabled dflags ] ++ - [ "-mattr=+avx512pf" | isAvx512pfEnabled dflags ] - - stackAlignOpts = - case platformArch (targetPlatform dflags) of - ArchX86_64 | isAvxEnabled dflags -> ["-stack-alignment=32"] - _ -> [] + -- 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 + -- + llvmOpts = case optLevel dflags of + 0 -> "-O1" -- required to get the non-naive reg allocator. Passing -regalloc=greedy is not sufficient. + 1 -> "-O1" + _ -> "-O2" + + optFlag = if null (getOpts dflags opt_lc) + then map SysTools.Option $ words llvmOpts + else [] + + defaultOptions = map SysTools.Option . concat . fmap words . snd + $ unzip (llvmOptions dflags) + ----------------------------------------------------------------------------- -- LlvmMangle phase diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index c15943c7f3..d68299ad54 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -76,6 +76,9 @@ module DynFlags ( safeDirectImpsReq, safeImplicitImpsReq, unsafeFlags, unsafeFlagsForInfer, + -- ** LLVM Targets + LlvmTarget(..), LlvmTargets, + -- ** System tool settings and locations Settings(..), targetPlatform, programName, projectVersion, @@ -83,9 +86,9 @@ module DynFlags ( versionedAppDir, extraGccViaCFlags, systemPackageConfig, pgm_L, pgm_P, pgm_F, pgm_c, pgm_s, pgm_a, pgm_l, pgm_dll, pgm_T, - pgm_windres, pgm_libtool, pgm_lo, pgm_lc, pgm_i, + pgm_windres, pgm_libtool, pgm_lo, pgm_lc, pgm_lcc, pgm_i, opt_L, opt_P, opt_F, opt_c, opt_a, opt_l, opt_i, - opt_windres, opt_lo, opt_lc, + opt_windres, opt_lo, opt_lc, opt_lcc, -- ** Manipulating DynFlags @@ -405,6 +408,7 @@ data GeneralFlag | Opt_DoAsmLinting | Opt_DoAnnotationLinting | Opt_NoLlvmMangler -- hidden flag + | Opt_FastLlvm -- hidden flag | Opt_WarnIsError -- -Werror; makes warnings fatal | Opt_ShowWarnGroups -- Show the group a warning belongs to @@ -700,6 +704,7 @@ data DynFlags = DynFlags { ghcLink :: GhcLink, hscTarget :: HscTarget, settings :: Settings, + llvmTargets :: LlvmTargets, verbosity :: Int, -- ^ Verbosity level: see Note [Verbosity levels] optLevel :: Int, -- ^ Optimisation level debugLevel :: Int, -- ^ How much debug information to produce @@ -996,6 +1001,14 @@ data ProfAuto | ProfAutoCalls -- ^ annotate call-sites deriving (Eq,Enum) +data LlvmTarget = LlvmTarget + { lDataLayout :: String + , lCPU :: String + , lAttributes :: [String] + } + +type LlvmTargets = [(String, LlvmTarget)] + data Settings = Settings { sTargetPlatform :: Platform, -- Filled in by SysTools sGhcUsagePath :: FilePath, -- Filled in by SysTools @@ -1028,6 +1041,7 @@ data Settings = Settings { sPgm_libtool :: String, sPgm_lo :: (String,[Option]), -- LLVM: opt llvm optimiser sPgm_lc :: (String,[Option]), -- LLVM: llc static compiler + sPgm_lcc :: (String,[Option]), -- LLVM: c compiler sPgm_i :: String, -- options for particular phases sOpt_L :: [String], @@ -1039,6 +1053,7 @@ data Settings = Settings { sOpt_windres :: [String], sOpt_lo :: [String], -- LLVM: llvm optimiser sOpt_lc :: [String], -- LLVM: llc static compiler + sOpt_lcc :: [String], -- LLVM: c compiler sOpt_i :: [String], -- iserv options sPlatformConstants :: PlatformConstants @@ -1086,6 +1101,8 @@ pgm_windres :: DynFlags -> String pgm_windres dflags = sPgm_windres (settings dflags) pgm_libtool :: DynFlags -> String pgm_libtool dflags = sPgm_libtool (settings dflags) +pgm_lcc :: DynFlags -> (String,[Option]) +pgm_lcc dflags = sPgm_lcc (settings dflags) pgm_lo :: DynFlags -> (String,[Option]) pgm_lo dflags = sPgm_lo (settings dflags) pgm_lc :: DynFlags -> (String,[Option]) @@ -1109,6 +1126,8 @@ opt_l dflags = concatMap (wayOptl (targetPlatform dflags)) (ways dflags) ++ sOpt_l (settings dflags) opt_windres :: DynFlags -> [String] opt_windres dflags = sOpt_windres (settings dflags) +opt_lcc :: DynFlags -> [String] +opt_lcc dflags = sOpt_lcc (settings dflags) opt_lo :: DynFlags -> [String] opt_lo dflags = sOpt_lo (settings dflags) opt_lc :: DynFlags -> [String] @@ -1542,8 +1561,8 @@ initDynFlags dflags = do -- | The normal 'DynFlags'. Note that they are not suitable for use in this form -- and must be fully initialized by 'GHC.runGhc' first. -defaultDynFlags :: Settings -> DynFlags -defaultDynFlags mySettings = +defaultDynFlags :: Settings -> LlvmTargets -> DynFlags +defaultDynFlags mySettings myLlvmTargets = -- See Note [Updating flag description in the User's Guide] DynFlags { ghcMode = CompManager, @@ -1633,6 +1652,8 @@ defaultDynFlags mySettings = buildTag = mkBuildTag (defaultWays mySettings), splitInfo = Nothing, settings = mySettings, + llvmTargets = myLlvmTargets, + -- ghc -M values depMakefile = "Makefile", depIncludePkgDeps = False, @@ -3058,6 +3079,8 @@ dynamic_flags_deps = [ (NoArg (setGeneralFlag Opt_D_faststring_stats)) , make_ord_flag defGhcFlag "dno-llvm-mangler" (NoArg (setGeneralFlag Opt_NoLlvmMangler)) -- hidden flag + , make_ord_flag defGhcFlag "fast-llvm" + (NoArg (setGeneralFlag Opt_FastLlvm)) -- hidden flag , make_ord_flag defGhcFlag "ddump-debug" (setDumpFlag Opt_D_dump_debug) , make_ord_flag defGhcFlag "ddump-json" @@ -5240,9 +5263,10 @@ makeDynFlagsConsistent dflags -- initialized. defaultGlobalDynFlags :: DynFlags defaultGlobalDynFlags = - (defaultDynFlags settings) { verbosity = 2 } + (defaultDynFlags settings llvmTargets) { verbosity = 2 } where - settings = panic "v_unsafeGlobalDynFlags: not initialised" + settings = panic "v_unsafeGlobalDynFlags: settings not initialised" + llvmTargets = panic "v_unsafeGlobalDynFlags: llvmTargets not initialised" #if STAGE < 2 GLOBAL_VAR(v_unsafeGlobalDynFlags, defaultGlobalDynFlags, DynFlags) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 8a8735fa47..e02f6b8e6b 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -493,7 +493,8 @@ initGhcMonad :: GhcMonad m => Maybe FilePath -> m () initGhcMonad mb_top_dir = do { env <- liftIO $ do { mySettings <- initSysTools mb_top_dir - ; dflags <- initDynFlags (defaultDynFlags mySettings) + ; myLlvmTargets <- initLlvmTargets mb_top_dir + ; dflags <- initDynFlags (defaultDynFlags mySettings myLlvmTargets) ; checkBrokenTablesNextToCode dflags ; setUnsafeGlobalDynFlags dflags -- c.f. DynFlags.parseDynamicFlagsFull, which diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index b48bbf4202..cd7a23d833 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -13,6 +13,7 @@ module SysTools ( -- Initialisation initSysTools, + initLlvmTargets, -- Interface to system tools runUnlit, runCpp, runCc, -- [Option] -> IO () @@ -174,6 +175,20 @@ stuff. ************************************************************************ -} +initLlvmTargets :: Maybe String + -> IO LlvmTargets +initLlvmTargets mbMinusB + = do top_dir <- findTopDir mbMinusB + let llvmTargetsFile = top_dir </> "llvm-targets" + llvmTargetsStr <- readFile llvmTargetsFile + case maybeReadFuzzy llvmTargetsStr of + Just s -> return (fmap mkLlvmTarget <$> s) + Nothing -> pgmError ("Can't parse " ++ show llvmTargetsFile) + where + mkLlvmTarget :: (String, String, String) -> LlvmTarget + mkLlvmTarget (dl, cpu, attrs) = LlvmTarget dl cpu (words attrs) + + initSysTools :: Maybe String -- Maybe TopDir path (without the '-B' prefix) -> IO Settings -- Set all the mutable variables above, holding -- (a) the system programs @@ -309,6 +324,7 @@ initSysTools mbMinusB -- We just assume on command line lc_prog <- getSetting "LLVM llc command" lo_prog <- getSetting "LLVM opt command" + lcc_prog <- getSetting "LLVM clang command" let iserv_prog = libexec "ghc-iserv" @@ -352,6 +368,7 @@ initSysTools mbMinusB sPgm_libtool = libtool_path, sPgm_lo = (lo_prog,[]), sPgm_lc = (lc_prog,[]), + sPgm_lcc = (lcc_prog,[]), sPgm_i = iserv_prog, sOpt_L = [], sOpt_P = [], @@ -360,6 +377,7 @@ initSysTools mbMinusB sOpt_a = [], sOpt_l = [], sOpt_windres = [], + sOpt_lcc = [], sOpt_lo = [], sOpt_lc = [], sOpt_i = [], @@ -574,8 +592,7 @@ runLlvmLlc dflags args = do -- assembler) runClang :: DynFlags -> [Option] -> IO () runClang dflags args = do - -- we simply assume its available on the PATH - let clang = "clang" + let (clang,_) = pgm_lcc dflags -- be careful what options we call clang with -- see #5903 and #7617 for bugs caused by this. (_,args0) = pgm_a dflags diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs index 2ba682ad17..c13d02edb8 100644 --- a/compiler/nativeGen/RegAlloc/Linear/Main.hs +++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs @@ -496,7 +496,7 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do -- debugging {- freeregs <- getFreeRegsR assig <- getAssigR - pprDebugAndThen (defaultDynFlags Settings{ sTargetPlatform=platform }) trace "genRaInsn" + pprDebugAndThen (defaultDynFlags Settings{ sTargetPlatform=platform } undefined) trace "genRaInsn" (ppr instr $$ text "r_dying = " <+> ppr r_dying $$ text "w_dying = " <+> ppr w_dying diff --git a/configure.ac b/configure.ac index 500be7e491..92b8523023 100644 --- a/configure.ac +++ b/configure.ac @@ -637,6 +637,12 @@ AC_SUBST([LlvmVersion]) sUPPORTED_LLVM_VERSION=$(echo \($LlvmVersion\) | sed 's/\./,/') AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION], ${sUPPORTED_LLVM_VERSION}, [The supported LLVM version number]) +dnl ** Which LLVM clang to use? +dnl -------------------------------------------------------------- +AC_CHECK_TARGET_TOOL([CLANG], [clang]) +ClangCmd="$CLANG" +AC_SUBST([ClangCmd]) + dnl ** Which LLVM llc to use? dnl -------------------------------------------------------------- FIND_LLVM_PROG([LLC], [llc], [$LlvmVersion]) @@ -1324,6 +1330,7 @@ echo "\ xelatex : $XELATEX Using LLVM tools + clang : $ClangCmd llc : $LlcCmd opt : $OptCmd" @@ -1050,6 +1050,7 @@ $(eval $(call bindist-list,.,\ INSTALL \ configure config.sub config.guess install-sh \ settings.in \ + llvm-targets \ packages \ Makefile \ mk/config.mk.in \ @@ -1076,7 +1077,7 @@ $(eval $(call bindist-list,.,\ $(wildcard compiler/stage2/doc) \ $(wildcard libraries/*/dist-install/doc/) \ $(wildcard libraries/*/*/dist-install/doc/) \ - $(filter-out settings,$(INSTALL_LIBS)) \ + $(filter-out settings llvm-targets,$(INSTALL_LIBS)) \ $(RTS_INSTALL_LIBS) \ $(filter-out %/project.mk mk/config.mk %/mk/install.mk,$(MAKEFILE_LIST)) \ mk/project.mk \ @@ -1109,7 +1110,7 @@ BIN_DIST_MK = $(BIN_DIST_PREP_DIR)/bindist.mk unix-binary-dist-prep: $(call removeTrees,bindistprep/) "$(MKDIRHIER)" $(BIN_DIST_PREP_DIR) - set -e; for i in packages LICENSE compiler ghc iserv rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh settings.in ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done + set -e; for i in packages LICENSE compiler ghc iserv rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh settings.in llvm-targets ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done echo "HADDOCK_DOCS = $(HADDOCK_DOCS)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_HTML = $(BUILD_SPHINX_HTML)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_PDF = $(BUILD_SPHINX_PDF)" >> $(BIN_DIST_MK) @@ -1207,7 +1208,7 @@ SRC_DIST_GHC_DIRS = mk rules docs distrib bindisttest libffi includes \ SRC_DIST_GHC_FILES += \ configure.ac config.guess config.sub configure \ aclocal.m4 README.md ANNOUNCE HACKING.md INSTALL.md LICENSE Makefile \ - install-sh settings.in VERSION GIT_COMMIT_ID \ + install-sh settings.in llvm-targets VERSION GIT_COMMIT_ID \ boot packages ghc.mk MAKEHELP.md .PHONY: VERSION diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index 8012d741e0..6a03b3c365 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -2510,7 +2510,7 @@ showDynFlags show_all dflags = do is_on = test f dflags quiet = not show_all && test f default_dflags == is_on - default_dflags = defaultDynFlags (settings dflags) + default_dflags = defaultDynFlags (settings dflags) (llvmTargets dflags) (ghciFlags,others) = partition (\f -> flagSpecFlag f `elem` flgs) DynFlags.fFlags @@ -2921,7 +2921,7 @@ showLanguages' show_all dflags = quiet = not show_all && test f default_dflags == is_on default_dflags = - defaultDynFlags (settings dflags) `lang_set` + defaultDynFlags (settings dflags) (llvmTargets dflags) `lang_set` case language dflags of Nothing -> Just Haskell2010 other -> other diff --git a/ghc/ghc.mk b/ghc/ghc.mk index 319f969c75..20fa142df5 100644 --- a/ghc/ghc.mk +++ b/ghc/ghc.mk @@ -132,6 +132,9 @@ all_ghc_stage3 : $(GHC_STAGE3) $(INPLACE_LIB)/settings : settings "$(CP)" $< $@ +$(INPLACE_LIB)/llvm-targets : llvm-targets + "$(CP)" $< $@ + $(INPLACE_LIB)/platformConstants: $(includes_GHCCONSTANTS_HASKELL_VALUE) "$(CP)" $< $@ @@ -140,6 +143,7 @@ $(INPLACE_LIB)/platformConstants: $(includes_GHCCONSTANTS_HASKELL_VALUE) GHC_DEPENDENCIES += $$(unlit_INPLACE) GHC_DEPENDENCIES += $(INPLACE_LIB)/settings +GHC_DEPENDENCIES += $(INPLACE_LIB)/llvm-targets GHC_DEPENDENCIES += $(INPLACE_LIB)/platformConstants $(GHC_STAGE1) : | $(GHC_DEPENDENCIES) @@ -167,6 +171,7 @@ $(GHC_STAGE2) : $(foreach w,$(GhcLibWays),libraries/base/dist-install/build/GHC/ endif INSTALL_LIBS += settings +INSTALL_LIBS += llvm-targets ifeq "$(Windows_Host)" "NO" install: install_ghc_link diff --git a/llvm-targets b/llvm-targets new file mode 100644 index 0000000000..0f717b7dc9 --- /dev/null +++ b/llvm-targets @@ -0,0 +1,22 @@ +[("i386-unknown-windows", ("e-m:x-p:32:32-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) +,("i686-unknown-windows", ("e-m:x-p:32:32-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) +,("x86_64-unknown-windows", ("e-m:w-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("arm-unknown-linux-gnueabihf", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align")) +,("armv6-unknown-linux-gnueabihf", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "arm1136jf-s", "+strict-align")) +,("armv7-unknown-linux-gnueabihf", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "cortex-a8", "")) +,("aarch64-unknown-linux-gnu", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) +,("aarch64-unknown-linux", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) +,("i386-unknown-linux-gnu", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i386-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("x86_64-unknown-linux-gnu", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("armv7-unknown-linux-androideabi", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "cortex-a8", "+soft-float-abi")) +,("aarch64-unknown-linux-android", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) +,("arm-unknown-nto-qnx-eabi", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "arm7tdmi", "+soft-float-abi +strict-align")) +,("i386-apple-darwin", ("e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) +,("x86_64-apple-darwin", ("e-m:o-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) +,("armv7-apple-ios", ("e-m:o-p:32:32-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "cortex-a8", "+soft-float-abi")) +,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "generic", "+neon")) +,("i386-apple-ios", ("e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) +,("x86_64-apple-ios", ("e-m:o-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) +] diff --git a/mk/config.mk.in b/mk/config.mk.in index 2e920ca76e..dbcd0e45b8 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -736,6 +736,7 @@ NM = @NmCmd@ AR = @ArCmd@ OBJDUMP = @ObjdumpCmd@ +CLANG = @ClangCmd@ LLC = @LlcCmd@ OPT = @OptCmd@ diff --git a/settings.in b/settings.in index df647f1b1d..6bf5156a03 100644 --- a/settings.in +++ b/settings.in @@ -29,6 +29,7 @@ ("target has RTS linker", "@HaskellHaveRTSLinker@"), ("Unregisterised", "@Unregisterised@"), ("LLVM llc command", "@SettingsLlcCommand@"), - ("LLVM opt command", "@SettingsOptCommand@") + ("LLVM opt command", "@SettingsOptCommand@"), + ("LLVM clang command", "@SettingsClangCommand@") ] diff --git a/testsuite/mk/ghc-config.hs b/testsuite/mk/ghc-config.hs index cf550082db..b0278bcfae 100644 --- a/testsuite/mk/ghc-config.hs +++ b/testsuite/mk/ghc-config.hs @@ -27,6 +27,7 @@ main = do getGhcFieldOrDefault fields "GhcDynamic" "GHC Dynamic" "NO" getGhcFieldOrDefault fields "GhcProfiled" "GHC Profiled" "NO" getGhcFieldProgWithDefault fields "AR" "ar command" "ar" + getGhcFieldProgWithDefault fields "CLANG" "LLVM clang command" "clang" getGhcFieldProgWithDefault fields "LLC" "LLVM llc command" "llc" getGhcFieldProgWithDefault fields "TEST_CC" "C compiler command" "gcc" diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 7609dd73ca..d309f6c48a 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -657,7 +657,7 @@ test('T5837', # 2017-02-19 59161648 (x64/Windows) - Unknown # 2017-04-21 54985248 (x64/Windows) - Unknown - (wordsize(64), 52625920, 7)]) + (wordsize(64), 56782344, 7)]) # sample: 3926235424 (amd64/Linux, 15/2/2012) # 2012-10-02 81879216 # 2012-09-20 87254264 amd64/Linux @@ -693,6 +693,7 @@ test('T5837', # 2017-02-20 58648600 amd64/Linux Type-indexed Typeable # 2017-02-28 54151864 amd64/Linux Likely drift due to recent simplifier improvements # 2017-02-25 52625920 amd64/Linux Early inlining patch + # 2017-09-06 56782344 amd64/Linux Drift manifest in unrelated LLVM patch ], compile, ['-freduction-depth=50']) @@ -1019,13 +1020,14 @@ test('T12227', test('T12425', [ only_ways(['optasm']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 127500136, 5), + [(wordsize(64), 134780272, 5), # initial: 125831400 # 2017-01-18: 133380960 Allow top-level string literals in Core # 2017-02-17: 153611448 Type-indexed Typeable # 2017-03-03: 142256192 Share Typeable KindReps # 2017-03-21: 134334800 Unclear # 2017-04-28: 127500136 Remove exponential behaviour in simplifier + # 2017-05-23: 134780272 Addition of llvm-targets in dynflags (D3352) ]), ], compile, diff --git a/utils/llvm-targets/gen-data-layout.sh b/utils/llvm-targets/gen-data-layout.sh new file mode 100755 index 0000000000..315222fe1d --- /dev/null +++ b/utils/llvm-targets/gen-data-layout.sh @@ -0,0 +1,80 @@ +#!/bin/bash +# +# llvm-target generator +# +# Author: Moritz Angermann <moritz.angermann@gmail.com> +# +# This file generates the `llvm-targets` file, which contains the +# data-layout, cpu and attributes for the target. This is done by +# querying `clang` for the data-layout, cpu and attributes based +# on a given target. +# +# To utilize it run it as +# +# $ ./gen-data-layout.sh > llvm-targets +# +# Add missing targets to the list below to have them included in +# llvm-targets file. + +# Target sets +WINDOWS_x86="i386-unknown-windows i686-unknown-windows x86_64-unknown-windows" +LINUX_ARM="arm-unknown-linux-gnueabihf armv6-unknown-linux-gnueabihf armv7-unknown-linux-gnueabihf aarch64-unknown-linux-gnu aarch64-unknown-linux" +LINUX_x86="i386-unknown-linux-gnu i386-unknown-linux x86_64-unknown-linux-gnu x86_64-unknown-linux" +ANDROID="armv7-unknown-linux-androideabi aarch64-unknown-linux-android" +QNX="arm-unknown-nto-qnx-eabi" +MACOS="i386-apple-darwin x86_64-apple-darwin" +IOS="armv7-apple-ios arm64-apple-ios i386-apple-ios x86_64-apple-ios" + +# targets for which to generate the llvm-targets file +TARGETS="${WINDOWS_x86} ${LINUX_ARM} ${LINUX_x86} ${ANDROID} ${QNX} ${MACOS} ${IOS}" + +# given the call to clang -c11 that clang --target -v generates, +# parse the -target-cpu <CPU> and -target-feature <feature> from +# the output. +function get_cpu_and_attr() { + # echo $@ + while [ "$#" -gt 0 ]; do + case "$1" in + -target-cpu) CPU=$2; shift 2;; + -target-feature) ATTR+=("$2"); shift 2;; + *) shift 1;; + esac + done +} + +# first marker to discrimiate the first line being outputted. +FST=1 +# a dummy file to use for the clang invocation. +FILE=_____dummy.c +touch $FILE + +for target in $TARGETS; do + # find the cpu and attributes emitte by clang for the given $target + CPU="" + ATTR=() + args=$(clang --target=$target -S $FILE -o /dev/null -v 2>&1 |grep $FILE) + get_cpu_and_attr $args + + # find the data-layout from the llvm code emitted by clang. + dl=$(clang --target=$target -S $FILE -emit-llvm -o -|grep datalayout |awk -F\ '{ print $4 }') + # GNU and Apple/LLVM can't agree on the aarch64 target. + # aarch64-apple-ios, is understood by autotools but not by LLVM. + # arm64-apple-ios, is understood by LLVM, but not by autotools. + # + # therefore, while we query clang with arm64-apple-ios, we put + # aarch64-apple-ios into the llvm-target list, as that is what + # we have to configure ghc with --target with anyway. Also we + # want to retain the GNU naming for compatibility with libraries + # that use autotools. + if [ "$target" == "arm64-apple-ios" ]; then + target="aarch64-apple-ios" + fi + if [ $FST -eq 1 ]; then + echo "[(\"${target}\", ($dl, \"$CPU\", \"${ATTR[*]}\"))" + FST=0 + else + echo ",(\"${target}\", ($dl, \"$CPU\", \"${ATTR[*]}\"))" + fi +done +rm $FILE +echo "]" |