[Git][ghc/ghc][wip/T16738] 2 commits: gitlab-ci: Disable shallow clones

Ben Gamari gitlab at gitlab.haskell.org
Sat Jun 8 18:16:57 UTC 2019



Ben Gamari pushed to branch wip/T16738 at Glasgow Haskell Compiler / GHC


Commits:
b2f106f5 by Ben Gamari at 2019-06-08T18:02:02Z
gitlab-ci: Disable shallow clones

Previously we were passing `--unshallow` to `git fetch` in the linting
rules to ensure that the base commit which we were linting with respect
to was available. However, this breaks due to GitLab's re-use of
working directories since `git fetch --unshallow` fails on a repository
which is not currently shallow.

Given that `git fetch --unshallow` circumvents the efficiencies provided
by shallow clones anyways, let's just disable them entirely.

There is no documented way to do disable shallow clones but on checking
the GitLab implementation it seems that setting `GIT_DEPTH=0` should do
the trick.

- - - - -
0f4169ae by Ben Gamari at 2019-06-08T18:16:54Z
Maintain separate flags for C++ compiler invocations

Previously we would pass flags intended for the C compiler to the C++
compiler (see #16738). This would cause, for instance, `-std=gnu99` to
be passed to the C++ compiler, causing spurious test failures. Fix this
by maintaining a separate set of flags for C++ compilation invocations.

- - - - -


14 changed files:

- .gitlab-ci.yml
- aclocal.m4
- compiler/ghci/Linker.hs
- compiler/main/DynFlags.hs
- compiler/main/Settings.hs
- compiler/main/SysTools.hs
- compiler/main/SysTools/Info.hs
- compiler/main/SysTools/Tasks.hs
- compiler/main/ToolSettings.hs
- hadrian/cfg/system.config.in
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- includes/ghc.mk
- mk/config.mk.in


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -8,6 +8,9 @@ variables:
   # .gitlab/win32-init.sh.
   WINDOWS_TOOLCHAIN_VERSION: 1
 
+  # Disable shallow clones; they break our linting rules
+  GIT_DEPTH: 0
+
 before_script:
   - python3 .gitlab/fix-submodules.py
   - git submodule sync --recursive
@@ -52,13 +55,7 @@ ghc-linters:
   stage: lint
   image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV"
   script:
-    # Note [Unshallow clone for linting]
-    # ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-    # GitLab creates a shallow clone which means that we may not have the base
-    # commit of the MR being tested (e.g. if the MR is quite old), causing `git
-    # merge-base` to fail.  Passing `--unshallow` to `git fetch` ensures that
-    # we have the entire history.
-    - git fetch --unshallow "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
+    - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
     - base="$(git merge-base FETCH_HEAD $CI_COMMIT_SHA)"
     - "echo Linting changes between $base..$CI_COMMIT_SHA"
     #    - validate-commit-msg .git $(git rev-list $base..$CI_COMMIT_SHA)
@@ -80,8 +77,7 @@ ghc-linters:
   stage: lint
   image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV"
   script:
-    # See Note [Unshallow clone for linting]
-    - git fetch --unshallow "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
+    - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
     - base="$(git merge-base FETCH_HEAD $CI_COMMIT_SHA)"
     - "echo Linting changes between $base..$CI_COMMIT_SHA"
     - submodchecker .git $(git rev-list $base..$CI_COMMIT_SHA)


=====================================
aclocal.m4
=====================================
@@ -511,6 +511,7 @@ AC_DEFUN([FP_SETTINGS],
     then
         SettingsCCompilerCommand="$(basename $CC)"
         SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2"
+        SettingsCxxCompilerFlags="$CONF_CXX_OPTS_STAGE2"
         SettingsHaskellCPPCommand="$(basename $HaskellCPPCmd)"
         SettingsHaskellCPPFlags="$HaskellCPPArgs"
         SettingsLdCommand="$(basename $LdCmd)"
@@ -564,6 +565,7 @@ AC_DEFUN([FP_SETTINGS],
       SettingsOptCommand="$OptCmd"
     fi
     SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2"
+    SettingsCxxCompilerFlags="$CONF_CXX_OPTS_STAGE2"
     SettingsCCompilerLinkFlags="$CONF_GCC_LINKER_OPTS_STAGE2"
     SettingsCCompilerSupportsNoPie="$CONF_GCC_SUPPORTS_NO_PIE"
     SettingsLdFlags="$CONF_LD_LINKER_OPTS_STAGE2"
@@ -571,6 +573,7 @@ AC_DEFUN([FP_SETTINGS],
     AC_SUBST(SettingsHaskellCPPCommand)
     AC_SUBST(SettingsHaskellCPPFlags)
     AC_SUBST(SettingsCCompilerFlags)
+    AC_SUBST(SettingsCxxCompilerFlags)
     AC_SUBST(SettingsCCompilerLinkFlags)
     AC_SUBST(SettingsCCompilerSupportsNoPie)
     AC_SUBST(SettingsLdCommand)


=====================================
compiler/ghci/Linker.hs
=====================================
@@ -343,7 +343,7 @@ linkCmdLineLibs' hsc_env pls =
 
       -- Add directories to library search paths, this only has an effect
       -- on Windows. On Unix OSes this function is a NOP.
-      let all_paths = let paths = takeDirectory (fst $ pgm_c dflags)
+      let all_paths = let paths = takeDirectory (pgm_c dflags)
                                 : framework_paths
                                ++ lib_paths_base
                                ++ [ takeDirectory dll | DLLPath dll <- libspecs ]


=====================================
compiler/main/DynFlags.hs
=====================================
@@ -1420,7 +1420,7 @@ pgm_P                 :: DynFlags -> (String,[Option])
 pgm_P dflags = toolSettings_pgm_P $ toolSettings dflags
 pgm_F                 :: DynFlags -> String
 pgm_F dflags = toolSettings_pgm_F $ toolSettings dflags
-pgm_c                 :: DynFlags -> (String,[Option])
+pgm_c                 :: DynFlags -> String
 pgm_c dflags = toolSettings_pgm_c $ toolSettings dflags
 pgm_a                 :: DynFlags -> (String,[Option])
 pgm_a dflags = toolSettings_pgm_a $ toolSettings dflags
@@ -3048,7 +3048,7 @@ dynamic_flags_deps = [
       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_F   = f }
   , make_ord_flag defFlag "pgmc"
       $ hasArg $ \f -> alterToolSettings $ \s -> s
-         { toolSettings_pgm_c   = (f,[])
+         { toolSettings_pgm_c   = f
          , -- Don't pass -no-pie with -pgmc
            -- (see #15319)
            toolSettings_ccSupportsNoPie = False


=====================================
compiler/main/Settings.hs
=====================================
@@ -119,7 +119,7 @@ sPgm_P :: Settings -> (String, [Option])
 sPgm_P = toolSettings_pgm_P . sToolSettings
 sPgm_F :: Settings -> String
 sPgm_F = toolSettings_pgm_F . sToolSettings
-sPgm_c :: Settings -> (String, [Option])
+sPgm_c :: Settings -> String
 sPgm_c = toolSettings_pgm_c . sToolSettings
 sPgm_a :: Settings -> (String, [Option])
 sPgm_a = toolSettings_pgm_a . sToolSettings


=====================================
compiler/main/SysTools.hs
=====================================
@@ -194,17 +194,18 @@ initSysTools top_dir
        -- It would perhaps be nice to be able to override this
        -- with the settings file, but it would be a little fiddly
        -- to make that possible, so for now you can't.
-       gcc_prog <- getToolSetting "C compiler command"
-       gcc_args_str <- getSetting "C compiler flags"
+       cc_prog <- getToolSetting "C compiler command"
+       cc_args_str <- getSetting "C compiler flags"
+       cxx_args_str <- getSetting "C++ compiler flags"
        gccSupportsNoPie <- getBooleanSetting "C compiler supports -no-pie"
        cpp_prog <- getToolSetting "Haskell CPP command"
        cpp_args_str <- getSetting "Haskell CPP flags"
-       let unreg_gcc_args = if targetUnregisterised
-                            then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
-                            else []
-           cpp_args= map Option (words cpp_args_str)
-           gcc_args = map Option (words gcc_args_str
-                               ++ unreg_gcc_args)
+       let unreg_cc_args = if targetUnregisterised
+                           then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
+                           else []
+           cpp_args = map Option (words cpp_args_str)
+           cc_args  = words cc_args_str ++ unreg_cc_args
+           cxx_args = words cxx_args_str
        ldSupportsCompactUnwind <- getBooleanSetting "ld supports compact unwind"
        ldSupportsBuildId       <- getBooleanSetting "ld supports build-id"
        ldSupportsFilelist      <- getBooleanSetting "ld supports filelist"
@@ -236,11 +237,11 @@ initSysTools top_dir
 
 
        -- Other things being equal, as and ld are simply gcc
-       gcc_link_args_str <- getSetting "C compiler link flags"
-       let   as_prog  = gcc_prog
-             as_args  = gcc_args
-             ld_prog  = gcc_prog
-             ld_args  = gcc_args ++ map Option (words gcc_link_args_str)
+       cc_link_args_str <- getSetting "C compiler link flags"
+       let   as_prog  = cc_prog
+             as_args  = map Option cc_args
+             ld_prog  = cc_prog
+             ld_args  = map Option (cc_args ++ words cc_link_args_str)
 
        -- We just assume on command line
        lc_prog <- getSetting "LLVM llc command"
@@ -308,7 +309,7 @@ initSysTools top_dir
            , toolSettings_pgm_L   = unlit_path
            , toolSettings_pgm_P   = (cpp_prog, cpp_args)
            , toolSettings_pgm_F   = ""
-           , toolSettings_pgm_c   = (gcc_prog, gcc_args)
+           , toolSettings_pgm_c   = cc_prog
            , toolSettings_pgm_a   = (as_prog, as_args)
            , toolSettings_pgm_l   = (ld_prog, ld_args)
            , toolSettings_pgm_dll = (mkdll_prog,mkdll_args)
@@ -325,8 +326,8 @@ initSysTools top_dir
            , toolSettings_opt_P       = []
            , toolSettings_opt_P_fingerprint = fingerprint0
            , toolSettings_opt_F       = []
-           , toolSettings_opt_c       = []
-           , toolSettings_opt_cxx     = []
+           , toolSettings_opt_c       = cc_args
+           , toolSettings_opt_cxx     = cxx_args
            , toolSettings_opt_a       = []
            , toolSettings_opt_l       = []
            , toolSettings_opt_windres = []


=====================================
compiler/main/SysTools/Info.hs
=====================================
@@ -219,7 +219,7 @@ getCompilerInfo dflags = do
 -- See Note [Run-time linker info].
 getCompilerInfo' :: DynFlags -> IO CompilerInfo
 getCompilerInfo' dflags = do
-  let (pgm,_) = pgm_c dflags
+  let pgm = pgm_c dflags
       -- Try to grab the info from the process output.
       parseCompilerInfo _stdo stde _exitc
         -- Regular GCC


=====================================
compiler/main/SysTools/Tasks.hs
=====================================
@@ -62,9 +62,9 @@ runPp dflags args =   do
 -- | Run compiler of C-like languages and raw objects (such as gcc or clang).
 runCc :: Maybe ForeignSrcLang -> DynFlags -> [Option] -> IO ()
 runCc mLanguage dflags args =   do
-  let (p,args0) = pgm_c dflags
+  let p = pgm_c dflags
       args1 = map Option userOpts
-      args2 = args0 ++ languageOptions ++ args ++ args1
+      args2 = languageOptions ++ args ++ args1
       -- We take care to pass -optc flags in args1 last to ensure that the
       -- user can override flags passed by GHC. See #14452.
   mb_env <- getGccEnv args2
@@ -126,12 +126,16 @@ runCc mLanguage dflags args =   do
   -- -x c option.
   (languageOptions, userOpts) = case mLanguage of
     Nothing -> ([], userOpts_c)
-    Just language -> ([Option "-x", Option languageName], opts) where
-      (languageName, opts) = case language of
-        LangCxx    -> ("c++",           userOpts_cxx)
-        LangObjc   -> ("objective-c",   userOpts_c)
-        LangObjcxx -> ("objective-c++", userOpts_cxx)
-        _          -> ("c",             userOpts_c)
+    Just language -> ([Option "-x", Option languageName], opts)
+      where
+        s = settings dflags
+        (languageName, opts) = case language of
+          LangC      -> ("c",             sOpt_c s ++ userOpts_c)
+          LangCxx    -> ("c++",           sOpt_cxx s ++ userOpts_cxx)
+          LangObjc   -> ("objective-c",   userOpts_c)
+          LangObjcxx -> ("objective-c++", userOpts_cxx)
+          LangAsm    -> ("assembler",     [])
+          RawObject  -> ("c",             []) -- claim C for lack of a better idea
   userOpts_c   = getOpts dflags opt_c
   userOpts_cxx = getOpts dflags opt_cxx
 
@@ -333,7 +337,8 @@ runMkDLL dflags args = do
 
 runWindres :: DynFlags -> [Option] -> IO ()
 runWindres dflags args = do
-  let (gcc, gcc_args) = pgm_c dflags
+  let cc = pgm_c dflags
+      cc_args = map Option (sOpt_c (settings dflags))
       windres = pgm_windres dflags
       opts = map Option (getOpts dflags opt_windres)
       quote x = "\"" ++ x ++ "\""
@@ -341,8 +346,7 @@ runWindres dflags args = do
               -- spaces then windres fails to run gcc. We therefore need
               -- to tell it what command to use...
               Option ("--preprocessor=" ++
-                      unwords (map quote (gcc :
-                                          map showOpt gcc_args ++
+                      unwords (map quote (cc :
                                           map showOpt opts ++
                                           ["-E", "-xc", "-DRC_INVOKED"])))
               -- ...but if we do that then if windres calls popen then
@@ -351,7 +355,7 @@ runWindres dflags args = do
               -- See #1828.
             : Option "--use-temp-file"
             : args
-  mb_env <- getGccEnv gcc_args
+  mb_env <- getGccEnv cc_args
   runSomethingFiltered dflags id "Windres" windres args' Nothing mb_env
 
 touch :: DynFlags -> String -> String -> IO ()


=====================================
compiler/main/ToolSettings.hs
=====================================
@@ -22,7 +22,7 @@ data ToolSettings = ToolSettings
   , toolSettings_pgm_L       :: String
   , toolSettings_pgm_P       :: (String, [Option])
   , toolSettings_pgm_F       :: String
-  , toolSettings_pgm_c       :: (String, [Option])
+  , toolSettings_pgm_c       :: String
   , toolSettings_pgm_a       :: (String, [Option])
   , toolSettings_pgm_l       :: (String, [Option])
   , toolSettings_pgm_dll     :: (String, [Option])


=====================================
hadrian/cfg/system.config.in
=====================================
@@ -126,6 +126,7 @@ settings-c-compiler-command = @SettingsCCompilerCommand@
 settings-haskell-cpp-command = @SettingsHaskellCPPCommand@
 settings-haskell-cpp-flags = @SettingsHaskellCPPFlags@
 settings-c-compiler-flags = @SettingsCCompilerFlags@
+settings-cxx-compiler-flags = @SettingsCxxCompilerFlags@
 settings-c-compiler-link-flags = @SettingsCCompilerLinkFlags@
 settings-c-compiler-supports-no-pie = @SettingsCCompilerSupportsNoPie@
 settings-ld-command = @SettingsLdCommand@


=====================================
hadrian/src/Oracles/Setting.hs
=====================================
@@ -88,6 +88,7 @@ data SettingsFileSetting
     | SettingsFileSetting_HaskellCPPCommand
     | SettingsFileSetting_HaskellCPPFlags
     | SettingsFileSetting_CCompilerFlags
+    | SettingsFileSetting_CxxCompilerFlags
     | SettingsFileSetting_CCompilerLinkFlags
     | SettingsFileSetting_CCompilerSupportsNoPie
     | SettingsFileSetting_LdCommand
@@ -162,6 +163,7 @@ settingsFileSetting key = lookupValueOrError configFile $ case key of
     SettingsFileSetting_HaskellCPPCommand -> "settings-haskell-cpp-command"
     SettingsFileSetting_HaskellCPPFlags -> "settings-haskell-cpp-flags"
     SettingsFileSetting_CCompilerFlags -> "settings-c-compiler-flags"
+    SettingsFileSetting_CxxCompilerFlags -> "settings-cxx-compiler-flags"
     SettingsFileSetting_CCompilerLinkFlags -> "settings-c-compiler-link-flags"
     SettingsFileSetting_CCompilerSupportsNoPie -> "settings-c-compiler-supports-no-pie"
     SettingsFileSetting_LdCommand -> "settings-ld-command"


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -277,6 +277,7 @@ generateSettings = do
         [ ("GCC extra via C opts", expr $ lookupValueOrError configFile "gcc-extra-via-c-opts")
         , ("C compiler command", expr $ settingsFileSetting SettingsFileSetting_CCompilerCommand)
         , ("C compiler flags", expr $ settingsFileSetting SettingsFileSetting_CCompilerFlags)
+        , ("C++ compiler flags", expr $ settingsFileSetting SettingsFileSetting_CxxCompilerFlags)
         , ("C compiler link flags", expr $ settingsFileSetting SettingsFileSetting_CCompilerLinkFlags)
         , ("C compiler supports -no-pie", expr $ settingsFileSetting SettingsFileSetting_CCompilerSupportsNoPie)
         , ("Haskell CPP command", expr $ settingsFileSetting SettingsFileSetting_HaskellCPPCommand)


=====================================
includes/ghc.mk
=====================================
@@ -179,6 +179,7 @@ $(includes_SETTINGS) : includes/Makefile | $$(dir $$@)/.
 	@echo '[("GCC extra via C opts", "$(GccExtraViaCOpts)")' >> $@
 	@echo ',("C compiler command", "$(SettingsCCompilerCommand)")' >> $@
 	@echo ',("C compiler flags", "$(SettingsCCompilerFlags)")' >> $@
+	@echo ',("C++ compiler flags", "$(SettingsCxxCompilerFlags)")' >> $@
 	@echo ',("C compiler link flags", "$(SettingsCCompilerLinkFlags)")' >> $@
 	@echo ',("C compiler supports -no-pie", "$(SettingsCCompilerSupportsNoPie)")' >> $@
 	@echo ',("Haskell CPP command", "$(SettingsHaskellCPPCommand)")' >> $@


=====================================
mk/config.mk.in
=====================================
@@ -510,6 +510,7 @@ SettingsCCompilerCommand = @SettingsCCompilerCommand@
 SettingsHaskellCPPCommand = @SettingsHaskellCPPCommand@
 SettingsHaskellCPPFlags = @SettingsHaskellCPPFlags@
 SettingsCCompilerFlags = @SettingsCCompilerFlags@
+SettingsCxxCompilerFlags = @SettingsCxxCompilerFlags@
 SettingsCCompilerLinkFlags = @SettingsCCompilerLinkFlags@
 SettingsCCompilerSupportsNoPie = @SettingsCCompilerSupportsNoPie@
 SettingsLdCommand = @SettingsLdCommand@



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/68bae167ed7ab34f4294cca51a3d59d979fd4ebc...0f4169ae350ebd5514855c3756f55d574fef2a6b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/68bae167ed7ab34f4294cca51a3d59d979fd4ebc...0f4169ae350ebd5514855c3756f55d574fef2a6b
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/20190608/08dc3427/attachment-0001.html>


More information about the ghc-commits mailing list