Rodrigo Mesquita pushed to branch wip/romes/24212 at Glasgow Haskell Compiler / GHC

Commits:

26 changed files:

Changes:

  • compiler/GHC/Driver/DynFlags.hs
    ... ... @@ -145,6 +145,7 @@ import GHC.Foreign (withCString, peekCString)
    145 145
     import qualified Data.Set as Set
    
    146 146
     
    
    147 147
     import qualified GHC.LanguageExtensions as LangExt
    
    148
    +import GHC.Toolchain.Target (Target)
    
    148 149
     
    
    149 150
     -- -----------------------------------------------------------------------------
    
    150 151
     -- DynFlags
    
    ... ... @@ -178,6 +179,7 @@ data DynFlags = DynFlags {
    178 179
       toolSettings      :: {-# UNPACK #-} !ToolSettings,
    
    179 180
       platformMisc      :: {-# UNPACK #-} !PlatformMisc,
    
    180 181
       rawSettings       :: [(String, String)],
    
    182
    +  rawTarget         :: Target,
    
    181 183
       tmpDir            :: TempDir,
    
    182 184
     
    
    183 185
       llvmOptLevel          :: Int,         -- ^ LLVM optimisation level
    
    ... ... @@ -656,6 +658,7 @@ defaultDynFlags mySettings =
    656 658
             targetPlatform = sTargetPlatform mySettings,
    
    657 659
             platformMisc = sPlatformMisc mySettings,
    
    658 660
             rawSettings = sRawSettings mySettings,
    
    661
    +        rawTarget   = sRawTarget mySettings,
    
    659 662
     
    
    660 663
             tmpDir                  = panic "defaultDynFlags: uninitialized tmpDir",
    
    661 664
     
    

  • compiler/GHC/Driver/Session.hs
    ... ... @@ -280,6 +280,9 @@ import GHC.Parser.Lexer (mkParserOpts, initParserState, P(..), ParseResult(..))
    280 280
     
    
    281 281
     import GHC.SysTools.BaseDir ( expandToolDir, expandTopDir )
    
    282 282
     
    
    283
    +import GHC.Toolchain
    
    284
    +import GHC.Toolchain.Program
    
    285
    +
    
    283 286
     import Data.IORef
    
    284 287
     import Control.Arrow ((&&&))
    
    285 288
     import Control.Monad
    
    ... ... @@ -403,6 +406,7 @@ settings dflags = Settings
    403 406
       , sToolSettings = toolSettings dflags
    
    404 407
       , sPlatformMisc = platformMisc dflags
    
    405 408
       , sRawSettings = rawSettings dflags
    
    409
    +  , sRawTarget = rawTarget dflags
    
    406 410
       }
    
    407 411
     
    
    408 412
     pgm_L                 :: DynFlags -> String
    
    ... ... @@ -3454,9 +3458,58 @@ compilerInfo dflags
    3454 3458
           -- Next come the settings, so anything else can be overridden
    
    3455 3459
           -- in the settings file (as "lookup" uses the first match for the
    
    3456 3460
           -- key)
    
    3457
    -    : map (fmap $ expandDirectories (topDir dflags) (toolDir dflags))
    
    3458
    -          (rawSettings dflags)
    
    3459
    -   ++ [("Project version",             projectVersion dflags),
    
    3461
    +     : map (fmap expandDirectories)
    
    3462
    +           (rawSettings dflags)
    
    3463
    +     ++
    
    3464
    +      [("C compiler command", queryCmd $ ccProgram . tgtCCompiler),
    
    3465
    +       ("C compiler flags", queryFlags $ ccProgram . tgtCCompiler),
    
    3466
    +       ("C++ compiler command", queryCmd $ cxxProgram . tgtCxxCompiler),
    
    3467
    +       ("C++ compiler flags", queryFlags $ cxxProgram . tgtCxxCompiler),
    
    3468
    +       ("C compiler link flags", queryFlags $ ccLinkProgram . tgtCCompilerLink),
    
    3469
    +       ("C compiler supports -no-pie", queryBool $ ccLinkSupportsNoPie . tgtCCompilerLink),
    
    3470
    +       ("CPP command", queryCmd $ cppProgram . tgtCPreprocessor),
    
    3471
    +       ("CPP flags", queryFlags $ cppProgram . tgtCPreprocessor),
    
    3472
    +       ("Haskell CPP command", queryCmd $ hsCppProgram . tgtHsCPreprocessor),
    
    3473
    +       ("Haskell CPP flags", queryFlags $ hsCppProgram . tgtHsCPreprocessor),
    
    3474
    +       ("JavaScript CPP command", queryCmdMaybe jsCppProgram tgtJsCPreprocessor),
    
    3475
    +       ("JavaScript CPP flags", queryFlagsMaybe jsCppProgram tgtJsCPreprocessor),
    
    3476
    +       ("C-- CPP command", queryCmd $ cmmCppProgram . tgtCmmCPreprocessor),
    
    3477
    +       ("C-- CPP flags", queryFlags $ cmmCppProgram . tgtCmmCPreprocessor),
    
    3478
    +       ("C-- CPP supports -g0", queryBool $ cmmCppSupportsG0 . tgtCmmCPreprocessor),
    
    3479
    +       ("ld supports compact unwind", queryBool $ ccLinkSupportsCompactUnwind . tgtCCompilerLink),
    
    3480
    +       ("ld supports filelist", queryBool $ ccLinkSupportsFilelist . tgtCCompilerLink),
    
    3481
    +       ("ld supports single module", queryBool $ ccLinkSupportsSingleModule . tgtCCompilerLink),
    
    3482
    +       ("ld is GNU ld", queryBool $ ccLinkIsGnu . tgtCCompilerLink),
    
    3483
    +       ("Merge objects command", queryCmdMaybe mergeObjsProgram tgtMergeObjs),
    
    3484
    +       ("Merge objects flags", queryFlagsMaybe mergeObjsProgram tgtMergeObjs),
    
    3485
    +       ("Merge objects supports response files", queryBool $ maybe False mergeObjsSupportsResponseFiles . tgtMergeObjs),
    
    3486
    +       ("ar command", queryCmd $ arMkArchive . tgtAr),
    
    3487
    +       ("ar flags", queryFlags $ arMkArchive . tgtAr),
    
    3488
    +       ("ar supports at file", queryBool $ arSupportsAtFile . tgtAr),
    
    3489
    +       ("ar supports -L", queryBool $ arSupportsDashL . tgtAr),
    
    3490
    +       ("ranlib command", queryCmdMaybe ranlibProgram tgtRanlib),
    
    3491
    +       ("otool command", queryCmdMaybe id tgtOtool),
    
    3492
    +       ("install_name_tool command", queryCmdMaybe id tgtInstallNameTool),
    
    3493
    +       ("windres command", queryCmd $ fromMaybe (Program "/bin/false" []) . tgtWindres),
    
    3494
    +       ("cross compiling", queryBool (not . tgtLocallyExecutable)),
    
    3495
    +       ("target platform string", query targetPlatformTriple),
    
    3496
    +       ("target os", query (show . archOS_OS . tgtArchOs)),
    
    3497
    +       ("target arch", query (show . archOS_arch . tgtArchOs)),
    
    3498
    +       ("target word size", query $ show . wordSize2Bytes . tgtWordSize),
    
    3499
    +       ("target word big endian", queryBool $ (\case BigEndian -> True; LittleEndian -> False) . tgtEndianness),
    
    3500
    +       ("target has GNU nonexec stack", queryBool tgtSupportsGnuNonexecStack),
    
    3501
    +       ("target has .ident directive", queryBool tgtSupportsIdentDirective),
    
    3502
    +       ("target has subsections via symbols", queryBool tgtSupportsSubsectionsViaSymbols),
    
    3503
    +       ("Unregisterised", queryBool tgtUnregisterised),
    
    3504
    +       ("LLVM target", query tgtLlvmTarget),
    
    3505
    +       ("LLVM llc command", queryCmdMaybe id tgtLlc),
    
    3506
    +       ("LLVM opt command", queryCmdMaybe id tgtOpt),
    
    3507
    +       ("LLVM llvm-as command", queryCmdMaybe id tgtLlvmAs),
    
    3508
    +       ("LLVM llvm-as flags", queryFlagsMaybe id tgtLlvmAs),
    
    3509
    +       ("Tables next to code", queryBool tgtTablesNextToCode),
    
    3510
    +       ("Leading underscore", queryBool tgtSymbolsHaveLeadingUnderscore)
    
    3511
    +      ] ++
    
    3512
    +      [("Project version",             projectVersion dflags),
    
    3460 3513
            ("Project Git commit id",       cProjectGitCommitId),
    
    3461 3514
            ("Project Version Int",         cProjectVersionInt),
    
    3462 3515
            ("Project Patch Level",         cProjectPatchLevel),
    
    ... ... @@ -3513,9 +3566,16 @@ compilerInfo dflags
    3513 3566
         showBool False = "NO"
    
    3514 3567
         platform  = targetPlatform dflags
    
    3515 3568
         isWindows = platformOS platform == OSMinGW32
    
    3516
    -    useInplaceMinGW = toolSettings_useInplaceMinGW $ toolSettings dflags
    
    3517
    -    expandDirectories :: FilePath -> Maybe FilePath -> String -> String
    
    3518
    -    expandDirectories topd mtoold = expandToolDir useInplaceMinGW mtoold . expandTopDir topd
    
    3569
    +    expandDirectories = expandToolDir (toolDir dflags) . expandTopDir (topDir dflags)
    
    3570
    +    query :: (Target -> a) -> a
    
    3571
    +    query f = f (rawTarget dflags)
    
    3572
    +    queryFlags f = query (unwords . map escapeArg . prgFlags . f)
    
    3573
    +    queryCmd f = expandDirectories (query (prgPath . f))
    
    3574
    +    queryBool = showBool . query
    
    3575
    +
    
    3576
    +    queryCmdMaybe, queryFlagsMaybe :: (a -> Program) -> (Target -> Maybe a) -> String
    
    3577
    +    queryCmdMaybe p f = expandDirectories (query (maybe "" (prgPath . p) . f))
    
    3578
    +    queryFlagsMaybe p f = query (maybe "" (unwords . map escapeArg . prgFlags . p) . f)
    
    3519 3579
     
    
    3520 3580
     -- Note [Special unit-ids]
    
    3521 3581
     -- ~~~~~~~~~~~~~~~~~~~~~~~
    
    ... ... @@ -3843,3 +3903,19 @@ updatePlatformConstants dflags mconstants = do
    3843 3903
       let platform1 = (targetPlatform dflags) { platform_constants = mconstants }
    
    3844 3904
       let dflags1   = dflags { targetPlatform = platform1 }
    
    3845 3905
       return dflags1
    
    3906
    +
    
    3907
    +-- ----------------------------------------------------------------------------
    
    3908
    +-- Escape Args helpers
    
    3909
    +-- ----------------------------------------------------------------------------
    
    3910
    +
    
    3911
    +-- | Just like 'GHC.ResponseFile.escapeArg', but it is not exposed from base.
    
    3912
    +escapeArg :: String -> String
    
    3913
    +escapeArg = reverse . foldl' escape []
    
    3914
    +
    
    3915
    +escape :: String -> Char -> String
    
    3916
    +escape cs c
    
    3917
    +  |    isSpace c
    
    3918
    +    || '\\' == c
    
    3919
    +    || '\'' == c
    
    3920
    +    || '"'  == c = c:'\\':cs -- n.b., our caller must reverse the result
    
    3921
    +  | otherwise    = c:cs

  • compiler/GHC/Settings.hs
    ... ... @@ -23,7 +23,6 @@ module GHC.Settings
    23 23
       , sMergeObjsSupportsResponseFiles
    
    24 24
       , sLdIsGnuLd
    
    25 25
       , sGccSupportsNoPie
    
    26
    -  , sUseInplaceMinGW
    
    27 26
       , sArSupportsDashL
    
    28 27
       , sPgm_L
    
    29 28
       , sPgm_P
    
    ... ... @@ -75,6 +74,7 @@ import GHC.Utils.CliOption
    75 74
     import GHC.Utils.Fingerprint
    
    76 75
     import GHC.Platform
    
    77 76
     import GHC.Unit.Types
    
    77
    +import GHC.Toolchain.Target
    
    78 78
     
    
    79 79
     data Settings = Settings
    
    80 80
       { sGhcNameVersion    :: {-# UNPACk #-} !GhcNameVersion
    
    ... ... @@ -87,6 +87,10 @@ data Settings = Settings
    87 87
       -- You shouldn't need to look things up in rawSettings directly.
    
    88 88
       -- They should have their own fields instead.
    
    89 89
       , sRawSettings       :: [(String, String)]
    
    90
    +
    
    91
    +  -- Store the target to print out information about the raw target description
    
    92
    +  -- (e.g. in --info)
    
    93
    +  , sRawTarget         :: Target
    
    90 94
       }
    
    91 95
     
    
    92 96
     data UnitSettings = UnitSettings { unitSettings_baseUnitId :: !UnitId }
    
    ... ... @@ -102,7 +106,6 @@ data ToolSettings = ToolSettings
    102 106
       , toolSettings_mergeObjsSupportsResponseFiles :: Bool
    
    103 107
       , toolSettings_ldIsGnuLd               :: Bool
    
    104 108
       , toolSettings_ccSupportsNoPie         :: Bool
    
    105
    -  , toolSettings_useInplaceMinGW         :: Bool
    
    106 109
       , toolSettings_arSupportsDashL         :: Bool
    
    107 110
       , toolSettings_cmmCppSupportsG0        :: Bool
    
    108 111
     
    
    ... ... @@ -221,8 +224,6 @@ sLdIsGnuLd :: Settings -> Bool
    221 224
     sLdIsGnuLd = toolSettings_ldIsGnuLd . sToolSettings
    
    222 225
     sGccSupportsNoPie :: Settings -> Bool
    
    223 226
     sGccSupportsNoPie = toolSettings_ccSupportsNoPie . sToolSettings
    
    224
    -sUseInplaceMinGW :: Settings -> Bool
    
    225
    -sUseInplaceMinGW = toolSettings_useInplaceMinGW . sToolSettings
    
    226 227
     sArSupportsDashL :: Settings -> Bool
    
    227 228
     sArSupportsDashL = toolSettings_arSupportsDashL . sToolSettings
    
    228 229
     
    

  • compiler/GHC/Settings/IO.hs
    1
    -
    
    1
    +{-# LANGUAGE RecordWildCards #-}
    
    2 2
     {-# LANGUAGE LambdaCase #-}
    
    3 3
     {-# LANGUAGE ScopedTypeVariables #-}
    
    4 4
     
    
    ... ... @@ -16,18 +16,20 @@ import GHC.Utils.CliOption
    16 16
     import GHC.Utils.Fingerprint
    
    17 17
     import GHC.Platform
    
    18 18
     import GHC.Utils.Panic
    
    19
    -import GHC.ResponseFile
    
    20 19
     import GHC.Settings
    
    21 20
     import GHC.SysTools.BaseDir
    
    22 21
     import GHC.Unit.Types
    
    23 22
     
    
    24 23
     import Control.Monad.Trans.Except
    
    25 24
     import Control.Monad.IO.Class
    
    26
    -import Data.Char
    
    27 25
     import qualified Data.Map as Map
    
    28 26
     import System.FilePath
    
    29 27
     import System.Directory
    
    30 28
     
    
    29
    +import GHC.Toolchain.Program
    
    30
    +import GHC.Toolchain
    
    31
    +import GHC.Data.Maybe
    
    32
    +import Data.Bifunctor (Bifunctor(second))
    
    31 33
     
    
    32 34
     data SettingsError
    
    33 35
       = SettingsError_MissingData String
    
    ... ... @@ -44,6 +46,7 @@ initSettings top_dir = do
    44 46
           libexec :: FilePath -> FilePath
    
    45 47
           libexec file = top_dir </> ".." </> "bin" </> file
    
    46 48
           settingsFile = installed "settings"
    
    49
    +      targetFile   = installed $ "targets" </> "default.target"
    
    47 50
     
    
    48 51
           readFileSafe :: FilePath -> ExceptT SettingsError m String
    
    49 52
           readFileSafe path = liftIO (doesFileExist path) >>= \case
    
    ... ... @@ -55,85 +58,72 @@ initSettings top_dir = do
    55 58
         Just s -> pure s
    
    56 59
         Nothing -> throwE $ SettingsError_BadData $
    
    57 60
           "Can't parse " ++ show settingsFile
    
    61
    +  targetStr <- readFileSafe targetFile
    
    62
    +  target <- case maybeReadFuzzy @Target targetStr of
    
    63
    +    Just s -> pure s
    
    64
    +    Nothing -> throwE $ SettingsError_BadData $
    
    65
    +      "Can't parse as Target " ++ show targetFile
    
    58 66
       let mySettings = Map.fromList settingsList
    
    59 67
           getBooleanSetting :: String -> ExceptT SettingsError m Bool
    
    60 68
           getBooleanSetting key = either pgmError pure $
    
    61 69
             getRawBooleanSetting settingsFile mySettings key
    
    62 70
     
    
    63
    -  -- On Windows, by mingw is often distributed with GHC,
    
    64
    -  -- so we look in TopDir/../mingw/bin,
    
    65
    -  -- as well as TopDir/../../mingw/bin for hadrian.
    
    66
    -  -- But we might be disabled, in which we we don't do that.
    
    67
    -  useInplaceMinGW <- getBooleanSetting "Use inplace MinGW toolchain"
    
    68
    -
    
    69 71
       -- see Note [topdir: How GHC finds its files]
    
    70 72
       -- NB: top_dir is assumed to be in standard Unix
    
    71 73
       -- format, '/' separated
    
    72
    -  mtool_dir <- liftIO $ findToolDir useInplaceMinGW top_dir
    
    74
    +  mtool_dir <- liftIO $ findToolDir top_dir
    
    73 75
             -- see Note [tooldir: How GHC finds mingw on Windows]
    
    74 76
     
    
    75
    -    -- Escape 'top_dir' and 'mtool_dir', to make sure we don't accidentally
    
    76
    -    -- introduce unescaped spaces. See #24265 and #25204.
    
    77
    -  let escaped_top_dir = escapeArg top_dir
    
    78
    -      escaped_mtool_dir = fmap escapeArg mtool_dir
    
    79
    -
    
    80
    -      getSetting_raw key = either pgmError pure $
    
    77
    +  let getSetting_raw key = either pgmError pure $
    
    81 78
             getRawSetting settingsFile mySettings key
    
    82 79
           getSetting_topDir top key = either pgmError pure $
    
    83 80
             getRawFilePathSetting top settingsFile mySettings key
    
    84 81
           getSetting_toolDir top tool key =
    
    85
    -        expandToolDir useInplaceMinGW tool <$> getSetting_topDir top key
    
    86
    -
    
    87
    -      getSetting :: String -> ExceptT SettingsError m String
    
    82
    +        expandToolDir tool <$> getSetting_topDir top key
    
    88 83
           getSetting key = getSetting_topDir top_dir key
    
    89
    -      getToolSetting :: String -> ExceptT SettingsError m String
    
    90 84
           getToolSetting key = getSetting_toolDir top_dir mtool_dir key
    
    91
    -      getFlagsSetting :: String -> ExceptT SettingsError m [String]
    
    92
    -      getFlagsSetting key = unescapeArgs <$> getSetting_toolDir escaped_top_dir escaped_mtool_dir key
    
    93
    -        -- Make sure to unescape, as we have escaped top_dir and tool_dir.
    
    85
    +
    
    86
    +      expandDirVars top tool = expandToolDir tool . expandTopDir top
    
    87
    +
    
    88
    +      getToolPath :: (Target -> Program) -> String
    
    89
    +      getToolPath key = expandDirVars top_dir mtool_dir (prgPath . key $ target)
    
    90
    +
    
    91
    +      getMaybeToolPath :: (Target -> Maybe Program) -> String
    
    92
    +      getMaybeToolPath key = getToolPath (fromMaybe (Program "" []) . key)
    
    93
    +
    
    94
    +      getToolFlags :: (Target -> Program) -> [String]
    
    95
    +      getToolFlags key = expandDirVars top_dir mtool_dir <$> (prgFlags . key $ target)
    
    96
    +
    
    97
    +      getTool :: (Target -> Program) -> (String, [String])
    
    98
    +      getTool key = (getToolPath key, getToolFlags key)
    
    94 99
     
    
    95 100
       -- See Note [Settings file] for a little more about this file. We're
    
    96 101
       -- just partially applying those functions and throwing 'Left's; they're
    
    97 102
       -- written in a very portable style to keep ghc-boot light.
    
    98
    -  targetPlatformString <- getSetting_raw "target platform string"
    
    99
    -  cc_prog <- getToolSetting "C compiler command"
    
    100
    -  cxx_prog <- getToolSetting "C++ compiler command"
    
    101
    -  cc_args0 <- getFlagsSetting "C compiler flags"
    
    102
    -  cxx_args <- getFlagsSetting "C++ compiler flags"
    
    103
    -  gccSupportsNoPie <- getBooleanSetting "C compiler supports -no-pie"
    
    104
    -  cmmCppSupportsG0 <- getBooleanSetting "C-- CPP supports -g0"
    
    105
    -  cpp_prog <- getToolSetting "CPP command"
    
    106
    -  cpp_args <- map Option <$> getFlagsSetting "CPP flags"
    
    107
    -  hs_cpp_prog <- getToolSetting "Haskell CPP command"
    
    108
    -  hs_cpp_args <- map Option <$> getFlagsSetting "Haskell CPP flags"
    
    109
    -  js_cpp_prog <- getToolSetting "JavaScript CPP command"
    
    110
    -  js_cpp_args <- map Option <$> getFlagsSetting "JavaScript CPP flags"
    
    111
    -  cmmCpp_prog <- getToolSetting "C-- CPP command"
    
    112
    -  cmmCpp_args <- map Option <$> getFlagsSetting "C-- CPP flags"
    
    113
    -
    
    114
    -  platform <- either pgmError pure $ getTargetPlatform settingsFile mySettings
    
    115
    -
    
    116
    -  let unreg_cc_args = if platformUnregisterised platform
    
    117
    -                      then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
    
    118
    -                      else []
    
    119
    -      cc_args = cc_args0 ++ unreg_cc_args
    
    120
    -
    
    121
    -      -- The extra flags we need to pass gcc when we invoke it to compile .hc code.
    
    122
    -      --
    
    123
    -      -- -fwrapv is needed for gcc to emit well-behaved code in the presence of
    
    124
    -      -- integer wrap around (#952).
    
    125
    -      extraGccViaCFlags = if platformUnregisterised platform
    
    126
    -                            -- configure guarantees cc support these flags
    
    127
    -                            then ["-fwrapv", "-fno-builtin"]
    
    128
    -                            else []
    
    129
    -
    
    130
    -  ldSupportsCompactUnwind <- getBooleanSetting "ld supports compact unwind"
    
    131
    -  ldSupportsFilelist      <- getBooleanSetting "ld supports filelist"
    
    132
    -  ldSupportsSingleModule  <- getBooleanSetting "ld supports single module"
    
    133
    -  mergeObjsSupportsResponseFiles <- getBooleanSetting "Merge objects supports response files"
    
    134
    -  ldIsGnuLd               <- getBooleanSetting "ld is GNU ld"
    
    135
    -  arSupportsDashL         <- getBooleanSetting "ar supports -L"
    
    136
    -
    
    103
    +  targetHasLibm <- getBooleanSetting "target has libm"
    
    104
    +  let
    
    105
    +    (cc_prog, cc_args0)  = getTool (ccProgram . tgtCCompiler)
    
    106
    +    (cxx_prog, cxx_args) = getTool (cxxProgram . tgtCxxCompiler)
    
    107
    +    (cpp_prog, cpp_args) = getTool (cppProgram . tgtCPreprocessor)
    
    108
    +    (hs_cpp_prog, hs_cpp_args) = getTool (hsCppProgram . tgtHsCPreprocessor)
    
    109
    +    (js_cpp_prog, js_cpp_args) = getTool (maybe (Program "" []) jsCppProgram . tgtJsCPreprocessor)
    
    110
    +    (cmmCpp_prog, cmmCpp_args) = getTool (cmmCppProgram . tgtCmmCPreprocessor)
    
    111
    +
    
    112
    +    platform = getTargetPlatform targetHasLibm target
    
    113
    +
    
    114
    +    unreg_cc_args = if platformUnregisterised platform
    
    115
    +                    then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
    
    116
    +                    else []
    
    117
    +    cc_args = cc_args0 ++ unreg_cc_args
    
    118
    +
    
    119
    +    -- The extra flags we need to pass gcc when we invoke it to compile .hc code.
    
    120
    +    --
    
    121
    +    -- -fwrapv is needed for gcc to emit well-behaved code in the presence of
    
    122
    +    -- integer wrap around (#952).
    
    123
    +    extraGccViaCFlags = if platformUnregisterised platform
    
    124
    +                          -- configure guarantees cc support these flags
    
    125
    +                          then ["-fwrapv", "-fno-builtin"]
    
    126
    +                          else []
    
    137 127
     
    
    138 128
       -- The package database is either a relative path to the location of the settings file
    
    139 129
       -- OR an absolute path.
    
    ... ... @@ -148,41 +138,20 @@ initSettings top_dir = do
    148 138
       -- architecture-specific stuff is done when building Config.hs
    
    149 139
       unlit_path <- getToolSetting "unlit command"
    
    150 140
     
    
    151
    -  windres_path <- getToolSetting "windres command"
    
    152
    -  ar_path <- getToolSetting "ar command"
    
    153
    -  otool_path <- getToolSetting "otool command"
    
    154
    -  install_name_tool_path <- getToolSetting "install_name_tool command"
    
    155
    -  ranlib_path <- getToolSetting "ranlib command"
    
    156
    -
    
    157
    -  -- HACK, see setPgmP below. We keep 'words' here to remember to fix
    
    158
    -  -- Config.hs one day.
    
    159
    -
    
    160
    -
    
    161
    -  -- Other things being equal, 'as' and 'ld' are simply 'gcc'
    
    162
    -  cc_link_args <- getFlagsSetting "C compiler link flags"
    
    163
    -  let   as_prog  = cc_prog
    
    164
    -        as_args  = map Option cc_args
    
    165
    -        ld_prog  = cc_prog
    
    166
    -        ld_args  = map Option (cc_args ++ cc_link_args)
    
    167
    -  ld_r_prog <- getToolSetting "Merge objects command"
    
    168
    -  ld_r_args <- getFlagsSetting "Merge objects flags"
    
    169
    -  let ld_r
    
    170
    -        | null ld_r_prog = Nothing
    
    171
    -        | otherwise      = Just (ld_r_prog, map Option ld_r_args)
    
    172
    -
    
    173
    -  llvmTarget <- getSetting_raw "LLVM target"
    
    174
    -
    
    175
    -  -- We just assume on command line
    
    176
    -  lc_prog <- getToolSetting "LLVM llc command"
    
    177
    -  lo_prog <- getToolSetting "LLVM opt command"
    
    178
    -  las_prog <- getToolSetting "LLVM llvm-as command"
    
    179
    -  las_args <- map Option <$> getFlagsSetting "LLVM llvm-as flags"
    
    180
    -
    
    181
    -  let iserv_prog = libexec "ghc-iserv"
    
    141
    +  -- Other things being equal, 'as' is simply 'gcc'
    
    142
    +  let (cc_link, cc_link_args) = getTool (ccLinkProgram . tgtCCompilerLink)
    
    143
    +      as_prog      = cc_prog
    
    144
    +      as_args      = map Option cc_args
    
    145
    +      ld_prog      = cc_link
    
    146
    +      ld_args      = map Option (cc_args ++ cc_link_args)
    
    147
    +      ld_r         = do
    
    148
    +        ld_r_prog <- tgtMergeObjs target
    
    149
    +        let (ld_r_path, ld_r_args) = getTool (mergeObjsProgram . const ld_r_prog)
    
    150
    +        pure (ld_r_path, map Option ld_r_args)
    
    151
    +      iserv_prog   = libexec "ghc-iserv"
    
    182 152
     
    
    183 153
       targetRTSLinkerOnlySupportsSharedLibs <- getBooleanSetting "target RTS linker only supports shared libraries"
    
    184 154
       ghcWithInterpreter <- getBooleanSetting "Use interpreter"
    
    185
    -  useLibFFI <- getBooleanSetting "Use LibFFI"
    
    186 155
     
    
    187 156
       baseUnitId <- getSetting_raw "base unit-id"
    
    188 157
     
    
    ... ... @@ -206,36 +175,38 @@ initSettings top_dir = do
    206 175
           }
    
    207 176
     
    
    208 177
         , sToolSettings = ToolSettings
    
    209
    -      { toolSettings_ldSupportsCompactUnwind = ldSupportsCompactUnwind
    
    210
    -      , toolSettings_ldSupportsFilelist      = ldSupportsFilelist
    
    211
    -      , toolSettings_ldSupportsSingleModule  = ldSupportsSingleModule
    
    212
    -      , toolSettings_mergeObjsSupportsResponseFiles = mergeObjsSupportsResponseFiles
    
    213
    -      , toolSettings_ldIsGnuLd               = ldIsGnuLd
    
    214
    -      , toolSettings_ccSupportsNoPie         = gccSupportsNoPie
    
    215
    -      , toolSettings_useInplaceMinGW         = useInplaceMinGW
    
    216
    -      , toolSettings_arSupportsDashL         = arSupportsDashL
    
    217
    -      , toolSettings_cmmCppSupportsG0        = cmmCppSupportsG0
    
    218
    -
    
    219
    -      , toolSettings_pgm_L   = unlit_path
    
    220
    -      , toolSettings_pgm_P   = (hs_cpp_prog, hs_cpp_args)
    
    221
    -      , toolSettings_pgm_JSP = (js_cpp_prog, js_cpp_args)
    
    222
    -      , toolSettings_pgm_CmmP = (cmmCpp_prog, cmmCpp_args)
    
    223
    -      , toolSettings_pgm_F   = ""
    
    224
    -      , toolSettings_pgm_c   = cc_prog
    
    225
    -      , toolSettings_pgm_cxx = cxx_prog
    
    226
    -      , toolSettings_pgm_cpp = (cpp_prog, cpp_args)
    
    227
    -      , toolSettings_pgm_a   = (as_prog, as_args)
    
    228
    -      , toolSettings_pgm_l   = (ld_prog, ld_args)
    
    229
    -      , toolSettings_pgm_lm  = ld_r
    
    230
    -      , toolSettings_pgm_windres = windres_path
    
    231
    -      , toolSettings_pgm_ar = ar_path
    
    232
    -      , toolSettings_pgm_otool = otool_path
    
    233
    -      , toolSettings_pgm_install_name_tool = install_name_tool_path
    
    234
    -      , toolSettings_pgm_ranlib = ranlib_path
    
    235
    -      , toolSettings_pgm_lo  = (lo_prog,[])
    
    236
    -      , toolSettings_pgm_lc  = (lc_prog,[])
    
    237
    -      , toolSettings_pgm_las = (las_prog, las_args)
    
    238
    -      , toolSettings_pgm_i   = iserv_prog
    
    178
    +      { toolSettings_ldSupportsCompactUnwind = ccLinkSupportsCompactUnwind $ tgtCCompilerLink target
    
    179
    +      , toolSettings_ldSupportsFilelist      = ccLinkSupportsFilelist      $ tgtCCompilerLink target
    
    180
    +      , toolSettings_ldSupportsSingleModule  = ccLinkSupportsSingleModule  $ tgtCCompilerLink target
    
    181
    +      , toolSettings_ldIsGnuLd               = ccLinkIsGnu                 $ tgtCCompilerLink target
    
    182
    +      , toolSettings_ccSupportsNoPie         = ccLinkSupportsNoPie         $ tgtCCompilerLink target
    
    183
    +      , toolSettings_mergeObjsSupportsResponseFiles
    
    184
    +                                      = maybe False mergeObjsSupportsResponseFiles
    
    185
    +                                                         $ tgtMergeObjs target
    
    186
    +      , toolSettings_arSupportsDashL  = arSupportsDashL  $ tgtAr target
    
    187
    +      , toolSettings_cmmCppSupportsG0 = cmmCppSupportsG0 $ tgtCmmCPreprocessor target
    
    188
    +
    
    189
    +      , toolSettings_pgm_L       = unlit_path
    
    190
    +      , toolSettings_pgm_P       = (hs_cpp_prog, map Option hs_cpp_args)
    
    191
    +      , toolSettings_pgm_JSP     = (js_cpp_prog, map Option js_cpp_args)
    
    192
    +      , toolSettings_pgm_CmmP    = (cmmCpp_prog, map Option cmmCpp_args)
    
    193
    +      , toolSettings_pgm_F       = ""
    
    194
    +      , toolSettings_pgm_c       = cc_prog
    
    195
    +      , toolSettings_pgm_cxx     = cxx_prog
    
    196
    +      , toolSettings_pgm_cpp     = (cpp_prog, map Option cpp_args)
    
    197
    +      , toolSettings_pgm_a       = (as_prog, as_args)
    
    198
    +      , toolSettings_pgm_l       = (ld_prog, ld_args)
    
    199
    +      , toolSettings_pgm_lm      = ld_r
    
    200
    +      , toolSettings_pgm_windres = getMaybeToolPath tgtWindres
    
    201
    +      , toolSettings_pgm_ar      = getToolPath (arMkArchive . tgtAr)
    
    202
    +      , toolSettings_pgm_otool   = getMaybeToolPath tgtOtool
    
    203
    +      , toolSettings_pgm_install_name_tool = getMaybeToolPath tgtInstallNameTool
    
    204
    +      , toolSettings_pgm_ranlib  = getMaybeToolPath (fmap ranlibProgram . tgtRanlib)
    
    205
    +      , toolSettings_pgm_lo      = (getMaybeToolPath tgtOpt,[])
    
    206
    +      , toolSettings_pgm_lc      = (getMaybeToolPath tgtLlc,[])
    
    207
    +      , toolSettings_pgm_las     = second (map Option) $
    
    208
    +                                   getTool (fromMaybe (Program "" []) . tgtLlvmAs)
    
    209
    +      , toolSettings_pgm_i       = iserv_prog
    
    239 210
           , toolSettings_opt_L       = []
    
    240 211
           , toolSettings_opt_P       = []
    
    241 212
           , toolSettings_opt_JSP     = []
    
    ... ... @@ -260,65 +231,30 @@ initSettings top_dir = do
    260 231
     
    
    261 232
         , sTargetPlatform = platform
    
    262 233
         , sPlatformMisc = PlatformMisc
    
    263
    -      { platformMisc_targetPlatformString = targetPlatformString
    
    234
    +      { platformMisc_targetPlatformString = targetPlatformTriple target
    
    264 235
           , platformMisc_ghcWithInterpreter = ghcWithInterpreter
    
    265
    -      , platformMisc_libFFI = useLibFFI
    
    266
    -      , platformMisc_llvmTarget = llvmTarget
    
    236
    +      , platformMisc_libFFI = tgtUseLibffiForAdjustors target
    
    237
    +      , platformMisc_llvmTarget = tgtLlvmTarget target
    
    267 238
           , platformMisc_targetRTSLinkerOnlySupportsSharedLibs = targetRTSLinkerOnlySupportsSharedLibs
    
    268 239
           }
    
    269 240
     
    
    270 241
         , sRawSettings    = settingsList
    
    242
    +    , sRawTarget      = target
    
    271 243
         }
    
    272 244
     
    
    273
    -getTargetPlatform
    
    274
    -  :: FilePath     -- ^ Settings filepath (for error messages)
    
    275
    -  -> RawSettings  -- ^ Raw settings file contents
    
    276
    -  -> Either String Platform
    
    277
    -getTargetPlatform settingsFile settings = do
    
    278
    -  let
    
    279
    -    getBooleanSetting = getRawBooleanSetting settingsFile settings
    
    280
    -    readSetting :: (Show a, Read a) => String -> Either String a
    
    281
    -    readSetting = readRawSetting settingsFile settings
    
    282
    -
    
    283
    -  targetArchOS <- getTargetArchOS settingsFile settings
    
    284
    -  targetWordSize <- readSetting "target word size"
    
    285
    -  targetWordBigEndian <- getBooleanSetting "target word big endian"
    
    286
    -  targetLeadingUnderscore <- getBooleanSetting "Leading underscore"
    
    287
    -  targetUnregisterised <- getBooleanSetting "Unregisterised"
    
    288
    -  targetHasGnuNonexecStack <- getBooleanSetting "target has GNU nonexec stack"
    
    289
    -  targetHasIdentDirective <- getBooleanSetting "target has .ident directive"
    
    290
    -  targetHasSubsectionsViaSymbols <- getBooleanSetting "target has subsections via symbols"
    
    291
    -  targetHasLibm <- getBooleanSetting "target has libm"
    
    292
    -  crossCompiling <- getBooleanSetting "cross compiling"
    
    293
    -  tablesNextToCode <- getBooleanSetting "Tables next to code"
    
    294
    -
    
    295
    -  pure $ Platform
    
    296
    -    { platformArchOS    = targetArchOS
    
    297
    -    , platformWordSize  = targetWordSize
    
    298
    -    , platformByteOrder = if targetWordBigEndian then BigEndian else LittleEndian
    
    299
    -    , platformUnregisterised = targetUnregisterised
    
    300
    -    , platformHasGnuNonexecStack = targetHasGnuNonexecStack
    
    301
    -    , platformHasIdentDirective = targetHasIdentDirective
    
    302
    -    , platformHasSubsectionsViaSymbols = targetHasSubsectionsViaSymbols
    
    303
    -    , platformIsCrossCompiling = crossCompiling
    
    304
    -    , platformLeadingUnderscore = targetLeadingUnderscore
    
    305
    -    , platformTablesNextToCode  = tablesNextToCode
    
    245
    +getTargetPlatform :: Bool {-^ Does target have libm -} -> Target -> Platform
    
    246
    +getTargetPlatform targetHasLibm Target{..} = Platform
    
    247
    +    { platformArchOS    = tgtArchOs
    
    248
    +    , platformWordSize  = case tgtWordSize of WS4 -> PW4
    
    249
    +                                              WS8 -> PW8
    
    250
    +    , platformByteOrder = tgtEndianness
    
    251
    +    , platformUnregisterised = tgtUnregisterised
    
    252
    +    , platformHasGnuNonexecStack = tgtSupportsGnuNonexecStack
    
    253
    +    , platformHasIdentDirective = tgtSupportsIdentDirective
    
    254
    +    , platformHasSubsectionsViaSymbols = tgtSupportsSubsectionsViaSymbols
    
    255
    +    , platformIsCrossCompiling = not tgtLocallyExecutable
    
    256
    +    , platformLeadingUnderscore = tgtSymbolsHaveLeadingUnderscore
    
    257
    +    , platformTablesNextToCode  = tgtTablesNextToCode
    
    306 258
         , platformHasLibm = targetHasLibm
    
    307 259
         , platform_constants = Nothing -- will be filled later when loading (or building) the RTS unit
    
    308 260
         }
    309
    -
    
    310
    --- ----------------------------------------------------------------------------
    
    311
    --- Escape Args helpers
    
    312
    --- ----------------------------------------------------------------------------
    
    313
    -
    
    314
    --- | Just like 'GHC.ResponseFile.escapeArg', but it is not exposed from base.
    
    315
    -escapeArg :: String -> String
    
    316
    -escapeArg = reverse . foldl' escape []
    
    317
    -
    
    318
    -escape :: String -> Char -> String
    
    319
    -escape cs c
    
    320
    -  |    isSpace c
    
    321
    -    || '\\' == c
    
    322
    -    || '\'' == c
    
    323
    -    || '"'  == c = c:'\\':cs -- n.b., our caller must reverse the result
    
    324
    -  | otherwise    = c:cs

  • compiler/GHC/SysTools/BaseDir.hs
    ... ... @@ -90,13 +90,10 @@ the build system finds and wires through the toolchain information.
    90 90
     3) The next step is to generate the settings file: The file
    
    91 91
       `cfg/system.config.in` is preprocessed by configure and the output written to
    
    92 92
       `system.config`.  This serves the same purpose as `config.mk` but it rewrites
    
    93
    -  the values that were exported.  As an example `SettingsCCompilerCommand` is
    
    94
    -  rewritten to `settings-c-compiler-command`.
    
    93
    +  the values that were exported.
    
    95 94
     
    
    96 95
       Next up is `src/Oracles/Settings.hs` which makes from some Haskell ADT to
    
    97
    -  the settings `keys` in the `system.config`.  As an example,
    
    98
    -  `settings-c-compiler-command` is mapped to
    
    99
    -  `SettingsFileSetting_CCompilerCommand`.
    
    96
    +  the settings `keys` in the `system.config`.
    
    100 97
     
    
    101 98
       The last part of this is the `generateSettings` in `src/Rules/Generate.hs`
    
    102 99
       which produces the desired settings file out of Hadrian. This is the
    
    ... ... @@ -122,15 +119,13 @@ play nice with the system compiler instead.
    122 119
     -- | Expand occurrences of the @$tooldir@ interpolation in a string
    
    123 120
     -- on Windows, leave the string untouched otherwise.
    
    124 121
     expandToolDir
    
    125
    -  :: Bool -- ^ whether we use the ambient mingw toolchain
    
    126
    -  -> Maybe FilePath -- ^ tooldir
    
    122
    +  :: Maybe FilePath -- ^ tooldir
    
    127 123
       -> String -> String
    
    128 124
     #if defined(mingw32_HOST_OS)
    
    129
    -expandToolDir False (Just tool_dir) s = expandPathVar "tooldir" tool_dir s
    
    130
    -expandToolDir False Nothing         _ = panic "Could not determine $tooldir"
    
    131
    -expandToolDir True  _               s = s
    
    125
    +expandToolDir (Just tool_dir) s = expandPathVar "tooldir" tool_dir s
    
    126
    +expandToolDir Nothing         _ = panic "Could not determine $tooldir"
    
    132 127
     #else
    
    133
    -expandToolDir _ _ s = s
    
    128
    +expandToolDir _ s = s
    
    134 129
     #endif
    
    135 130
     
    
    136 131
     -- | Returns a Unix-format path pointing to TopDir.
    
    ... ... @@ -164,13 +159,13 @@ tryFindTopDir Nothing
    164 159
     -- Returns @Nothing@ when not on Windows.
    
    165 160
     -- When called on Windows, it either throws an error when the
    
    166 161
     -- tooldir can't be located, or returns @Just tooldirpath@.
    
    167
    --- If the distro toolchain is being used we treat Windows the same as Linux
    
    162
    +-- If the distro toolchain is being used, there will be no variables to
    
    163
    +-- substitute for anyway, so this is a no-op.
    
    168 164
     findToolDir
    
    169
    -  :: Bool -- ^ whether we use the ambient mingw toolchain
    
    170
    -  -> FilePath -- ^ topdir
    
    165
    +  :: FilePath -- ^ topdir
    
    171 166
       -> IO (Maybe FilePath)
    
    172 167
     #if defined(mingw32_HOST_OS)
    
    173
    -findToolDir False top_dir = go 0 (top_dir </> "..") []
    
    168
    +findToolDir top_dir = go 0 (top_dir </> "..") []
    
    174 169
       where maxDepth = 3
    
    175 170
             go :: Int -> FilePath -> [FilePath] -> IO (Maybe FilePath)
    
    176 171
             go k path tried
    
    ... ... @@ -183,7 +178,6 @@ findToolDir False top_dir = go 0 (top_dir </> "..") []
    183 178
                   if oneLevel
    
    184 179
                     then return (Just path)
    
    185 180
                     else go (k+1) (path </> "..") tried'
    
    186
    -findToolDir True _ = return Nothing
    
    187 181
     #else
    
    188
    -findToolDir _ _ = return Nothing
    
    182
    +findToolDir _ = return Nothing
    
    189 183
     #endif

  • compiler/ghc.cabal.in
    ... ... @@ -131,6 +131,7 @@ Library
    131 131
                        semaphore-compat,
    
    132 132
                        stm,
    
    133 133
                        rts,
    
    134
    +                   ghc-toolchain,
    
    134 135
                        ghc-boot   == @ProjectVersionMunged@,
    
    135 136
                        ghc-heap   == @ProjectVersionMunged@,
    
    136 137
                        ghci == @ProjectVersionMunged@
    

  • configure.ac
    ... ... @@ -132,6 +132,7 @@ AC_ARG_ENABLE(distro-toolchain,
    132 132
       [FP_CAPITALIZE_YES_NO(["$enableval"], [EnableDistroToolchain])],
    
    133 133
       [EnableDistroToolchain=NO]
    
    134 134
     )
    
    135
    +AC_SUBST([EnableDistroToolchain])
    
    135 136
     
    
    136 137
     if test "$EnableDistroToolchain" = "YES"; then
    
    137 138
       TarballsAutodownload=NO
    
    ... ... @@ -752,8 +753,6 @@ FP_PROG_AR_NEEDS_RANLIB
    752 753
     dnl ** Check to see whether ln -s works
    
    753 754
     AC_PROG_LN_S
    
    754 755
     
    
    755
    -FP_SETTINGS
    
    756
    -
    
    757 756
     dnl ** Find the path to sed
    
    758 757
     AC_PATH_PROGS(SedCmd,gsed sed,sed)
    
    759 758
     
    

  • distrib/configure.ac.in
    ... ... @@ -89,8 +89,9 @@ AC_ARG_ENABLE(distro-toolchain,
    89 89
     [AS_HELP_STRING([--enable-distro-toolchain],
    
    90 90
                     [Do not use bundled Windows toolchain binaries.])],
    
    91 91
       [FP_CAPITALIZE_YES_NO(["$enableval"], [EnableDistroToolchain])],
    
    92
    -  [EnableDistroToolchain=@SettingsUseDistroMINGW@]
    
    92
    +  [EnableDistroToolchain=@EnableDistroToolchain@]
    
    93 93
     )
    
    94
    +AC_SUBST([EnableDistroToolchain])
    
    94 95
     
    
    95 96
     if test "$HostOS" = "mingw32" -a "$EnableDistroToolchain" = "NO"; then
    
    96 97
       FP_SETUP_WINDOWS_TOOLCHAIN([$hardtop/mingw/], [\$\$topdir/../mingw/])
    
    ... ... @@ -384,8 +385,6 @@ fi
    384 385
     
    
    385 386
     AC_SUBST(BaseUnitId)
    
    386 387
     
    
    387
    -FP_SETTINGS
    
    388
    -
    
    389 388
     # We get caught by
    
    390 389
     #     http://savannah.gnu.org/bugs/index.php?1516
    
    391 390
     #     $(eval ...) inside conditionals causes errors
    
    ... ... @@ -418,6 +417,34 @@ AC_OUTPUT
    418 417
     
    
    419 418
     VALIDATE_GHC_TOOLCHAIN([default.target],[default.target.ghc-toolchain])
    
    420 419
     
    
    420
    +if test "$EnableDistroToolchain" = "YES"; then
    
    421
    +    # If the user specified --enable-distro-toolchain then we just use the
    
    422
    +    # executable names, not paths. We do this by finding strings of paths to
    
    423
    +    # programs and keeping the basename only:
    
    424
    +    cp default.target default.target.bak
    
    425
    +
    
    426
    +    while IFS= read -r line; do
    
    427
    +      if echo "$line" | grep -q 'prgPath = "'; then
    
    428
    +        path=$(echo "$line" | sed -E 's/.*prgPath = "([[^"]]+)".*/\1/')
    
    429
    +        base=$(basename "$path")
    
    430
    +        echo "$line" | sed "s|$path|$base|"
    
    431
    +      else
    
    432
    +        echo "$line"
    
    433
    +      fi
    
    434
    +    done < default.target.bak > default.target
    
    435
    +    echo "Applied --enable-distro-toolchain basename substitution to default.target:"
    
    436
    +    cat default.target
    
    437
    +fi
    
    438
    +
    
    439
    +if test "$windows" = YES -a "$EnableDistroToolchain" = "NO"; then
    
    440
    +    # Handle the Windows toolchain installed in FP_SETUP_WINDOWS_TOOLCHAIN.
    
    441
    +    # We need to issue a substitution to use $tooldir,
    
    442
    +    # See Note [tooldir: How GHC finds mingw on Windows]
    
    443
    +    SUBST_TOOLDIR([default.target])
    
    444
    +    echo "Applied tooldir substitution to default.target:"
    
    445
    +    cat default.target
    
    446
    +fi
    
    447
    +
    
    421 448
     rm -Rf acargs acghc-toolchain actmp-ghc-toolchain
    
    422 449
     
    
    423 450
     echo "****************************************************"
    

  • hadrian/bindist/Makefile
    ... ... @@ -85,67 +85,24 @@ WrapperBinsDir=${bindir}
    85 85
     # N.B. this is duplicated from includes/ghc.mk.
    
    86 86
     lib/settings : config.mk
    
    87 87
     	@rm -f $@
    
    88
    -	@echo '[("C compiler command", "$(SettingsCCompilerCommand)")' >> $@
    
    89
    -	@echo ',("C compiler flags", "$(SettingsCCompilerFlags)")' >> $@
    
    90
    -	@echo ',("C++ compiler command", "$(SettingsCxxCompilerCommand)")' >> $@
    
    91
    -	@echo ',("C++ compiler flags", "$(SettingsCxxCompilerFlags)")' >> $@
    
    92
    -	@echo ',("C compiler link flags", "$(SettingsCCompilerLinkFlags)")' >> $@
    
    93
    -	@echo ',("C compiler supports -no-pie", "$(SettingsCCompilerSupportsNoPie)")' >> $@
    
    94
    -	@echo ',("CPP command", "$(SettingsCPPCommand)")' >> $@
    
    95
    -	@echo ',("CPP flags", "$(SettingsCPPFlags)")' >> $@
    
    96
    -	@echo ',("Haskell CPP command", "$(SettingsHaskellCPPCommand)")' >> $@
    
    97
    -	@echo ',("Haskell CPP flags", "$(SettingsHaskellCPPFlags)")' >> $@
    
    98
    -	@echo ',("JavaScript CPP command", "$(SettingsJavaScriptCPPCommand)")' >> $@
    
    99
    -	@echo ',("JavaScript CPP flags", "$(SettingsJavaScriptCPPFlags)")' >> $@
    
    100
    -	@echo ',("C-- CPP command", "$(SettingsCmmCPPCommand)")' >> $@
    
    101
    -	@echo ',("C-- CPP flags", "$(SettingsCmmCPPFlags)")' >> $@
    
    102
    -	@echo ',("C-- CPP supports -g0", "$(SettingsCmmCPPSupportsG0)")' >> $@
    
    103
    -	@echo ',("ld supports compact unwind", "$(LdHasNoCompactUnwind)")' >> $@
    
    104
    -	@echo ',("ld supports filelist", "$(LdHasFilelist)")' >> $@
    
    105
    -	@echo ',("ld supports single module", "$(LdHasSingleModule)")' >> $@
    
    106
    -	@echo ',("ld is GNU ld", "$(LdIsGNULd)")' >> $@
    
    107
    -	@echo ',("Merge objects command", "$(SettingsMergeObjectsCommand)")' >> $@
    
    108
    -	@echo ',("Merge objects flags", "$(SettingsMergeObjectsFlags)")' >> $@
    
    109
    -	@echo ',("Merge objects supports response files", "$(MergeObjsSupportsResponseFiles)")' >> $@
    
    110
    -	@echo ',("ar command", "$(SettingsArCommand)")' >> $@
    
    111
    -	@echo ',("ar flags", "$(ArArgs)")' >> $@
    
    112
    -	@echo ',("ar supports at file", "$(ArSupportsAtFile)")' >> $@
    
    113
    -	@echo ',("ar supports -L", "$(ArSupportsDashL)")' >> $@
    
    114
    -	@echo ',("ranlib command", "$(SettingsRanlibCommand)")' >> $@
    
    115
    -	@echo ',("otool command", "$(SettingsOtoolCommand)")' >> $@
    
    116
    -	@echo ',("install_name_tool command", "$(SettingsInstallNameToolCommand)")' >> $@
    
    117
    -	@echo ',("windres command", "$(SettingsWindresCommand)")' >> $@
    
    118
    -	@echo ',("unlit command", "$$topdir/../bin/$(CrossCompilePrefix)unlit")' >> $@
    
    119
    -	@echo ',("cross compiling", "$(CrossCompiling)")' >> $@
    
    120
    -	@echo ',("target platform string", "$(TARGETPLATFORM)")' >> $@
    
    121
    -	@echo ',("target os", "$(HaskellTargetOs)")' >> $@
    
    88
    +	@echo '[("target os", "$(HaskellTargetOs)")' >> $@
    
    122 89
     	@echo ',("target arch", "$(HaskellTargetArch)")' >> $@
    
    123
    -	@echo ',("target word size", "$(TargetWordSize)")' >> $@
    
    124
    -	@echo ',("target word big endian", "$(TargetWordBigEndian)")' >> $@
    
    125
    -	@echo ',("target has GNU nonexec stack", "$(TargetHasGnuNonexecStack)")' >> $@
    
    126
    -	@echo ',("target has .ident directive", "$(TargetHasIdentDirective)")' >> $@
    
    127
    -	@echo ',("target has subsections via symbols", "$(TargetHasSubsectionsViaSymbols)")' >> $@
    
    128 90
     	@echo ',("target has libm", "$(TargetHasLibm)")' >> $@
    
    129
    -	@echo ',("Unregisterised", "$(GhcUnregisterised)")' >> $@
    
    130
    -	@echo ',("LLVM target", "$(LLVMTarget)")' >> $@
    
    131
    -	@echo ',("LLVM llc command", "$(SettingsLlcCommand)")' >> $@
    
    132
    -	@echo ',("LLVM opt command", "$(SettingsOptCommand)")' >> $@
    
    133
    -	@echo ',("LLVM llvm-as command", "$(SettingsLlvmAsCommand)")' >> $@
    
    134
    -	@echo ',("LLVM llvm-as flags", "$(SettingsLlvmAsFlags)")' >> $@
    
    135
    -	@echo ',("Use inplace MinGW toolchain", "$(SettingsUseDistroMINGW)")' >> $@
    
    136
    -	@echo
    
    91
    +	@echo ',("unlit command", "$$topdir/../bin/$(CrossCompilePrefix)unlit")' >> $@
    
    137 92
     	@echo ',("target RTS linker only supports shared libraries", "$(TargetRTSLinkerOnlySupportsSharedLibs)")' >> $@
    
    138 93
     	@echo ',("Use interpreter", "$(GhcWithInterpreter)")' >> $@
    
    139 94
     	@echo ',("Support SMP", "$(GhcWithSMP)")' >> $@
    
    140 95
     	@echo ',("RTS ways", "$(GhcRTSWays)")' >> $@
    
    141
    -	@echo ',("Tables next to code", "$(TablesNextToCode)")' >> $@
    
    142
    -	@echo ',("Leading underscore", "$(LeadingUnderscore)")' >> $@
    
    143
    -	@echo ',("Use LibFFI", "$(UseLibffiForAdjustors)")' >> $@
    
    144 96
     	@echo ',("RTS expects libdw", "$(GhcRtsWithLibdw)")' >> $@
    
    145 97
     	@echo ',("Relative Global Package DB", "package.conf.d")' >> $@
    
    146 98
     	@echo ',("base unit-id", "$(BaseUnitId)")' >> $@
    
    147 99
     	@echo "]" >> $@
    
    148 100
     
    
    101
    +lib/targets/default.target : config.mk default.target
    
    102
    +	@rm -f $@
    
    103
    +	@echo "Copying the bindist-configured default.target to lib/targets/default.target"
    
    104
    +	cp default.target $@
    
    105
    +
    
    149 106
     # We need to install binaries relative to libraries.
    
    150 107
     BINARIES = $(wildcard ./bin/*)
    
    151 108
     .PHONY: install_bin_libdir
    
    ... ... @@ -167,7 +124,7 @@ install_bin_direct:
    167 124
     	$(INSTALL_PROGRAM) ./bin/* "$(DESTDIR)$(WrapperBinsDir)/"
    
    168 125
     
    
    169 126
     .PHONY: install_lib
    
    170
    -install_lib: lib/settings
    
    127
    +install_lib: lib/settings lib/targets/default.target
    
    171 128
     	@echo "Copying libraries to $(DESTDIR)$(ActualLibsDir)"
    
    172 129
     	$(INSTALL_DIR) "$(DESTDIR)$(ActualLibsDir)"
    
    173 130
     
    

  • hadrian/bindist/config.mk.in
    ... ... @@ -133,7 +133,7 @@ INSTALL_DIR = $(INSTALL) -m 755 -d
    133 133
     CrossCompiling        = @CrossCompiling@
    
    134 134
     CrossCompilePrefix    = @CrossCompilePrefix@
    
    135 135
     GhcUnregisterised     = @Unregisterised@
    
    136
    -EnableDistroToolchain = @SettingsUseDistroMINGW@
    
    136
    +EnableDistroToolchain = @EnableDistroToolchain@
    
    137 137
     BaseUnitId            = @BaseUnitId@
    
    138 138
     
    
    139 139
     # The THREADED_RTS requires `BaseReg` to be in a register and the
    
    ... ... @@ -205,31 +205,3 @@ TargetHasLibm = @TargetHasLibm@
    205 205
     TablesNextToCode = @TablesNextToCode@
    
    206 206
     LeadingUnderscore = @LeadingUnderscore@
    
    207 207
     LlvmTarget = @LlvmTarget@
    208
    -
    
    209
    -SettingsCCompilerCommand = @SettingsCCompilerCommand@
    
    210
    -SettingsCxxCompilerCommand = @SettingsCxxCompilerCommand@
    
    211
    -SettingsCPPCommand = @SettingsCPPCommand@
    
    212
    -SettingsCPPFlags = @SettingsCPPFlags@
    
    213
    -SettingsHaskellCPPCommand = @SettingsHaskellCPPCommand@
    
    214
    -SettingsHaskellCPPFlags = @SettingsHaskellCPPFlags@
    
    215
    -SettingsJavaScriptCPPCommand = @SettingsJavaScriptCPPCommand@
    
    216
    -SettingsJavaScriptCPPFlags = @SettingsJavaScriptCPPFlags@
    
    217
    -SettingsCmmCPPCommand = @SettingsCmmCPPCommand@
    
    218
    -SettingsCmmCPPFlags = @SettingsCmmCPPFlags@
    
    219
    -SettingsCmmCPPSupportsG0 = @SettingsCmmCPPSupportsG0@
    
    220
    -SettingsCCompilerFlags = @SettingsCCompilerFlags@
    
    221
    -SettingsCxxCompilerFlags = @SettingsCxxCompilerFlags@
    
    222
    -SettingsCCompilerLinkFlags = @SettingsCCompilerLinkFlags@
    
    223
    -SettingsCCompilerSupportsNoPie = @SettingsCCompilerSupportsNoPie@
    
    224
    -SettingsMergeObjectsCommand = @SettingsMergeObjectsCommand@
    
    225
    -SettingsMergeObjectsFlags = @SettingsMergeObjectsFlags@
    
    226
    -SettingsArCommand = @SettingsArCommand@
    
    227
    -SettingsOtoolCommand = @SettingsOtoolCommand@
    
    228
    -SettingsInstallNameToolCommand = @SettingsInstallNameToolCommand@
    
    229
    -SettingsRanlibCommand = @SettingsRanlibCommand@
    
    230
    -SettingsWindresCommand = @SettingsWindresCommand@
    
    231
    -SettingsLibtoolCommand = @SettingsLibtoolCommand@
    
    232
    -SettingsLlcCommand = @SettingsLlcCommand@
    
    233
    -SettingsOptCommand = @SettingsOptCommand@
    
    234
    -SettingsLlvmAsCommand = @SettingsLlvmAsCommand@
    
    235
    -SettingsUseDistroMINGW = @SettingsUseDistroMINGW@

  • hadrian/cfg/system.config.in
    ... ... @@ -79,7 +79,7 @@ project-git-commit-id = @ProjectGitCommitId@
    79 79
     # generated by configure, to generated being by the build system. Many of these
    
    80 80
     # might become redundant.
    
    81 81
     # See Note [tooldir: How GHC finds mingw on Windows]
    
    82
    -settings-use-distro-mingw = @SettingsUseDistroMINGW@
    
    82
    +settings-use-distro-mingw = @EnableDistroToolchain@
    
    83 83
     
    
    84 84
     target-has-libm = @TargetHasLibm@
    
    85 85
     
    

  • hadrian/src/Base.hs
    ... ... @@ -151,6 +151,7 @@ ghcLibDeps stage iplace = do
    151 151
             , "llvm-passes"
    
    152 152
             , "ghc-interp.js"
    
    153 153
             , "settings"
    
    154
    +        , "targets" -/- "default.target"
    
    154 155
             , "ghc-usage.txt"
    
    155 156
             , "ghci-usage.txt"
    
    156 157
             , "dyld.mjs"
    

  • hadrian/src/Rules/Generate.hs
    ... ... @@ -10,7 +10,7 @@ import qualified Data.Set as Set
    10 10
     import Base
    
    11 11
     import qualified Context
    
    12 12
     import Expression
    
    13
    -import Hadrian.Oracles.TextFile (lookupSystemConfig)
    
    13
    +import Hadrian.Oracles.TextFile (lookupSystemConfig, getTargetTarget)
    
    14 14
     import Oracles.Flag hiding (arSupportsAtFile, arSupportsDashL)
    
    15 15
     import Oracles.ModuleFiles
    
    16 16
     import Oracles.Setting
    
    ... ... @@ -24,7 +24,6 @@ import Target
    24 24
     import Utilities
    
    25 25
     
    
    26 26
     import GHC.Toolchain as Toolchain hiding (HsCpp(HsCpp))
    
    27
    -import GHC.Toolchain.Program
    
    28 27
     import GHC.Platform.ArchOS
    
    29 28
     import Settings.Program (ghcWithInterpreter)
    
    30 29
     
    
    ... ... @@ -263,6 +262,7 @@ generateRules = do
    263 262
             let prefix = root -/- stageString stage -/- "lib"
    
    264 263
                 go gen file = generate file (semiEmptyTarget (succStage stage)) gen
    
    265 264
             (prefix -/- "settings") %> \out -> go (generateSettings out) out
    
    265
    +        (prefix -/- "targets" -/- "default.target") %> \out -> go (show <$> expr getTargetTarget) out
    
    266 266
     
    
    267 267
       where
    
    268 268
         file <~+ gen = file %> \out -> generate out emptyTarget gen >> makeExecutable out
    
    ... ... @@ -425,7 +425,7 @@ bindistRules = do
    425 425
         , interpolateSetting "LlvmMinVersion" LlvmMinVersion
    
    426 426
         , interpolateVar "LlvmTarget" $ getTarget tgtLlvmTarget
    
    427 427
         , interpolateSetting "ProjectVersion" ProjectVersion
    
    428
    -    , interpolateVar "SettingsUseDistroMINGW" $ lookupSystemConfig "settings-use-distro-mingw"
    
    428
    +    , interpolateVar "EnableDistroToolchain" $ lookupSystemConfig "settings-use-distro-mingw"
    
    429 429
         , interpolateVar "TablesNextToCode" $ yesNo <$> getTarget tgtTablesNextToCode
    
    430 430
         , interpolateVar "TargetHasLibm" $ lookupSystemConfig "target-has-libm"
    
    431 431
         , interpolateVar "TargetPlatform" $ getTarget targetPlatformTriple
    
    ... ... @@ -483,62 +483,14 @@ generateSettings settingsFile = do
    483 483
         let rel_pkg_db = makeRelativeNoSysLink (dropFileName settingsFile) package_db_path
    
    484 484
     
    
    485 485
         settings <- traverse sequence $
    
    486
    -        [ ("C compiler command",   queryTarget ccPath)
    
    487
    -        , ("C compiler flags",     queryTarget ccFlags)
    
    488
    -        , ("C++ compiler command", queryTarget cxxPath)
    
    489
    -        , ("C++ compiler flags",   queryTarget cxxFlags)
    
    490
    -        , ("C compiler link flags",       queryTarget clinkFlags)
    
    491
    -        , ("C compiler supports -no-pie", queryTarget linkSupportsNoPie)
    
    492
    -        , ("CPP command",         queryTarget cppPath)
    
    493
    -        , ("CPP flags",           queryTarget cppFlags)
    
    494
    -        , ("Haskell CPP command", queryTarget hsCppPath)
    
    495
    -        , ("Haskell CPP flags",   queryTarget hsCppFlags)
    
    496
    -        , ("JavaScript CPP command", queryTarget jsCppPath)
    
    497
    -        , ("JavaScript CPP flags", queryTarget jsCppFlags)
    
    498
    -        , ("C-- CPP command", queryTarget cmmCppPath)
    
    499
    -        , ("C-- CPP flags",   queryTarget cmmCppFlags)
    
    500
    -        , ("C-- CPP supports -g0", queryTarget cmmCppSupportsG0')
    
    501
    -        , ("ld supports compact unwind", queryTarget linkSupportsCompactUnwind)
    
    502
    -        , ("ld supports filelist",       queryTarget linkSupportsFilelist)
    
    503
    -        , ("ld supports single module",       queryTarget linkSupportsSingleModule)
    
    504
    -        , ("ld is GNU ld",               queryTarget linkIsGnu)
    
    505
    -        , ("Merge objects command", queryTarget mergeObjsPath)
    
    506
    -        , ("Merge objects flags", queryTarget mergeObjsFlags)
    
    507
    -        , ("Merge objects supports response files", queryTarget mergeObjsSupportsResponseFiles')
    
    508
    -        , ("ar command",          queryTarget arPath)
    
    509
    -        , ("ar flags",            queryTarget arFlags)
    
    510
    -        , ("ar supports at file", queryTarget arSupportsAtFile')
    
    511
    -        , ("ar supports -L",      queryTarget arSupportsDashL')
    
    512
    -        , ("ranlib command",      queryTarget ranlibPath)
    
    513
    -        , ("otool command",       queryTarget otoolPath)
    
    514
    -        , ("install_name_tool command", queryTarget installNameToolPath)
    
    515
    -        , ("windres command", queryTarget (maybe "/bin/false" prgPath . tgtWindres)) -- TODO: /bin/false is not available on many distributions by default, but we keep it as it were before the ghc-toolchain patch. Fix-me.
    
    516
    -        , ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit })))
    
    517
    -        , ("cross compiling", expr $ yesNo <$> flag CrossCompiling)
    
    518
    -        , ("target platform string", queryTarget targetPlatformTriple)
    
    519
    -        , ("target os",        queryTarget (show . archOS_OS . tgtArchOs))
    
    486
    +        [ ("target os",        queryTarget (show . archOS_OS . tgtArchOs))
    
    520 487
             , ("target arch",      queryTarget (show . archOS_arch . tgtArchOs))
    
    521
    -        , ("target word size", queryTarget wordSize)
    
    522
    -        , ("target word big endian",       queryTarget isBigEndian)
    
    523
    -        , ("target has GNU nonexec stack", queryTarget (yesNo . Toolchain.tgtSupportsGnuNonexecStack))
    
    524
    -        , ("target has .ident directive",  queryTarget (yesNo . Toolchain.tgtSupportsIdentDirective))
    
    525
    -        , ("target has subsections via symbols", queryTarget (yesNo . Toolchain.tgtSupportsSubsectionsViaSymbols))
    
    488
    +        , ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit })))
    
    526 489
             , ("target has libm", expr $  lookupSystemConfig "target-has-libm")
    
    527
    -        , ("Unregisterised", queryTarget (yesNo . tgtUnregisterised))
    
    528
    -        , ("LLVM target", queryTarget tgtLlvmTarget)
    
    529
    -        , ("LLVM llc command", queryTarget llcPath)
    
    530
    -        , ("LLVM opt command", queryTarget optPath)
    
    531
    -        , ("LLVM llvm-as command", queryTarget llvmAsPath)
    
    532
    -        , ("LLVM llvm-as flags", queryTarget llvmAsFlags)
    
    533
    -        , ("Use inplace MinGW toolchain", expr $ lookupSystemConfig "settings-use-distro-mingw")
    
    534
    -
    
    535 490
             , ("target RTS linker only supports shared libraries", expr $ yesNo <$> targetRTSLinkerOnlySupportsSharedLibs)
    
    536 491
             , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter (predStage stage))
    
    537 492
             , ("Support SMP", expr $ yesNo <$> targetSupportsSMP)
    
    538 493
             , ("RTS ways", escapeArgs . map show . Set.toList <$> getRtsWays)
    
    539
    -        , ("Tables next to code", queryTarget (yesNo . tgtTablesNextToCode))
    
    540
    -        , ("Leading underscore",  queryTarget (yesNo . tgtSymbolsHaveLeadingUnderscore))
    
    541
    -        , ("Use LibFFI", expr $ yesNo <$> useLibffiForAdjustors)
    
    542 494
             , ("RTS expects libdw", yesNo <$> getFlag UseLibdw)
    
    543 495
             , ("Relative Global Package DB", pure rel_pkg_db)
    
    544 496
             , ("base unit-id", pure base_unit_id)
    
    ... ... @@ -550,40 +502,6 @@ generateSettings settingsFile = do
    550 502
                 ("[" ++ showTuple s)
    
    551 503
                 : ((\s' -> "," ++ showTuple s') <$> ss)
    
    552 504
                 ++ ["]"]
    
    553
    -  where
    
    554
    -    ccPath  = prgPath . ccProgram . tgtCCompiler
    
    555
    -    ccFlags = escapeArgs . prgFlags . ccProgram . tgtCCompiler
    
    556
    -    cxxPath  = prgPath . cxxProgram . tgtCxxCompiler
    
    557
    -    cxxFlags = escapeArgs . prgFlags . cxxProgram . tgtCxxCompiler
    
    558
    -    clinkFlags = escapeArgs . prgFlags . ccLinkProgram . tgtCCompilerLink
    
    559
    -    linkSupportsNoPie = yesNo . ccLinkSupportsNoPie . tgtCCompilerLink
    
    560
    -    cppPath  = prgPath . cppProgram . tgtCPreprocessor
    
    561
    -    cppFlags = escapeArgs . prgFlags . cppProgram . tgtCPreprocessor
    
    562
    -    hsCppPath  = prgPath . hsCppProgram . tgtHsCPreprocessor
    
    563
    -    hsCppFlags = escapeArgs . prgFlags . hsCppProgram . tgtHsCPreprocessor
    
    564
    -    jsCppPath  = maybe "" (prgPath . jsCppProgram) . tgtJsCPreprocessor
    
    565
    -    jsCppFlags = maybe "" (escapeArgs . prgFlags . jsCppProgram) . tgtJsCPreprocessor
    
    566
    -    cmmCppPath  = prgPath . cmmCppProgram . tgtCmmCPreprocessor
    
    567
    -    cmmCppFlags = escapeArgs . prgFlags . cmmCppProgram . tgtCmmCPreprocessor
    
    568
    -    cmmCppSupportsG0' = yesNo . cmmCppSupportsG0 . tgtCmmCPreprocessor
    
    569
    -    mergeObjsPath  = maybe "" (prgPath . mergeObjsProgram) . tgtMergeObjs
    
    570
    -    mergeObjsFlags = maybe "" (escapeArgs . prgFlags . mergeObjsProgram) . tgtMergeObjs
    
    571
    -    linkSupportsSingleModule    = yesNo . ccLinkSupportsSingleModule . tgtCCompilerLink
    
    572
    -    linkSupportsFilelist        = yesNo . ccLinkSupportsFilelist . tgtCCompilerLink
    
    573
    -    linkSupportsCompactUnwind   = yesNo . ccLinkSupportsCompactUnwind . tgtCCompilerLink
    
    574
    -    linkIsGnu                   = yesNo . ccLinkIsGnu . tgtCCompilerLink
    
    575
    -    llcPath = maybe "" prgPath . tgtLlc
    
    576
    -    optPath = maybe "" prgPath . tgtOpt
    
    577
    -    llvmAsPath = maybe "" prgPath . tgtLlvmAs
    
    578
    -    llvmAsFlags = escapeArgs . maybe [] prgFlags . tgtLlvmAs
    
    579
    -    arPath  = prgPath . arMkArchive . tgtAr
    
    580
    -    arFlags = escapeArgs . prgFlags . arMkArchive . tgtAr
    
    581
    -    arSupportsAtFile' = yesNo . arSupportsAtFile . tgtAr
    
    582
    -    arSupportsDashL' = yesNo . arSupportsDashL . tgtAr
    
    583
    -    otoolPath = maybe "" prgPath . tgtOtool
    
    584
    -    installNameToolPath = maybe "" prgPath . tgtInstallNameTool
    
    585
    -    ranlibPath  = maybe "" (prgPath . ranlibProgram) . tgtRanlib
    
    586
    -    mergeObjsSupportsResponseFiles' = maybe "NO" (yesNo . mergeObjsSupportsResponseFiles) . tgtMergeObjs
    
    587 505
     
    
    588 506
     isBigEndian, wordSize :: Toolchain.Target -> String
    
    589 507
     isBigEndian = yesNo . (\case BigEndian -> True; LittleEndian -> False) . tgtEndianness
    

  • libraries/ghc-internal/src/GHC/Internal/ResponseFile.hs
    ... ... @@ -20,7 +20,7 @@
    20 20
     module GHC.Internal.ResponseFile (
    
    21 21
         getArgsWithResponseFiles,
    
    22 22
         unescapeArgs,
    
    23
    -    escapeArgs,
    
    23
    +    escapeArgs, escapeArg,
    
    24 24
         expandResponse
    
    25 25
       ) where
    
    26 26
     
    

  • m4/fp_settings.m4 deleted
    1
    -dnl Note [How we configure the bundled windows toolchain]
    
    2
    -dnl ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    3
    -dnl As per Note [tooldir: How GHC finds mingw on Windows], when using the
    
    4
    -dnl bundled windows toolchain, the GHC settings file must refer to the
    
    5
    -dnl toolchain through a path relative to $tooldir (binary distributions on
    
    6
    -dnl Windows should work without configure, so the paths must be relative to the
    
    7
    -dnl installation). However, hadrian expects the configured toolchain to use
    
    8
    -dnl full paths to the executable.
    
    9
    -dnl
    
    10
    -dnl This is how the bundled windows toolchain is configured, to define the
    
    11
    -dnl toolchain with paths to the executables, while still writing into GHC
    
    12
    -dnl settings the paths relative to $tooldir:
    
    13
    -dnl
    
    14
    -dnl * If using the bundled toolchain, FP_SETUP_WINDOWS_TOOLCHAIN will be invoked
    
    15
    -dnl
    
    16
    -dnl * FP_SETUP_WINDOWS_TOOLCHAIN will set the toolchain variables to paths
    
    17
    -dnl   to the bundled toolchain (e.g. CFLAGS=/full/path/to/mingw/bin/gcc)
    
    18
    -dnl
    
    19
    -dnl * Later on, in FP_SETTINGS, we substitute occurrences of the path to the
    
    20
    -dnl   mingw tooldir by $tooldir (see SUBST_TOOLDIR).
    
    21
    -dnl   The reason is the Settings* variants of toolchain variables are used by the bindist configure to
    
    22
    -dnl   create the settings file, which needs the windows bundled toolchain to be relative to $tooldir.
    
    23
    -dnl
    
    24
    -dnl * Finally, hadrian will also substitute the mingw prefix by $tooldir before writing the toolchain to the settings file (see generateSettings)
    
    25
    -dnl
    
    26
    -dnl The ghc-toolchain program isn't concerned with any of these complications:
    
    27
    -dnl it is passed either the full paths to the toolchain executables, or the bundled
    
    28
    -dnl mingw path is set first on $PATH before invoking it. And ghc-toolchain
    
    29
    -dnl will, as always, output target files with full paths to the executables.
    
    30
    -dnl
    
    31
    -dnl Hadrian accounts for this as it does for the toolchain executables
    
    32
    -dnl configured by configure -- in fact, hadrian doesn't need to know whether
    
    33
    -dnl the toolchain description file was generated by configure or by
    
    34
    -dnl ghc-toolchain.
    
    35
    -
    
    36
    -# SUBST_TOOLDIR
    
    37
    -# ----------------------------------
    
    38
    -# $1 - the variable where to search for occurrences of the path to the
    
    39
    -#      inplace mingw, and update by substituting said occurrences by
    
    40
    -#      the value of $mingw_install_prefix, where the mingw toolchain will be at
    
    41
    -#      install time
    
    42
    -#
    
    43
    -# See Note [How we configure the bundled windows toolchain]
    
    44
    -AC_DEFUN([SUBST_TOOLDIR],
    
    45
    -[
    
    46
    -    dnl and Note [How we configure the bundled windows toolchain]
    
    47
    -    $1=`echo "$$1" | sed 's%'"$mingw_prefix"'%'"$mingw_install_prefix"'%g'`
    
    48
    -])
    
    49
    -
    
    50
    -# FP_SETTINGS
    
    51
    -# ----------------------------------
    
    52
    -# Set the variables used in the settings file
    
    53
    -AC_DEFUN([FP_SETTINGS],
    
    54
    -[
    
    55
    -    SettingsUseDistroMINGW="$EnableDistroToolchain"
    
    56
    -
    
    57
    -    SettingsCCompilerCommand="$CC"
    
    58
    -    SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2"
    
    59
    -    SettingsCxxCompilerCommand="$CXX"
    
    60
    -    SettingsCxxCompilerFlags="$CONF_CXX_OPTS_STAGE2"
    
    61
    -    SettingsCPPCommand="$CPPCmd"
    
    62
    -    SettingsCPPFlags="$CONF_CPP_OPTS_STAGE2"
    
    63
    -    SettingsHaskellCPPCommand="$HaskellCPPCmd"
    
    64
    -    SettingsHaskellCPPFlags="$HaskellCPPArgs"
    
    65
    -    SettingsJavaScriptCPPCommand="$JavaScriptCPPCmd"
    
    66
    -    SettingsJavaScriptCPPFlags="$JavaScriptCPPArgs"
    
    67
    -    SettingsCmmCPPCommand="$CmmCPPCmd"
    
    68
    -    SettingsCmmCPPFlags="$CmmCPPArgs"
    
    69
    -    SettingsCCompilerLinkFlags="$CONF_GCC_LINKER_OPTS_STAGE2"
    
    70
    -    SettingsArCommand="$ArCmd"
    
    71
    -    SettingsRanlibCommand="$RanlibCmd"
    
    72
    -    SettingsMergeObjectsCommand="$MergeObjsCmd"
    
    73
    -    SettingsMergeObjectsFlags="$MergeObjsArgs"
    
    74
    -
    
    75
    -    AS_CASE(
    
    76
    -      ["$CmmCPPSupportsG0"],
    
    77
    -      [True], [SettingsCmmCPPSupportsG0=YES],
    
    78
    -      [False], [SettingsCmmCPPSupportsG0=NO],
    
    79
    -      [AC_MSG_ERROR(Unknown CPPSupportsG0 value $CmmCPPSupportsG0)]
    
    80
    -    )
    
    81
    -
    
    82
    -    if test -z "$WindresCmd"; then
    
    83
    -        SettingsWindresCommand="/bin/false"
    
    84
    -    else
    
    85
    -        SettingsWindresCommand="$WindresCmd"
    
    86
    -    fi
    
    87
    -
    
    88
    -    # LLVM backend tools
    
    89
    -    SettingsLlcCommand="$LlcCmd"
    
    90
    -    SettingsOptCommand="$OptCmd"
    
    91
    -    SettingsLlvmAsCommand="$LlvmAsCmd"
    
    92
    -    SettingsLlvmAsFlags="$LlvmAsFlags"
    
    93
    -
    
    94
    -    if test "$EnableDistroToolchain" = "YES"; then
    
    95
    -        # If the user specified --enable-distro-toolchain then we just use the
    
    96
    -        # executable names, not paths.
    
    97
    -        SettingsCCompilerCommand="$(basename $SettingsCCompilerCommand)"
    
    98
    -        SettingsHaskellCPPCommand="$(basename $SettingsHaskellCPPCommand)"
    
    99
    -        SettingsCmmCPPCommand="$(basename $SettingsCmmCPPCommand)"
    
    100
    -        SettingsJavaScriptCPPCommand="$(basename $SettingsJavaScriptCPPCommand)"
    
    101
    -        SettingsLdCommand="$(basename $SettingsLdCommand)"
    
    102
    -        SettingsMergeObjectsCommand="$(basename $SettingsMergeObjectsCommand)"
    
    103
    -        SettingsArCommand="$(basename $SettingsArCommand)"
    
    104
    -        SettingsWindresCommand="$(basename $SettingsWindresCommand)"
    
    105
    -        SettingsLlcCommand="$(basename $SettingsLlcCommand)"
    
    106
    -        SettingsOptCommand="$(basename $SettingsOptCommand)"
    
    107
    -        SettingsLlvmAsCommand="$(basename $SettingsLlvmAsCommand)"
    
    108
    -    fi
    
    109
    -
    
    110
    -    if test "$windows" = YES -a "$EnableDistroToolchain" = "NO"; then
    
    111
    -        # Handle the Windows toolchain installed in FP_SETUP_WINDOWS_TOOLCHAIN.
    
    112
    -        # We need to issue a substitution to use $tooldir,
    
    113
    -        # See Note [tooldir: How GHC finds mingw on Windows]
    
    114
    -        SUBST_TOOLDIR([SettingsCCompilerCommand])
    
    115
    -        SUBST_TOOLDIR([SettingsCCompilerFlags])
    
    116
    -        SUBST_TOOLDIR([SettingsCxxCompilerCommand])
    
    117
    -        SUBST_TOOLDIR([SettingsCxxCompilerFlags])
    
    118
    -        SUBST_TOOLDIR([SettingsCCompilerLinkFlags])
    
    119
    -        SUBST_TOOLDIR([SettingsCPPCommand])
    
    120
    -        SUBST_TOOLDIR([SettingsCPPFlags])
    
    121
    -        SUBST_TOOLDIR([SettingsHaskellCPPCommand])
    
    122
    -        SUBST_TOOLDIR([SettingsHaskellCPPFlags])
    
    123
    -        SUBST_TOOLDIR([SettingsCmmCPPCommand])
    
    124
    -        SUBST_TOOLDIR([SettingsCmmCPPFlags])
    
    125
    -        SUBST_TOOLDIR([SettingsJavaScriptCPPCommand])
    
    126
    -        SUBST_TOOLDIR([SettingsJavaScriptCPPFlags])
    
    127
    -        SUBST_TOOLDIR([SettingsMergeObjectsCommand])
    
    128
    -        SUBST_TOOLDIR([SettingsMergeObjectsFlags])
    
    129
    -        SUBST_TOOLDIR([SettingsArCommand])
    
    130
    -        SUBST_TOOLDIR([SettingsRanlibCommand])
    
    131
    -        SUBST_TOOLDIR([SettingsWindresCommand])
    
    132
    -        SUBST_TOOLDIR([SettingsLlcCommand])
    
    133
    -        SUBST_TOOLDIR([SettingsOptCommand])
    
    134
    -        SUBST_TOOLDIR([SettingsLlvmAsCommand])
    
    135
    -        SUBST_TOOLDIR([SettingsLlvmAsFlags])
    
    136
    -    fi
    
    137
    -
    
    138
    -    # Mac-only tools
    
    139
    -    SettingsOtoolCommand="$OtoolCmd"
    
    140
    -    SettingsInstallNameToolCommand="$InstallNameToolCmd"
    
    141
    -
    
    142
    -    SettingsCCompilerSupportsNoPie="$CONF_GCC_SUPPORTS_NO_PIE"
    
    143
    -
    
    144
    -    AC_SUBST(SettingsCCompilerCommand)
    
    145
    -    AC_SUBST(SettingsCxxCompilerCommand)
    
    146
    -    AC_SUBST(SettingsCPPCommand)
    
    147
    -    AC_SUBST(SettingsCPPFlags)
    
    148
    -    AC_SUBST(SettingsHaskellCPPCommand)
    
    149
    -    AC_SUBST(SettingsHaskellCPPFlags)
    
    150
    -    AC_SUBST(SettingsCmmCPPCommand)
    
    151
    -    AC_SUBST(SettingsCmmCPPFlags)
    
    152
    -    AC_SUBST(SettingsCmmCPPSupportsG0)
    
    153
    -    AC_SUBST(SettingsJavaScriptCPPCommand)
    
    154
    -    AC_SUBST(SettingsJavaScriptCPPFlags)
    
    155
    -    AC_SUBST(SettingsCCompilerFlags)
    
    156
    -    AC_SUBST(SettingsCxxCompilerFlags)
    
    157
    -    AC_SUBST(SettingsCCompilerLinkFlags)
    
    158
    -    AC_SUBST(SettingsCCompilerSupportsNoPie)
    
    159
    -    AC_SUBST(SettingsMergeObjectsCommand)
    
    160
    -    AC_SUBST(SettingsMergeObjectsFlags)
    
    161
    -    AC_SUBST(SettingsArCommand)
    
    162
    -    AC_SUBST(SettingsRanlibCommand)
    
    163
    -    AC_SUBST(SettingsOtoolCommand)
    
    164
    -    AC_SUBST(SettingsInstallNameToolCommand)
    
    165
    -    AC_SUBST(SettingsWindresCommand)
    
    166
    -    AC_SUBST(SettingsLlcCommand)
    
    167
    -    AC_SUBST(SettingsOptCommand)
    
    168
    -    AC_SUBST(SettingsLlvmAsCommand)
    
    169
    -    AC_SUBST(SettingsLlvmAsFlags)
    
    170
    -    AC_SUBST(SettingsUseDistroMINGW)
    
    171
    -])

  • m4/fp_setup_windows_toolchain.m4
    ... ... @@ -77,6 +77,7 @@ AC_DEFUN([FP_INSTALL_WINDOWS_TOOLCHAIN],[
    77 77
     # $2 the location that the windows toolchain will be installed in relative to the libdir
    
    78 78
     AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[
    
    79 79
     
    
    80
    +    # TODO: UPDATE COMMENT
    
    80 81
         # N.B. The parameters which get plopped in the `settings` file used by the
    
    81 82
         # resulting compiler are computed in `FP_SETTINGS`. Specifically, we use
    
    82 83
         # $$topdir-relative paths instead of fullpaths to the toolchain, by replacing
    

  • m4/subst_tooldir.m4
    1
    +dnl Note [How we configure the bundled windows toolchain]
    
    2
    +dnl ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    3
    +dnl As per Note [tooldir: How GHC finds mingw on Windows], when using the
    
    4
    +dnl bundled windows toolchain, the GHC settings file must refer to the
    
    5
    +dnl toolchain through a path relative to $tooldir (binary distributions on
    
    6
    +dnl Windows should work without configure, so the paths must be relative to the
    
    7
    +dnl installation). However, hadrian expects the configured toolchain to use
    
    8
    +dnl full paths to the executable.
    
    9
    +dnl
    
    10
    +dnl This is how the bundled windows toolchain is configured, to define the
    
    11
    +dnl toolchain with paths to the executables, while still writing into GHC
    
    12
    +dnl settings the paths relative to $tooldir:
    
    13
    +dnl
    
    14
    +dnl * If using the bundled toolchain, FP_SETUP_WINDOWS_TOOLCHAIN will be invoked
    
    15
    +dnl
    
    16
    +dnl * FP_SETUP_WINDOWS_TOOLCHAIN will set the toolchain variables to paths
    
    17
    +dnl   to the bundled toolchain (e.g. CFLAGS=/full/path/to/mingw/bin/gcc)
    
    18
    +dnl
    
    19
    +dnl * Later on, at the end of distrib/configure.ac, we substitute occurrences of the path to the
    
    20
    +dnl   mingw tooldir by $tooldir (see SUBST_TOOLDIR).
    
    21
    +dnl   The reason is the Settings* variants of toolchain variables are used by the bindist configure to
    
    22
    +dnl   create the settings file, which needs the windows bundled toolchain to be relative to $tooldir.
    
    23
    +dnl
    
    24
    +dnl The ghc-toolchain program isn't concerned with any of these complications:
    
    25
    +dnl it is passed either the full paths to the toolchain executables, or the bundled
    
    26
    +dnl mingw path is set first on $PATH before invoking it. And ghc-toolchain
    
    27
    +dnl will, as always, output target files with full paths to the executables.
    
    28
    +dnl
    
    29
    +dnl Hadrian accounts for this as it does for the toolchain executables
    
    30
    +dnl configured by configure -- in fact, hadrian doesn't need to know whether
    
    31
    +dnl the toolchain description file was generated by configure or by
    
    32
    +dnl ghc-toolchain.
    
    33
    +
    
    34
    +# SUBST_TOOLDIR
    
    35
    +# ----------------------------------
    
    36
    +# $1 - the filepath where to search for occurrences of the path to the
    
    37
    +#      inplace mingw, and update by substituting said occurrences by
    
    38
    +#      the value of $mingw_install_prefix, where the mingw toolchain will be at
    
    39
    +#      install time
    
    40
    +#
    
    41
    +# See Note [How we configure the bundled windows toolchain]
    
    42
    +AC_DEFUN([SUBST_TOOLDIR],
    
    43
    +[
    
    44
    +    sed -i.bkp $1 's%'"$mingw_prefix"'%'"$mingw_install_prefix"'%g'
    
    45
    +])

  • mk/hsc2hs.in
    1
    -HSC2HS_C="@SettingsCCompilerFlags@"
    
    1
    +HSC2HS_C="@CONF_CC_OPTS_STAGE2@"
    
    2 2
     
    
    3
    -HSC2HS_L="@SettingsCCompilerLinkFlags@"
    
    3
    +HSC2HS_L="@CONF_GCC_LINKER_OPTS_STAGE2@"
    
    4 4
     
    
    5 5
     tflag="--template=$libdir/template-hsc.h"
    
    6 6
     Iflag="-I$includedir/include/"
    

  • testsuite/tests/ghc-api/T20757.hs
    ... ... @@ -3,4 +3,4 @@ module Main where
    3 3
     import GHC.SysTools.BaseDir
    
    4 4
     
    
    5 5
     main :: IO ()
    
    6
    -main = findToolDir False "/" >>= print
    6
    +main = findToolDir "/" >>= print

  • testsuite/tests/ghc-api/settings-escape/T24265.hs
    ... ... @@ -16,6 +16,13 @@ import System.Environment
    16 16
     import System.IO (hPutStrLn, stderr)
    
    17 17
     import System.Exit (exitWith, ExitCode(ExitFailure))
    
    18 18
     
    
    19
    +import GHC.Toolchain
    
    20
    +import GHC.Toolchain.Program
    
    21
    +import GHC.Toolchain.Tools.Cc
    
    22
    +import GHC.Toolchain.Tools.Cpp
    
    23
    +import GHC.Toolchain.Tools.Cxx
    
    24
    +import GHC.Toolchain.Lens
    
    25
    +
    
    19 26
     -- Precondition: this test case must be executed in a directory with a space.
    
    20 27
     --
    
    21 28
     -- First we get the current settings file and amend it with extra arguments that we *know*
    
    ... ... @@ -30,35 +37,29 @@ main :: IO ()
    30 37
     main = do
    
    31 38
       libdir:_args <- getArgs
    
    32 39
     
    
    33
    -  (rawSettingOpts, originalSettings) <- runGhc (Just libdir) $ do
    
    40
    +  (rawSettingOpts, rawTargetOpts, originalSettings) <- runGhc (Just libdir) $ do
    
    34 41
         dflags <- hsc_dflags <$> getSession
    
    35
    -    pure (rawSettings dflags, settings dflags)
    
    42
    +    pure (rawSettings dflags, rawTarget dflags, settings dflags)
    
    36 43
     
    
    37 44
       top_dir <- makeAbsolute "./ghc-install-folder/lib with spaces"
    
    38 45
     
    
    39
    -  let argsWithSpaces = "\"-some option\" -some\\ other"
    
    40
    -      numberOfExtraArgs = length $ unescapeArgs argsWithSpaces
    
    41
    -      -- These are all options that can have multiple 'String' or 'Option' values.
    
    42
    -      -- We explicitly do not add 'C compiler link flags' here, as 'initSettings'
    
    43
    -      -- already adds the options of "C compiler flags" to this config field.
    
    44
    -      multipleArguments = Set.fromList
    
    45
    -        [ "Haskell CPP flags"
    
    46
    -        , "JavaScript CPP flags"
    
    47
    -        , "C-- CPP flags"
    
    48
    -        , "C compiler flags"
    
    49
    -        , "C++ compiler flags"
    
    50
    -        , "CPP flags"
    
    51
    -        , "Merge objects flags"
    
    46
    +  let argsWithSpaces l = over l (++["-some option", "-some\\ other"])
    
    47
    +      numberOfExtraArgs = 2
    
    48
    +      -- Test it on a handfull of list of flags
    
    49
    +      multipleArguments =
    
    50
    +        [ _tgtHsCpp % _hsCppProg  % _prgFlags -- "Haskell CPP flags"
    
    51
    +        , _tgtCC    % _ccProgram  % _prgFlags -- "C compiler flags"
    
    52
    +        , _tgtCxx   % _cxxProgram % _prgFlags -- "C++ compiler flags"
    
    53
    +        , _tgtCpp   % _cppProg    % _prgFlags -- "CPP flags"
    
    52 54
             ]
    
    53 55
     
    
    54
    -  let rawSettingOptsWithExtraArgs =
    
    55
    -        map (\(name, args) -> if Set.member name multipleArguments
    
    56
    -          then (name, args ++ " " ++ argsWithSpaces)
    
    57
    -          else (name, args)) rawSettingOpts
    
    56
    +      targetWithExtraArgs = foldr argsWithSpaces rawTargetOpts multipleArguments
    
    58 57
     
    
    59 58
       -- write out the modified settings. We try to keep it legible
    
    60 59
       writeFile (top_dir ++ "/settings") $
    
    61
    -    "[" ++ (intercalate "\n," (map show rawSettingOptsWithExtraArgs)) ++ "]"
    
    60
    +    "[" ++ (intercalate "\n," (map show rawSettingOpts)) ++ "]"
    
    61
    +  writeFile (top_dir ++ "/targets/default.target") $
    
    62
    +    show targetWithExtraArgs
    
    62 63
     
    
    63 64
       settingsm <- runExceptT $ initSettings top_dir
    
    64 65
     
    
    ... ... @@ -113,12 +114,6 @@ main = do
    113 114
           -- Setting 'Haskell CPP flags' contains '$topdir' reference.
    
    114 115
           -- Resolving those while containing spaces, should not introduce more options.
    
    115 116
           recordSetting "Haskell CPP flags" (map showOpt . snd . toolSettings_pgm_P . sToolSettings)
    
    116
    -      -- Setting 'JavaScript CPP flags' contains '$topdir' reference.
    
    117
    -      -- Resolving those while containing spaces, should not introduce more options.
    
    118
    -      recordSetting "JavaScript CPP flags" (map showOpt . snd . toolSettings_pgm_JSP . sToolSettings)
    
    119
    -      -- Setting 'C-- CPP flags' contains '$topdir' reference.
    
    120
    -      -- Resolving those while containing spaces, should not introduce more options.
    
    121
    -      recordSetting "C-- CPP flags" (map showOpt . snd . toolSettings_pgm_CmmP . sToolSettings)
    
    122 117
           -- Setting 'C compiler flags' contains strings with spaces.
    
    123 118
           -- GHC should not split these by word.
    
    124 119
           recordSetting "C compiler flags" (toolSettings_opt_c . sToolSettings)
    
    ... ... @@ -133,10 +128,6 @@ main = do
    133 128
           -- Setting 'CPP flags' contains strings with spaces.
    
    134 129
           -- GHC should not split these by word.
    
    135 130
           recordSetting "CPP flags" (map showOpt . snd . toolSettings_pgm_cpp . sToolSettings)
    
    136
    -      -- Setting 'Merge objects flags' contains strings with spaces.
    
    137
    -      -- GHC should not split these by word.
    
    138
    -      -- If 'Nothing', ignore this test, otherwise the same assertion holds as before.
    
    139
    -      recordSettingM "Merge objects flags" (fmap (map showOpt . snd) . toolSettings_pgm_lm . sToolSettings)
    
    140 131
           -- Setting 'C compiler command' contains '$topdir' reference.
    
    141 132
           -- Spaces in the final filepath should not be escaped.
    
    142 133
           recordFpSetting "C compiler" (toolSettings_pgm_c . sToolSettings)

  • testsuite/tests/ghc-api/settings-escape/T24265.stderr
    1 1
     === 'Haskell CPP flags' contains 2 new entries: True
    
    2 2
         Contains spaces: True
    
    3
    -=== 'JavaScript CPP flags' contains 2 new entries: True
    
    4
    -    Contains spaces: True
    
    5
    -=== 'C-- CPP flags' contains 2 new entries: True
    
    6
    -    Contains spaces: True
    
    7 3
     === 'C compiler flags' contains 2 new entries: True
    
    8 4
         Contains spaces: True
    
    9 5
     === 'C compiler link flags' contains 2 new entries: True
    
    ... ... @@ -12,5 +8,4 @@
    12 8
         Contains spaces: True
    
    13 9
     === 'CPP flags' contains 2 new entries: True
    
    14 10
         Contains spaces: True
    
    15
    -=== 'Merge objects flags' contains expected entries: True
    
    16 11
     === FilePath 'C compiler' contains escaped spaces: False

  • testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib with spaces/targets/.gitkeep

  • utils/ghc-toolchain/exe/Main.hs
    ... ... @@ -534,4 +534,3 @@ mkTarget opts = do
    534 534
                        }
    
    535 535
         return t
    
    536 536
     
    537
    ---- ROMES:TODO: fp_settings.m4 in general which I don't think was ported completely (e.g. the basenames and windows llvm-XX and such)

  • utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
    ... ... @@ -7,6 +7,9 @@ module GHC.Toolchain.Target
    7 7
     
    
    8 8
       , WordSize(..), wordSize2Bytes
    
    9 9
     
    
    10
    +    -- ** Lenses
    
    11
    +  , _tgtCC, _tgtCxx, _tgtCpp, _tgtHsCpp
    
    12
    +
    
    10 13
         -- * Re-exports
    
    11 14
       , ByteOrder(..)
    
    12 15
       ) where
    
    ... ... @@ -137,3 +140,29 @@ instance Show Target where
    137 140
         , ", tgtInstallNameTool = " ++ show tgtInstallNameTool
    
    138 141
         , "}"
    
    139 142
         ]
    
    143
    +
    
    144
    +--------------------------------------------------------------------------------
    
    145
    +-- Lenses
    
    146
    +--------------------------------------------------------------------------------
    
    147
    +
    
    148
    +_tgtCC :: Lens Target Cc
    
    149
    +_tgtCC = Lens tgtCCompiler (\x o -> o {tgtCCompiler = x})
    
    150
    +
    
    151
    +_tgtCxx :: Lens Target Cxx
    
    152
    +_tgtCxx = Lens tgtCxxCompiler (\x o -> o {tgtCxxCompiler = x})
    
    153
    +
    
    154
    +_tgtCpp :: Lens Target Cpp
    
    155
    +_tgtCpp = Lens tgtCPreprocessor (\x o -> o {tgtCPreprocessor = x})
    
    156
    +
    
    157
    +_tgtHsCpp :: Lens Target HsCpp
    
    158
    +_tgtHsCpp = Lens tgtHsCPreprocessor (\x o -> o {tgtHsCPreprocessor = x})
    
    159
    +
    
    160
    +_tgtJsCpp :: Lens Target (Maybe JsCpp)
    
    161
    +_tgtJsCpp = Lens tgtJsCPreprocessor (\x o -> o {tgtJsCPreprocessor = x})
    
    162
    +
    
    163
    +_tgtCmmCpp :: Lens Target CmmCpp
    
    164
    +_tgtCmmCpp = Lens tgtCmmCPreprocessor (\x o -> o {tgtCmmCPreprocessor = x})
    
    165
    +
    
    166
    +_tgtMergeObjs :: Lens Target (Maybe MergeObjs)
    
    167
    +_tgtMergeObjs = Lens tgtMergeObjs (\x o -> o {tgtMergeObjs = x})
    
    168
    +

  • utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
    ... ... @@ -5,6 +5,9 @@ module GHC.Toolchain.Tools.Cpp
    5 5
       , Cpp(..), findCpp
    
    6 6
       , JsCpp(..), findJsCpp
    
    7 7
       , CmmCpp(..), findCmmCpp
    
    8
    +
    
    9
    +    -- * Lenses
    
    10
    +  , _cppProg, _hsCppProg, _jsCppProg, _cmmCppProg
    
    8 11
       ) where
    
    9 12
     
    
    10 13
     import Control.Monad
    
    ... ... @@ -188,3 +191,18 @@ findCpp progOpt cc = checking "for C preprocessor" $ do
    188 191
       let cppProgram = addFlagIfNew "-E" cpp2
    
    189 192
       return Cpp{cppProgram}
    
    190 193
     
    
    194
    +--------------------------------------------------------------------------------
    
    195
    +-- Lenses
    
    196
    +--------------------------------------------------------------------------------
    
    197
    +
    
    198
    +_cppProg :: Lens Cpp Program
    
    199
    +_cppProg = Lens cppProgram (\x o -> o{cppProgram = x})
    
    200
    +
    
    201
    +_hsCppProg :: Lens HsCpp Program
    
    202
    +_hsCppProg = Lens hsCppProgram (\x o -> o{hsCppProgram = x})
    
    203
    +
    
    204
    +_jsCppProg :: Lens JsCpp Program
    
    205
    +_jsCppProg = Lens jsCppProgram (\x o -> o{jsCppProgram = x})
    
    206
    +
    
    207
    +_cmmCppProg :: Lens CmmCpp Program
    
    208
    +_cmmCppProg = Lens cmmCppProgram (\x o -> o{cmmCppProgram = x})

  • utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
    ... ... @@ -4,7 +4,7 @@ module GHC.Toolchain.Tools.Cxx
    4 4
         ( Cxx(..)
    
    5 5
         , findCxx
    
    6 6
           -- * Helpful utilities
    
    7
    -    , compileCxx
    
    7
    +    , compileCxx, _cxxProgram
    
    8 8
         ) where
    
    9 9
     
    
    10 10
     import System.FilePath