[Git][ghc/ghc][wip/romes/enable-ghc-toolchain] 6 commits: ghc-toolchain: Parse javascript and ghcjs as a Arch and OS

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Mon Jul 24 14:04:43 UTC 2023



Rodrigo Mesquita pushed to branch wip/romes/enable-ghc-toolchain at Glasgow Haskell Compiler / GHC


Commits:
e5f4f031 by Rodrigo Mesquita at 2023-07-24T14:58:41+01:00
ghc-toolchain: Parse javascript and ghcjs as a Arch and OS

- - - - -
d9d77ef8 by Rodrigo Mesquita at 2023-07-24T14:58:41+01:00
ghc-toolchain: Try the C compiler as a fallback C++ compiler

It's not uncommon for users to specify a particular C compiler but not the C++
compiler.

An example of this is `configure` invoking ghc-toolchain for the HOST
target configuration, but only configuring a CC_STAGE0, not a CXX_STAGE0

We instruct ghc-toolchain to be a bit cleverer here, by trying the C
compiler as a fallback C++ compiler if none is otherwise found. It might
be that the C compiler program is a collection of compilers that also
support C++, such as gcc or clang.

- - - - -
d9a1a0b0 by Rodrigo Mesquita at 2023-07-24T14:58:41+01:00
ghc-toolchain: Fix ranlib option

- - - - -
f986734a by Rodrigo Mesquita at 2023-07-24T14:58:41+01:00
Improve handling of Cc as a fallback

- - - - -
eb3a2a14 by Rodrigo Mesquita at 2023-07-24T15:04:32+01:00
Using more user options

- - - - -
a1d38409 by Rodrigo Mesquita at 2023-07-24T15:04:32+01:00
ghc-toolchain: Configure Cpp and HsCpp correctly when user specifies flags

In ghc-toolchain, we were only /not/ configuring required flags when the
user specified any flags at all for the  of the HsCpp and Cpp tools.

Otherwise, the linker takes into consideration the user specified flags
to determine whether to search for a better linker implementation, but
already configured the remaining GHC and platform-specific flags
regardless of the user options.

Other Tools consider the user options as a baseline for further
configuration (see `findProgram`), so #23689 is not applicable.

Closes #23689

- - - - -


9 changed files:

- configure.ac
- m4/ghc_toolchain.m4
- utils/ghc-toolchain/CHANGELOG.md
- utils/ghc-toolchain/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Program.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs


Changes:

=====================================
configure.ac
=====================================
@@ -49,7 +49,11 @@ USER_CFLAGS="$CFLAGS"
 USER_LDFLAGS="$LDFLAGS"
 USER_LIBS="$LIBS"
 USER_CXXFLAGS="$CXXFLAGS"
-
+dnl The lower-level/not user-facing environment variables that may still be set
+dnl by developers such as in ghc-wasm-meta
+USER_CONF_CC_OPTS_STAGE2="$CONF_CC_OPTS_STAGE2"
+USER_CONF_CXX_OPTS_STAGE2="$CONF_CXX_OPTS_STAGE2"
+USER_CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2"
 
 dnl ----------------------------------------------------------
 dnl ** Find unixy sort and find commands,


=====================================
m4/ghc_toolchain.m4
=====================================
@@ -8,6 +8,18 @@ AC_DEFUN([ADD_GHC_TOOLCHAIN_ARG],
     done
 ])
 
+dnl $1 argument name
+dnl $2 first variable to try
+dnl $3 variable to add if the first variable is empty
+AC_DEFUN([ADD_GHC_TOOLCHAIN_ARG_CHOOSE],
+[
+    if test -z "$2"; then
+        ADD_GHC_TOOLCHAIN_ARG([$1],[$3])
+    else
+        ADD_GHC_TOOLCHAIN_ARG([$1],[$2])
+    fi
+])
+
 AC_DEFUN([ENABLE_GHC_TOOLCHAIN_ARG],
 [
     if test "$2" = "YES"; then
@@ -99,10 +111,10 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN],
     ENABLE_GHC_TOOLCHAIN_ARG([libffi-adjustors], [$UseLibffiForAdjustors])
 
     dnl We store USER_* variants of all user-specified flags to pass them over to ghc-toolchain.
-    ADD_GHC_TOOLCHAIN_ARG([cc-opt], [$USER_CFLAGS])
-    ADD_GHC_TOOLCHAIN_ARG([cc-link-opt], [$USER_LDFLAGS])
+    ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cc-opt], [$USER_CONF_CC_OPTS_STAGE2], [$USER_CFLAGS])
+    ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cc-link-opt], [$USER_CONF_GCC_LINKER_OPTS_STAGE2], [$USER_LDFLAGS])
     ADD_GHC_TOOLCHAIN_ARG([cc-link-opt], [$USER_LIBS])
-    ADD_GHC_TOOLCHAIN_ARG([cxx-opt], [$USER_CXXFLAGS])
+    ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cxx-opt], [$USER_CONF_CXX_OPTS_STAGE2], [$USER_CXXFLAGS])
     ADD_GHC_TOOLCHAIN_ARG([cpp-opt], [$USER_CPP_ARGS])
     ADD_GHC_TOOLCHAIN_ARG([hs-cpp-opt], [$USER_HS_CPP_ARGS])
 


