[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: testsuite: Teach testsuite driver about c++ sources

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Jan 9 08:40:38 UTC 2024



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


Commits:
1c5d7584 by Zubin Duggal at 2024-01-09T03:40:15-05:00
testsuite: Teach testsuite driver about c++ sources

- - - - -
bb3d4f60 by Zubin Duggal at 2024-01-09T03:40:15-05:00
driver: Set -DPROFILING when compiling C++ sources with profiling

Earlier, we used to pass all preprocessor flags to the c++ compiler.
This meant that -DPROFILING was passed to the c++ compiler because
it was a part of C++ flags
However, this was incorrect and the behaviour was changed in
8ff3134ed4aa323b0199ad683f72165e51a59ab6. See #21291.

But that commit exposed this bug where -DPROFILING was no longer being passed
when compiling c++ sources.

The fix is to explicitly include -DPROFILING in `opt_cxx` when profiling is
enabled to ensure we pass the correct options for the way to both C and C++
compilers

Fixes #24286

- - - - -
3f6a6aea by Zubin Duggal at 2024-01-09T03:40:15-05:00
testsuite: rename objcpp -> objcxx

To avoid confusion with C Pre Processsor

- - - - -
957759e5 by Simon Peyton Jones at 2024-01-09T03:40:15-05:00
Make TYPE and CONSTRAINT not-apart

Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty
which is supposed to make TYPE and CONSTRAINT be not-apart.

Easily fixed.

- - - - -
3dbcdbf8 by Zubin Duggal at 2024-01-09T03:40:16-05:00
ci: Fix typo in mk_ghcup_metadata.py

There was a missing colon in the fix to #24268 in 989bf8e53c08eb22de716901b914b3607bc8dd08

- - - - -


13 changed files:

- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Platform/Ways.hs
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/tests/driver/Makefile
- + testsuite/tests/driver/T24286.cpp
- testsuite/tests/driver/all.T
- testsuite/tests/driver/objc/all.T
- + testsuite/tests/typecheck/should_fail/T24279.hs
- + testsuite/tests/typecheck/should_fail/T24279.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
.gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
=====================================
@@ -145,7 +145,7 @@ def mk_one_metadata(release_mode, version, job_map, artifact):
         # So we must manually set the name of the bindist location
         if artifact == test_artifact:
             bindist_name = "testsuite"
-        else
+        else:
             bindist_name = fetch_gitlab.job_triple(artifact.job_name)
         final_url = release_base.format( version=version
                                        , bindistName=urllib.parse.quote_plus(f"{bindist_name}.tar.xz"))


=====================================
compiler/GHC/Core/Unify.hs
=====================================
@@ -31,6 +31,7 @@ import GHC.Types.Var
 import GHC.Types.Var.Env
 import GHC.Types.Var.Set
 import GHC.Types.Name( Name, mkSysTvName, mkSystemVarName )
+import GHC.Builtin.Names( tYPETyConKey, cONSTRAINTTyConKey )
 import GHC.Core.Type     hiding ( getTvSubstEnv )
 import GHC.Core.Coercion hiding ( getCvSubstEnv )
 import GHC.Core.TyCon
@@ -1149,8 +1150,10 @@ unify_ty env ty1 ty2 _kco
   -- TYPE and CONSTRAINT are not Apart
   -- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim
   -- NB: at this point we know that the two TyCons do not match
-  | Just {} <- sORTKind_maybe ty1
-  , Just {} <- sORTKind_maybe ty2
+  | Just (tc1,_) <- mb_tc_app1, let u1 = tyConUnique tc1
+  , Just (tc2,_) <- mb_tc_app2, let u2 = tyConUnique tc2
+  , (u1 == tYPETyConKey && u2 == cONSTRAINTTyConKey) ||
+    (u2 == tYPETyConKey && u1 == cONSTRAINTTyConKey)
   = maybeApart MARTypeVsConstraint
     -- We don't bother to look inside; wrinkle (W3) in GHC.Builtin.Types.Prim
     -- Note [Type and Constraint are not apart]


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -438,7 +438,8 @@ opt_c                 :: DynFlags -> [String]
 opt_c dflags = concatMap (wayOptc (targetPlatform dflags)) (ways dflags)
             ++ toolSettings_opt_c (toolSettings dflags)
 opt_cxx               :: DynFlags -> [String]
-opt_cxx dflags= toolSettings_opt_cxx $ toolSettings dflags
+opt_cxx dflags = concatMap (wayOptcxx (targetPlatform dflags)) (ways dflags)
+           ++ toolSettings_opt_cxx (toolSettings dflags)
 opt_a                 :: DynFlags -> [String]
 opt_a dflags= toolSettings_opt_a $ toolSettings dflags
 opt_l                 :: DynFlags -> [String]


=====================================
compiler/GHC/Platform/Ways.hs
=====================================
@@ -31,6 +31,7 @@ module GHC.Platform.Ways
    , wayGeneralFlags
    , wayUnsetGeneralFlags
    , wayOptc
+   , wayOptcxx
    , wayOptl
    , wayOptP
    , wayDesc
@@ -177,6 +178,9 @@ wayOptc _ WayDebug      = []
 wayOptc _ WayDyn        = []
 wayOptc _ WayProf       = ["-DPROFILING"]
 
+wayOptcxx :: Platform -> Way -> [String]
+wayOptcxx = wayOptc -- Use the same flags as C
+
 -- | Pass these options to linker when enabling this way
 wayOptl :: Platform -> Way -> [String]
 wayOptl _ (WayCustom {}) = []


=====================================
testsuite/driver/testglobals.py
=====================================
@@ -399,10 +399,11 @@ class TestOptions:
        # Does this test use a literate (.lhs) file?
        self.literate = False
 
-       # Does this test use a .c, .m or .mm file?
+       # Does this test use a .c, .cpp, .m or .mm file?
        self.c_src      = False
+       self.cxx_src    = False
        self.objc_src   = False
-       self.objcpp_src = False
+       self.objcxx_src = False
 
        # Does this test use a .cmm file?
        self.cmm_src    = False


=====================================
testsuite/driver/testlib.py
=====================================
@@ -299,6 +299,13 @@ def req_c( name, opts ):
     # JS backend doesn't support C (yet)
     js_skip(name, opts)
 
+def req_cxx( name, opts ):
+    """
+    Mark a test as requiring C++ source file support
+    """
+    # JS backend doesn't support C (yet)
+    js_skip(name, opts)
+
 def req_cmm( name, opts ):
     """
     Mark a test as requiring Cmm support
@@ -953,11 +960,15 @@ def c_src( name, opts ):
     opts.c_src = True
     req_c (name, opts)
 
+def cxx_src( name, opts ):
+    opts.cxx_src = True
+    req_cxx (name, opts)
+
 def objc_src( name, opts ):
     opts.objc_src = True
 
-def objcpp_src( name, opts ):
-    opts.objcpp_src = True
+def objcxx_src( name, opts ):
+    opts.objcxx_src = True
 
 def cmm_src( name, opts ):
     opts.cmm_src = True
@@ -1948,8 +1959,9 @@ async def simple_build(name: Union[TestName, str],
 
     # Required by GHC 7.3+, harmless for earlier versions:
     if (getTestOpts().c_src or
+        getTestOpts().cxx_src or
         getTestOpts().objc_src or
-        getTestOpts().objcpp_src):
+        getTestOpts().objcxx_src):
         extra_hc_opts += ' -no-hs-main '
 
     if getTestOpts().compile_cmd_prefix == '':
@@ -2922,9 +2934,11 @@ def add_hs_lhs_suffix(name: str) -> Path:
         return add_suffix(name, 'c')
     elif getTestOpts().cmm_src:
         return add_suffix(name, 'cmm')
+    elif getTestOpts().cxx_src:
+        return add_suffix(name, 'cpp')
     elif getTestOpts().objc_src:
         return add_suffix(name, 'm')
-    elif getTestOpts().objcpp_src:
+    elif getTestOpts().objcxx_src:
         return add_suffix(name, 'mm')
     elif getTestOpts().literate:
         return add_suffix(name, 'lhs')


=====================================
testsuite/tests/driver/Makefile
=====================================
@@ -808,5 +808,3 @@ T23339B:
 	"$(TEST_HC)" -tmpdir "$(PWD)/tmp" $(TEST_HC_OPTS) -v0 T23339B.hs -finfo-table-map
 	# Check that the file is kept and is the right one
 	find . -name "*.c" -exec cat {} \; | grep "init__ip_init"
-
-


=====================================
testsuite/tests/driver/T24286.cpp
=====================================
@@ -0,0 +1,7 @@
+#if !defined(PROFILING)
+#error PROFILING flag not set for C++ files, see #24286
+#endif
+
+int main() {
+  return 0;
+}


=====================================
testsuite/tests/driver/all.T
=====================================
@@ -326,3 +326,4 @@ test('T23339', req_c, makefile_test, [])
 test('T23339B', [extra_files(['T23339.hs']), req_c], makefile_test, [])
 test('T23613', normal, compile_and_run, ['-this-unit-id=foo'])
 test('T23944', [unless(have_dynamic(), skip), extra_files(['T23944A.hs'])], multimod_compile, ['T23944 T23944A', '-fprefer-byte-code -fbyte-code -fno-code -dynamic-too -fwrite-interface'])
+test('T24286', [cxx_src, unless(have_profiling(), skip), extra_files(['T24286.cpp'])], compile, ['-prof -no-hs-main'])


=====================================
testsuite/tests/driver/objc/all.T
=====================================
@@ -12,8 +12,8 @@ test('objc-hi',
        expect_fail_for(['ghci']) ],
      compile_and_run, ['-framework Foundation'])
 
-test('objcpp-hi',
+test('objcxx-hi',
      [ skip_if_not_osx,
-       objcpp_src,
+       objcxx_src,
        expect_fail_for(['ghci']) ],
      compile_and_run, ['-framework Foundation -lc++'])


=====================================
testsuite/tests/typecheck/should_fail/T24279.hs
=====================================
@@ -0,0 +1,31 @@
+{-# LANGUAGE TypeFamilies #-}
+module T24279 where
+
+import GHC.Exts
+import Data.Kind
+
+type F :: (RuntimeRep -> Type) -> Type
+type family F a where
+  F TYPE = Int
+  F CONSTRAINT = Bool
+
+type G :: Type -> RuntimeRep -> Type
+type family G a where
+  G (a b) = a
+
+-- Should be rejected
+foo :: (F (G Constraint)) -> Bool
+foo x = x
+
+
+type family H a b where
+  H a a = Int
+  H a b = Bool
+
+-- Should be rejected
+bar1 :: H TYPE CONSTRAINT -> Int
+bar1 x = x
+
+-- Should be rejected
+bar2 :: H Type Constraint -> Int
+bar2 x = x


=====================================
testsuite/tests/typecheck/should_fail/T24279.stderr
=====================================
@@ -0,0 +1,19 @@
+
+T24279.hs:18:9: error: [GHC-83865]
+    • Couldn't match type ‘F CONSTRAINT’ with ‘Bool’
+      Expected: Bool
+        Actual: F (G Constraint)
+    • In the expression: x
+      In an equation for ‘foo’: foo x = x
+
+T24279.hs:27:10: error: [GHC-83865]
+    • Couldn't match expected type ‘Int’
+                  with actual type ‘H TYPE CONSTRAINT’
+    • In the expression: x
+      In an equation for ‘bar1’: bar1 x = x
+
+T24279.hs:31:10: error: [GHC-83865]
+    • Couldn't match expected type ‘Int’
+                  with actual type ‘H (*) Constraint’
+    • In the expression: x
+      In an equation for ‘bar2’: bar2 x = x


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -711,3 +711,4 @@ test('T17940', normal, compile_fail, [''])
 test('ErrorIndexLinks', normal, compile_fail, ['-fprint-error-index-links=always'])
 test('T24064', normal, compile_fail, [''])
 test('T24298', normal, compile_fail, [''])
+test('T24279', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e6c963b281d7920291267e7b0fd72d61e63def94...3dbcdbf85466a1d97c1a43752951553d650cdea5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e6c963b281d7920291267e7b0fd72d61e63def94...3dbcdbf85466a1d97c1a43752951553d650cdea5
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/20240109/a38557eb/attachment-0001.html>


More information about the ghc-commits mailing list