[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: testsuite: A more portable solution to #9399

Marge Bot gitlab at gitlab.haskell.org
Thu Jun 13 16:24:24 UTC 2019



 Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
c53dfb3b by Ben Gamari at 2019-06-13T15:52:47Z
testsuite: A more portable solution to #9399

Previously we used an awful hybrid batch script/Bourne shell script to
allow this test to run both on Windows and Linux (fixing #9399).
However, this breaks on some libc implementations (e.g. musl). Fix this.

Fixes #16798.

- - - - -
74b5d049 by Ben Gamari at 2019-06-13T15:53:22Z
gitlab-ci: Disable deb9-llvm job, introduce nightly LLVM job

This should help alleviate queue times as the LLVM job is one of the
longest that we have.

- - - - -
5ce63d52 by Ben Gamari at 2019-06-13T15:53:22Z
gitlab-ci: Disable validate-x86_64-linux-deb9 job to reduce load

Enable artifacts on to ensure we have bindist coverage.

- - - - -
d2ebcf09 by Ben Gamari at 2019-06-13T16:24:10Z
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.

- - - - -
7a5e08c9 by Ömer Sinan Ağacan at 2019-06-13T16:24:14Z
Remove unused Unique field from StgFCallOp

Fixes #16696

- - - - -
c849592f by Alp Mestanogullari at 2019-06-13T16:24:17Z
Hadrian: remove superfluous dependencies in Rules.Compile

Each package's object files were 'need'ing the library files of all transitive
dependencies of the current package, whichi is pointless since the said
libraries are not needed until we link those object files together.

This fixes #16759.

- - - - -


25 changed files:

- .gitlab-ci.yml
- aclocal.m4
- compiler/codeGen/StgCmmExpr.hs
- compiler/codeGen/StgCmmPrim.hs
- 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
- compiler/stgSyn/CoreToStg.hs
- compiler/stgSyn/StgSyn.hs
- hadrian/cfg/system.config.in
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Compile.hs
- hadrian/src/Rules/Generate.hs
- includes/ghc.mk
- libraries/base/tests/all.T
- libraries/base/tests/enum01.hs
- libraries/base/tests/enum02.hs
- libraries/base/tests/enum03.hs
- libraries/base/tests/enum_processor.bat
- libraries/base/tests/enum_processor.py
- mk/config.mk.in


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -444,7 +444,8 @@ nightly-i386-linux-deb9:
   cache:
     key: linux-x86_64-deb9
 
-validate-x86_64-linux-deb9:
+# Disabled to reduce CI load
+.validate-x86_64-linux-deb9:
   extends: .build-x86_64-linux-deb9
   artifacts:
     when: always
@@ -468,13 +469,27 @@ validate-x86_64-linux-deb9-debug:
     BUILD_FLAVOUR: validate
     TEST_TYPE: slowtest
     TEST_ENV: "x86_64-linux-deb9-debug"
+  artifacts:
+    when: always
+    expire_in: 2 week
+
+# Disabled to alleviate CI load
+.validate-x86_64-linux-deb9-llvm:
+  extends: .build-x86_64-linux-deb9
+  stage: full-build
+  variables:
+    BUILD_FLAVOUR: perf-llvm
+    TEST_ENV: "x86_64-linux-deb9-llvm"
 
-validate-x86_64-linux-deb9-llvm:
+nightly-x86_64-linux-deb9-llvm:
   extends: .build-x86_64-linux-deb9
   stage: full-build
   variables:
     BUILD_FLAVOUR: perf-llvm
     TEST_ENV: "x86_64-linux-deb9-llvm"
+  only:
+    variables:
+      - $NIGHTLY
 
 validate-x86_64-linux-deb9-integer-simple:
   extends: .build-x86_64-linux-deb9
@@ -780,7 +795,7 @@ doc-tarball:
     - x86_64-linux
   image: ghcci/x86_64-linux-deb9:0.2
   dependencies:
-    - validate-x86_64-linux-deb9
+    - validate-x86_64-linux-deb9-debug
     - validate-x86_64-windows
   variables:
     LINUX_BINDIST: "ghc-x86_64-deb9-linux.tar.xz"


=====================================
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/codeGen/StgCmmExpr.hs
=====================================
@@ -577,7 +577,7 @@ isSimpleScrut _                _           = return False
 
 isSimpleOp :: StgOp -> [StgArg] -> FCode Bool
 -- True iff the op cannot block or allocate
-isSimpleOp (StgFCallOp (CCall (CCallSpec _ _ safe)) _ _) _ = return $! not (playSafe safe)
+isSimpleOp (StgFCallOp (CCall (CCallSpec _ _ safe)) _) _ = return $! not (playSafe safe)
 -- dataToTag# evalautes its argument, see Note [dataToTag#] in primops.txt.pp
 isSimpleOp (StgPrimOp DataToTagOp) _ = return False
 isSimpleOp (StgPrimOp op) stg_args                  = do


=====================================
compiler/codeGen/StgCmmPrim.hs
=====================================
@@ -71,7 +71,7 @@ cgOpApp :: StgOp        -- The op
         -> FCode ReturnKind
 
 -- Foreign calls
-cgOpApp (StgFCallOp fcall ty _) stg_args res_ty
+cgOpApp (StgFCallOp fcall ty) stg_args res_ty
   = cgForeignCall fcall ty stg_args res_ty
       -- Note [Foreign call results]
 


=====================================
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
=====================================
@@ -1421,7 +1421,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
@@ -3049,7 +3049,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])