=====================================
utils/ghc-toolchain/CHANGELOG.md
=====================================
@@ -2,4 +2,6 @@
 
 ## Unreleased
 
+* Try the C compiler as a fallback C++ compiler
+* Parse "javascript" and "ghcjs" as a valid Arch and OS
 * First version. See Note [ghc-toolchain overview] in GHC.Toolchain for an overview


=====================================
utils/ghc-toolchain/Main.hs
=====================================
@@ -146,7 +146,7 @@ options =
     , progOpts "cxx" "C++ compiler" _optCxx
     , progOpts "cc-link" "C compiler for linking" _optCcLink
     , progOpts "ar" "ar archiver" _optAr
-    , progOpts "ranlib" "ranlib utility" _optAr
+    , progOpts "ranlib" "ranlib utility" _optRanlib
     , progOpts "nm" "nm archiver" _optNm
     , progOpts "readelf" "readelf utility" _optReadelf
     , progOpts "merge-objs" "linker for merging objects" _optMergeObjs
@@ -314,7 +314,7 @@ mkTarget opts = do
     -- Use Llvm target if specified, otherwise use triple as llvm target
     let tgtLlvmTarget = fromMaybe (optTriple opts) (optLlvmTriple opts)
     cc0 <- findCc tgtLlvmTarget (optCc opts)
-    cxx <- findCxx tgtLlvmTarget (optCxx opts)
+    cxx <- findCxx tgtLlvmTarget (optCxx opts) cc0
     cpp <- findCpp (optCpp opts) cc0
     hsCpp <- findHsCpp (optHsCpp opts) cc0
     (archOs, tgtVendor) <- parseTriple cc0 (optTriple opts)


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs
=====================================
@@ -53,6 +53,7 @@ parseArch cc arch =
       "riscv64" -> pure ArchRISCV64
       "hppa" -> pure ArchUnknown
       "wasm32" -> pure ArchWasm32
+      "javascript" -> pure ArchJavaScript
       _ -> throwE $ "Unknown architecture " ++ arch
 
 parseOs :: String -> M OS
@@ -76,6 +77,7 @@ parseOs os =
       "aix" -> pure OSAIX
       "gnu" -> pure OSHurd
       "wasi" -> pure OSWasi
+      "ghcjs" -> pure OSGhcjs
       _ -> throwE $ "Unknown operating system " ++ os
 
 splitOn :: Char -> String -> [String]


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Program.hs
=====================================
@@ -2,6 +2,7 @@ module GHC.Toolchain.Program
     ( Program(..)
     , _prgPath
     , _prgFlags
+    , addFlagIfNew
       -- * Running programs
     , runProgram
     , callProgram
@@ -10,6 +11,7 @@ module GHC.Toolchain.Program
       -- * Finding 'Program's
     , ProgOpt(..)
     , emptyProgOpt
+    , programFromOpt
     , _poPath
     , _poFlags
     , findProgram
@@ -41,6 +43,13 @@ _prgPath = Lens prgPath (\x o -> o {prgPath = x})
 _prgFlags :: Lens Program [String]
 _prgFlags = Lens prgFlags (\x o -> o {prgFlags = x})
 
+-- | Prepends a flag to a program's flags if the flag is not in the existing flags.
+addFlagIfNew :: String -> Program -> Program
+addFlagIfNew flag prog@(Program path flags)
+  = if flag `elem` flags
+       then prog
+       else Program path (flag:flags)
+
 runProgram :: Program -> [String] -> M ExitCode
 runProgram prog args = do
     logExecute prog args
@@ -98,6 +107,14 @@ _poFlags = Lens poFlags (\x o -> o {poFlags=x})
 emptyProgOpt :: ProgOpt
 emptyProgOpt = ProgOpt Nothing Nothing
 
+-- | Make a @'Program'@ from user specified program options (@'ProgOpt'@),
+-- defaulting to the given path and flags if unspecified in the @'ProgOpt'@.
+programFromOpt :: ProgOpt
+               -> FilePath -- ^ Program path to default to
+               -> [String] -- ^ Program flags to default to
+               -> Program
+programFromOpt userSpec path flags = Program { prgPath = fromMaybe path (poPath userSpec), prgFlags = fromMaybe flags (poFlags userSpec) }
+
 -- | Tries to find the user specified program by path or tries to look for one
 -- in the given list of candidates.
 --


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
=====================================
@@ -23,17 +23,14 @@ newtype HsCpp = HsCpp { hsCppProgram :: Program
 
 findHsCpp :: ProgOpt -> Cc -> M HsCpp
 findHsCpp progOpt cc = checking "for Haskell C preprocessor" $ do
-  -- Use the specified HS CPP or try to find one (candidate is the c compiler)
-  foundHsCppProg <- findProgram "Haskell C preprocessor" progOpt [takeFileName $ prgPath $ ccProgram cc]
-  case poFlags progOpt of
-    -- If the user specified HS CPP flags don't second-guess them
-    Just _ -> return HsCpp{hsCppProgram=foundHsCppProg}
-    -- Otherwise, configure the HS CPP flags for this CPP program
-    Nothing -> do
-      let rawHsCppProgram = over _prgFlags (["-E"]++) foundHsCppProg
-      hppArgs <- findHsCppArgs rawHsCppProgram
-      let hsCppProgram = over _prgFlags (++hppArgs) rawHsCppProgram
-      return HsCpp{hsCppProgram}
+  -- Use the specified Hs Cpp or try to use the c compiler
+  foundHsCppProg <- findProgram "Haskell C preprocessor" progOpt [] <|> pure (programFromOpt progOpt (prgPath $ ccProgram cc) [])
+  -- Always add the -E flag to the CPP, regardless of the user options
+  let rawHsCppProgram = addFlagIfNew "-E" foundHsCppProg
+  -- Always try to add the Haskell-specific CPP flags, regardless of the user options
+  hppArgs <- findHsCppArgs rawHsCppProgram
+  let hsCppProgram = over _prgFlags (++hppArgs) rawHsCppProgram
+  return HsCpp{hsCppProgram}
 
 -- | Given a C preprocessor, figure out how it should be invoked to preprocess
 -- Haskell source.
@@ -61,13 +58,9 @@ findHsCppArgs cpp = withTempDir $ \dir -> do
 
 findCpp :: ProgOpt -> Cc -> M Cpp
 findCpp progOpt cc = checking "for C preprocessor" $ do
-  -- Use the specified CPP or try to find one (candidate is the c compiler)
-  foundCppProg <- findProgram "C preprocessor" progOpt [prgPath $ ccProgram cc]
-  case poFlags progOpt of
-    -- If the user specified CPP flags don't second-guess them
-    Just _ -> return Cpp{cppProgram=foundCppProg}
-    -- Otherwise, configure the CPP flags for this CPP program
-    Nothing -> do
-      let cppProgram = over _prgFlags (["-E"]++) foundCppProg
-      return Cpp{cppProgram}
+  -- Use the specified CPP or try to use the c compiler
+  foundCppProg <- findProgram "C preprocessor" progOpt [] <|> pure (programFromOpt progOpt (prgPath $ ccProgram cc) [])
+  -- Always add the -E flag to the CPP, regardless of the user options
+  let cppProgram = addFlagIfNew "-E" foundCppProg
+  return Cpp{cppProgram}
 


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
=====================================
@@ -11,6 +11,7 @@ import System.FilePath
 import GHC.Toolchain.Prelude
 import GHC.Toolchain.Program
 import GHC.Toolchain.Utils
+import GHC.Toolchain.Tools.Cc
 
 newtype Cxx = Cxx { cxxProgram :: Program
                   }
@@ -20,10 +21,12 @@ _cxxProgram :: Lens Cxx Program
 _cxxProgram = Lens cxxProgram (\x o -> o{cxxProgram=x})
 
 findCxx :: String -- ^ The llvm target to use if Cc supports --target
-        -> ProgOpt -> M Cxx
-findCxx target progOpt = checking "for C++ compiler" $ do
+        -> ProgOpt -- ^ A user specified C++ compiler
+        -> Cc      -- ^ The C compiler, to try as a fallback C++ compiler if we can't find one.
+        -> M Cxx
+findCxx target progOpt cc = checking "for C++ compiler" $ do
     -- TODO: We use the search order in configure, but there could be a more optimal one
-    cxxProgram <- findProgram "C++ compiler" progOpt ["g++", "clang++", "c++"]
+    cxxProgram <- findProgram "C++ compiler" progOpt ["g++", "clang++", "c++"] <|> pure (programFromOpt progOpt (prgPath $ ccProgram cc) [])
     cxx        <- cxxSupportsTarget target Cxx{cxxProgram}
     checkCxxWorks cxx
     return cxx


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
=====================================
@@ -46,8 +46,8 @@ findCcLink :: String -- ^ The llvm target to use if CcLink supports --target
            -> Bool   -- ^ Whether we should search for a more efficient linker
            -> ArchOS -> Cc -> Maybe Readelf -> M CcLink
 findCcLink target progOpt ldOverride archOs cc readelf = checking "for C compiler for linking command" $ do
-  -- Use the specified linker or try to find one
-  rawCcLink <- findProgram "C compiler for linking" progOpt [takeFileName $ prgPath $ ccProgram cc]
+  -- Use the specified linker or try using the C compiler
+  rawCcLink <- findProgram "C compiler for linking" progOpt [] <|> pure (programFromOpt progOpt (prgPath $ ccProgram cc) [])
   ccLinkProgram <- case poFlags progOpt of
                      Just _ ->
                          -- If the user specified linker flags don't second-guess them



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/58a37221f70f573bf317d006cb9ca571cdb26dec...a1d38409fcdb951af7613aae1dc7fb81cadb66f2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/58a37221f70f573bf317d006cb9ca571cdb26dec...a1d38409fcdb951af7613aae1dc7fb81cadb66f2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230724/eea428b7/attachment-0001.html>


More information about the ghc-commits mailing list