=====================================
compiler/stgSyn/CoreToStg.hs
=====================================
@@ -539,7 +539,7 @@ coreToStgApp _ f args ticks = do
 
                 -- A regular foreign call.
                 FCallId call     -> ASSERT( saturated )
-                                    StgOpApp (StgFCallOp call (idType f) (idUnique f)) args' res_ty
+                                    StgOpApp (StgFCallOp call (idType f)) args' res_ty
 
                 TickBoxOpId {}   -> pprPanic "coreToStg TickBox" $ ppr (f,args')
                 _other           -> StgApp f args'


=====================================
compiler/stgSyn/StgSyn.hs
=====================================
@@ -82,7 +82,6 @@ import PrimOp      ( PrimOp, PrimCall )
 import TyCon       ( PrimRep(..), TyCon )
 import Type        ( Type )
 import RepType     ( typePrimRep1 )
-import Unique      ( Unique )
 import Util
 
 import Data.List.NonEmpty ( NonEmpty, toList )
@@ -686,14 +685,11 @@ data StgOp
 
   | StgPrimCallOp PrimCall
 
-  | StgFCallOp ForeignCall Type Unique
-        -- The Unique is occasionally needed by the C pretty-printer
-        -- (which lacks a unique supply), notably when generating a
-        -- typedef for foreign-export-dynamic. The Type, which is
-        -- obtained from the foreign import declaration itself, is
-        -- needed by the stg-to-cmm pass to determine the offset to
-        -- apply to unlifted boxed arguments in StgCmmForeign.
-        -- See Note [Unlifted boxed arguments to foreign calls]
+  | StgFCallOp ForeignCall Type
+        -- The Type, which is obtained from the foreign import declaration
+        -- itself, is needed by the stg-to-cmm pass to determine the offset to
+        -- apply to unlifted boxed arguments in StgCmmForeign. See Note
+        -- [Unlifted boxed arguments to foreign calls]
 
 {-
 ************************************************************************
@@ -864,7 +860,7 @@ pprStgAlt indent (con, params, expr)
 pprStgOp :: StgOp -> SDoc
 pprStgOp (StgPrimOp  op)   = ppr op
 pprStgOp (StgPrimCallOp op)= ppr op
-pprStgOp (StgFCallOp op _ _) = ppr op
+pprStgOp (StgFCallOp op _) = ppr op
 
 instance Outputable AltType where
   ppr PolyAlt         = text "Polymorphic"


=====================================
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/Compile.hs
=====================================
@@ -10,7 +10,6 @@ import Rules.Generate
 import Settings
 import Target
 import Utilities
-import Rules.Library
 
 import qualified Text.Parsec as Parsec
 
@@ -177,7 +176,6 @@ compileHsObjectAndHi rs objpath = do
   ctxPath <- contextPath ctx
   (src, deps) <- lookupDependencies (ctxPath -/- ".dependencies") objpath
   need (src:deps)
-  needLibrary =<< contextDependencies ctx
 
   -- The .dependencies file lists indicating inputs. ghc will
   -- generally read more *.hi and *.hi-boot files (direct inputs).


=====================================
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)")' >> $@


=====================================
libraries/base/tests/all.T
=====================================
@@ -94,13 +94,27 @@ test('dynamic004',      omit_ways(['normal', 'threaded1', 'ghci']), compile_and_
 test('dynamic005',      normal, compile_and_run, [''])
 
 enum_setups = [when(fast(), skip)]
-test('enum01',          [extra_files(['enum_processor.bat', 'enum_processor.py']),
-                         enum_setups], compile_and_run, [''])
-test('enum02',          [extra_files(['enum_processor.bat', 'enum_processor.py']),
-                         enum_setups], compile_and_run, [''])
-test('enum03',          [extra_files(['enum_processor.bat', 'enum_processor.py']),
-                         enum_setups], compile_and_run, [''])
-test('enum04',          normal, compile_and_run, [''])
+def enum_test(name):
+    """
+    These tests have a funky Python preprocessor which require some headstands
+    to run on Windows.
+    """
+    if opsys('mingw32'):
+        test(name,
+             [when(opsys('mingw32'), extra_files(['enum_processor.bat'])),
+              extra_files(['enum_processor.py'])],
+             compile_and_run,
+             ['-F -pgmF ./enum_processor.bat'])
+    else:
+        test(name,
+             [extra_files(['enum_processor.py'])],
+             compile_and_run,
+             ['-F -pgmF ./enum_processor.py'])
+
+enum_test('enum01')
+enum_test('enum02')
+enum_test('enum03')
+test('enum04', normal, compile_and_run, [''])
 
 test('exceptionsrun001',        normal, compile_and_run, [''])
 test('exceptionsrun002', 	normal, compile_and_run, [''])


=====================================
libraries/base/tests/enum01.hs
=====================================
@@ -1,8 +1,4 @@
 -- !!! Testing the Prelude's Enum instances.
-{-# OPTIONS_GHC -F -pgmF ./enum_processor.bat #-}
--- The processor is a non-CPP-based equivalent of
--- #define printTest(x) (do{ putStr ( "    " ++ "x" ++ " = " ) ; print (x) })
--- which is not portable to clang
 
 module Main(main) where
 


=====================================
libraries/base/tests/enum02.hs
=====================================
@@ -1,8 +1,4 @@
 -- !!! Testing the Int Enum instances.
-{-# OPTIONS_GHC -F -pgmF ./enum_processor.bat #-}
--- The processor is a non-CPP-based equivalent of
--- #define printTest(x) (do{ putStr ( "    " ++ "x" ++ " = " ) ; print (x) })
--- which is not portable to clang
 
 module Main(main) where
 


=====================================
libraries/base/tests/enum03.hs
=====================================
@@ -1,8 +1,4 @@
 -- !!! Testing the Word Enum instances.
-{-# OPTIONS_GHC -F -pgmF ./enum_processor.bat #-}
--- The processor is a non-CPP-based equivalent of
--- #define printTest(x) (do{ putStr ( "    " ++ "x" ++ " = " ) ; print (x) })
--- which is not portable to clang
 
 module Main(main) where
 


=====================================
libraries/base/tests/enum_processor.bat
=====================================
@@ -1,11 +1,5 @@
 :;# Problem: GHC on Windows doesn't like '-pgmF ./enum_processor.py'.
 :;#          See ticket:365#comment:7 for details.
 :;#
-:;# Workaround: this file, which functions both as a Windows .bat script and a
-:;# Unix shell script. Hacky, but it seems to work.
 
-:;# Starts with a ':', to skip on Windows.
-:; "${PYTHON}" enum_processor.py $@; exit $?
-
-:;# Windows only:
 %PYTHON% enum_processor.py %*


=====================================
libraries/base/tests/enum_processor.py
=====================================
@@ -1,3 +1,5 @@
+#!/usr/bin/env python3
+
 # The rough equivalent of the traditional CPP:
 #   #define printTest(x) (do{ putStr ( "    " ++ "x" ++ " = " ) ; print (x) })
 # which is not portable to clang.


=====================================
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/38008a1276897fb2e03eeee7af0921d315afdd37...c849592f3aef9dced2b3a3ed16c628a6aef9aab5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/38008a1276897fb2e03eeee7af0921d315afdd37...c849592f3aef9dced2b3a3ed16c628a6aef9aab5
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/20190613/aa9c0cb0/attachment-0001.html>


More information about the ghc-commits mailing list