[Git][ghc/ghc][wip/t22807-test] 4 commits: rts: Use C11-compliant static assertion syntax
Matthew Pickering (@mpickering)
gitlab at gitlab.haskell.org
Fri Jan 27 17:21:16 UTC 2023
Matthew Pickering pushed to branch wip/t22807-test at Glasgow Haskell Compiler / GHC
Commits:
e480fbc2 by Ben Gamari at 2023-01-27T05:01:24-05:00
rts: Use C11-compliant static assertion syntax
Previously we used `static_assert` which is only available in C23. By
contrast, C11 only provides `_Static_assert`.
Fixes #22777
- - - - -
2648c09c by Andrei Borzenkov at 2023-01-27T05:02:07-05:00
Replace errors from badOrigBinding with new one (#22839)
Problem: in 02279a9c the type-level [] syntax was changed from a built-in name
to an alias for the GHC.Types.List constructor. badOrigBinding assumes that if
a name is not built-in then it must have come from TH quotation, but this is
not necessarily the case with [].
The outdated assumption in badOrigBinding leads to incorrect error messages.
This code:
data []
Fails with "Cannot redefine a Name retrieved by a Template Haskell quote: []"
Unfortunately, there is not enough information in RdrName to directly determine
if the name was constructed via TH or by the parser, so this patch changes the
error message instead.
It unifies TcRnIllegalBindingOfBuiltIn and TcRnNameByTemplateHaskellQuote
into a new error TcRnBindingOfExistingName and changes its wording to avoid
guessing the origin of the name.
- - - - -
545bf8cf by Matthew Pickering at 2023-01-27T14:58:53+00:00
Revert "base: NoImplicitPrelude in Data.Void and Data.Kind"
Fixes CI errors of the form.
```
===> Command failed with error code: 1
ghc: panic! (the 'impossible' happened)
GHC version 9.7.20230127:
lookupGlobal
Failed to load interface for ‘GHC.Num.BigNat’
There are files missing in the ‘ghc-bignum’ package,
try running 'ghc-pkg check'.
Use -v (or `:set -v` in ghci) to see a list of the files searched for.
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/GHC/Utils/Panic.hs:189:37 in ghc:GHC.Utils.Panic
pprPanic, called at compiler/GHC/Tc/Utils/Env.hs:154:32 in ghc:GHC.Tc.Utils.Env
CallStack (from HasCallStack):
panic, called at compiler/GHC/Utils/Error.hs:454:29 in ghc:GHC.Utils.Error
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
```
This reverts commit d0d7ba0fb053ebe7f919a5932066fbc776301ccd.
The module now lacks a dependency on GHC.Num.BigNat which it implicitly
depends on. It is causing all CI jobs to fail so we revert without haste
whilst the patch can be fixed.
Fixes #22848
- - - - -
afc9d4c7 by Matthew Pickering at 2023-01-27T17:20:44+00:00
Improve error message in tc_iface_binding and add broken test for #22807
I improved the error message in tc_iface_binding to avoid the "no match
in record selector" error.
Also added the currently broken test for #22807 which could be fixed by
!6080
- - - - -
18 changed files:
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Types/Error/Codes.hs
- libraries/base/Data/Kind.hs
- libraries/base/Data/Void.hs
- rts/include/Rts.h
- testsuite/tests/driver/fat-iface/Makefile
- + testsuite/tests/driver/fat-iface/T22807A.hs
- + testsuite/tests/driver/fat-iface/T22807B.hs
- testsuite/tests/driver/fat-iface/all.T
- testsuite/tests/rename/should_fail/T14907b.stderr
- + testsuite/tests/rename/should_fail/T22839.hs
- + testsuite/tests/rename/should_fail/T22839.stderr
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rename/should_fail/rnfail042.stderr
- testsuite/tests/th/T13968.stderr
Changes:
=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -933,7 +933,14 @@ tc_iface_bindings (IfaceRec bs) = do
-- | See Note [Interface File with Core: Sharing RHSs]
tc_iface_binding :: Id -> IfaceMaybeRhs -> IfL CoreExpr
-tc_iface_binding i IfUseUnfoldingRhs = return (unfoldingTemplate $ realIdUnfolding i)
+tc_iface_binding i IfUseUnfoldingRhs =
+ case maybeUnfoldingTemplate $ realIdUnfolding i of
+ Just e -> return e
+ Nothing -> pprPanic "tc_iface_binding" (vcat [text "Binding" <+> quotes (ppr i) <+> text "had an unfolding when the interface file was created"
+ , text "which has now gone missing. Perhaps you loaded the interface file with `-fignore-interface-pragmas`"
+ , text "but compiled it with `-fno-omit-interface-pragmas`. If this is you, leave a comment on #20021"
+ , text "Unfolding:" <+> ppr (realIdUnfolding i)])
+
tc_iface_binding _ (IfRhs rhs) = tcIfaceExpr rhs
mk_top_id :: IfaceTopBndrInfo -> IfL Id
=====================================
compiler/GHC/Rename/Env.hs
=====================================
@@ -187,7 +187,7 @@ newTopSrcBinder (L loc rdr_name)
if isExternalName name then
do { this_mod <- getModule
; unless (this_mod == nameModule name)
- (addErrAt (locA loc) (badOrigBinding rdr_name))
+ (addErrAt (locA loc) (TcRnBindingOfExistingName rdr_name))
; return name }
else -- See Note [Binders in Template Haskell] in "GHC.ThToHs"
do { this_mod <- getModule
@@ -196,7 +196,7 @@ newTopSrcBinder (L loc rdr_name)
| Just (rdr_mod, rdr_occ) <- isOrig_maybe rdr_name
= do { this_mod <- getModule
; unless (rdr_mod == this_mod || rdr_mod == rOOT_MAIN)
- (addErrAt (locA loc) (badOrigBinding rdr_name))
+ (addErrAt (locA loc) (TcRnBindingOfExistingName rdr_name))
-- When reading External Core we get Orig names as binders,
-- but they should agree with the module gotten from the monad
--
@@ -205,7 +205,7 @@ newTopSrcBinder (L loc rdr_name)
-- the constructor is parsed as a type, and then GHC.Parser.PostProcess.tyConToDataCon
-- uses setRdrNameSpace to make it into a data constructors. At that point
-- the nice Exact name for the TyCon gets swizzled to an Orig name.
- -- Hence the badOrigBinding error message.
+ -- Hence the TcRnBindingOfExistingName error message.
--
-- MP 2022: I suspect this code path is never called for `rOOT_MAIN` anymore
@@ -2118,13 +2118,3 @@ lookupQualifiedDoName ctxt std_name
= case qualifiedDoModuleName_maybe ctxt of
Nothing -> lookupSyntaxName std_name
Just modName -> lookupNameWithQualifier std_name modName
-
-
--- Error messages
-
-badOrigBinding :: RdrName -> TcRnMessage
-badOrigBinding name
- | Just _ <- isBuiltInOcc_maybe occ = TcRnIllegalBindingOfBuiltIn occ
- | otherwise = TcRnNameByTemplateHaskellQuote name
- where
- occ = rdrNameOcc $ filterCTuple name
=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -25,7 +25,7 @@ module GHC.Tc.Errors.Ppr
import GHC.Prelude
import GHC.Builtin.Names
-import GHC.Builtin.Types ( boxedRepDataConTyCon, tYPETyCon )
+import GHC.Builtin.Types ( boxedRepDataConTyCon, tYPETyCon, filterCTuple )
import GHC.Core.Coercion
import GHC.Core.Unify ( tcMatchTys )
@@ -968,10 +968,6 @@ instance Diagnostic TcRnMessage where
-> mkSimpleDecorated $
text "You cannot SPECIALISE" <+> quotes (ppr name)
<+> text "because its definition is not visible in this module"
- TcRnNameByTemplateHaskellQuote name -> mkSimpleDecorated $
- text "Cannot redefine a Name retrieved by a Template Haskell quote:" <+> ppr name
- TcRnIllegalBindingOfBuiltIn name -> mkSimpleDecorated $
- text "Illegal binding of built-in syntax:" <+> ppr name
TcRnPragmaWarning {pragma_warning_occ, pragma_warning_msg, pragma_warning_import_mod, pragma_warning_defined_mod}
-> mkSimpleDecorated $
sep [ sep [ text "In the use of"
@@ -1238,6 +1234,8 @@ instance Diagnostic TcRnMessage where
Left gbl_names -> vcat (map (\name -> quotes (ppr $ grePrintableName name) <+> pprNameProvenance name) gbl_names)
Right lcl_name -> quotes (ppr lcl_name) <+> text "defined at"
<+> ppr (nameSrcLoc lcl_name)
+ TcRnBindingOfExistingName name -> mkSimpleDecorated $
+ text "Illegal binding of an existing name:" <+> ppr (filterCTuple name)
diagnosticReason = \case
TcRnUnknownMessage m
@@ -1552,10 +1550,6 @@ instance Diagnostic TcRnMessage where
-> WarningWithoutFlag
TcRnSpecialiseNotVisible{}
-> WarningWithoutFlag
- TcRnNameByTemplateHaskellQuote{}
- -> ErrorWithoutFlag
- TcRnIllegalBindingOfBuiltIn{}
- -> ErrorWithoutFlag
TcRnPragmaWarning{}
-> WarningWithFlag Opt_WarnWarningsDeprecations
TcRnIllegalHsigDefaultMethods{}
@@ -1646,6 +1640,8 @@ instance Diagnostic TcRnMessage where
-> ErrorWithoutFlag
TcRnCapturedTermName{}
-> WarningWithFlag Opt_WarnTermVariableCapture
+ TcRnBindingOfExistingName{}
+ -> ErrorWithoutFlag
diagnosticHints = \case
TcRnUnknownMessage m
@@ -1962,10 +1958,6 @@ instance Diagnostic TcRnMessage where
-> noHints
TcRnSpecialiseNotVisible name
-> [SuggestSpecialiseVisibilityHints name]
- TcRnNameByTemplateHaskellQuote{}
- -> noHints
- TcRnIllegalBindingOfBuiltIn{}
- -> noHints
TcRnPragmaWarning{}
-> noHints
TcRnIllegalHsigDefaultMethods{}
@@ -2059,6 +2051,8 @@ instance Diagnostic TcRnMessage where
-> [suggestExtension LangExt.TupleSections]
TcRnCapturedTermName{}
-> [SuggestRenameTypeVariable]
+ TcRnBindingOfExistingName{}
+ -> noHints
diagnosticCode = constructorCode
=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -2193,32 +2193,6 @@ data TcRnMessage where
-}
TcRnSpecialiseNotVisible :: !Name -> TcRnMessage
- {- TcRnNameByTemplateHaskellQuote is an error that occurs when one tries
- to use a Template Haskell splice to define a top-level identifier with
- an already existing name.
-
- (See issue #13968 (closed) on GHC's issue tracker for more details)
-
- Example(s):
-
- $(pure [ValD (VarP 'succ) (NormalB (ConE 'True)) []])
-
- Test cases:
- T13968
- -}
- TcRnNameByTemplateHaskellQuote :: !RdrName -> TcRnMessage
-
- {- TcRnIllegalBindingOfBuiltIn is an error that occurs when one uses built-in
- syntax for data constructors or class names.
-
- Use an OccName here because we don't want to print Prelude.(,)
-
- Test cases:
- rename/should_fail/T14907b
- rename/should_fail/rnfail042
- -}
- TcRnIllegalBindingOfBuiltIn :: !OccName -> TcRnMessage
-
{- TcRnPragmaWarning is a warning that can happen when usage of something
is warned or deprecated by pragma.
@@ -2773,6 +2747,22 @@ data TcRnMessage where
-}
TcRnSectionWithoutParentheses :: HsExpr GhcPs -> TcRnMessage
+ {- TcRnBindingOfExistingName is an error triggered by an attempt to rebind
+ built-in syntax, punned list or tuple syntax, or a name quoted via Template Haskell.
+
+ Examples:
+
+ data []
+ data (->)
+ $(pure [ValD (VarP 'succ) (NormalB (ConE 'True)) []])
+
+ Test cases: rename/should_fail/T14907b
+ rename/should_fail/T22839
+ rename/should_fail/rnfail042
+ th/T13968
+ -}
+ TcRnBindingOfExistingName :: RdrName -> TcRnMessage
+
deriving Generic
-- | Things forbidden in @type data@ declarations.
=====================================
compiler/GHC/Types/Error/Codes.hs
=====================================
@@ -468,8 +468,6 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "TcRnNonOverloadedSpecialisePragma" = 35827
GhcDiagnosticCode "TcRnSpecialiseNotVisible" = 85337
GhcDiagnosticCode "TcRnIllegalTypeOperatorDecl" = 50649
- GhcDiagnosticCode "TcRnNameByTemplateHaskellQuote" = 40027
- GhcDiagnosticCode "TcRnIllegalBindingOfBuiltIn" = 69639
GhcDiagnosticCode "TcRnIllegalHsigDefaultMethods" = 93006
GhcDiagnosticCode "TcRnBadGenericMethod" = 59794
@@ -502,6 +500,7 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "TcRnBadFamInstDecl" = 06206
GhcDiagnosticCode "TcRnNotOpenFamily" = 06207
GhcDiagnosticCode "TcRnCapturedTermName" = 54201
+ GhcDiagnosticCode "TcRnBindingOfExistingName" = 58805
-- IllegalNewtypeReason
GhcDiagnosticCode "DoesNotHaveSingleField" = 23517
@@ -607,6 +606,8 @@ type family GhcDiagnosticCode c = n | n -> c where
-- no longer reports. These are collected below.
GhcDiagnosticCode "Example outdated error" = 00000
+ GhcDiagnosticCode "TcRnNameByTemplateHaskellQuote" = 40027
+ GhcDiagnosticCode "TcRnIllegalBindingOfBuiltIn" = 69639
{- *********************************************************************
* *
=====================================
libraries/base/Data/Kind.hs
=====================================
@@ -1,5 +1,4 @@
-{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE Trustworthy, ExplicitNamespaces #-}
-----------------------------------------------------------------------------
-- |
=====================================
libraries/base/Data/Void.hs
=====================================
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
=====================================
rts/include/Rts.h
=====================================
@@ -167,7 +167,10 @@ void _warnFail(const char *filename, unsigned int linenum);
#endif /* DEBUG */
#if __STDC_VERSION__ >= 201112L
-#define GHC_STATIC_ASSERT(x, msg) static_assert((x), msg)
+// `_Static_assert` is provided by C11 but is deprecated and replaced by
+// `static_assert` in C23. Perhaps some day we should instead use the latter.
+// See #22777.
+#define GHC_STATIC_ASSERT(x, msg) _Static_assert((x), msg)
#else
#define GHC_STATIC_ASSERT(x, msg)
#endif
=====================================
testsuite/tests/driver/fat-iface/Makefile
=====================================
@@ -49,4 +49,8 @@ fat010: clean
echo >> "THB.hs"
"$(TEST_HC)" $(TEST_HC_OPTS) THC.hs -fhide-source-paths -fwrite-if-simplified-core -fprefer-byte-code
+T22807: clean
+ "$(TEST_HC)" $(TEST_HC_OPTS) T22807A.hs -fhide-source-paths -fwrite-if-simplified-core -fbyte-code-and-object-code -fno-omit-interface-pragmas -fprefer-byte-code
+ "$(TEST_HC)" $(TEST_HC_OPTS) T22807B.hs -fhide-source-paths -fwrite-if-simplified-core -fprefer-byte-code -fbyte-code-and-object-code -fno-omit-interface-pragmas
+
=====================================
testsuite/tests/driver/fat-iface/T22807A.hs
=====================================
@@ -0,0 +1,6 @@
+module T22807A where
+
+xs :: [a]
+xs = []
+
+
=====================================
testsuite/tests/driver/fat-iface/T22807B.hs
=====================================
@@ -0,0 +1,5 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T22807B where
+import T22807A
+
+$(pure xs)
=====================================
testsuite/tests/driver/fat-iface/all.T
=====================================
@@ -15,5 +15,7 @@ test('fat013', [req_th, extra_files(['FatTH.hs', 'FatQuote.hs'])], multimod_comp
# When using interpreter should not produce objects
test('fat014', [req_th, extra_files(['FatTH.hs', 'FatQuote.hs']), extra_run_opts('-fno-code')], ghci_script, ['fat014.script'])
test('fat015', [req_th, unless(ghc_dynamic(), skip), extra_files(['FatQuote.hs', 'FatQuote1.hs', 'FatQuote2.hs', 'FatTH1.hs', 'FatTH2.hs', 'FatTHTop.hs'])], multimod_compile, ['FatTHTop', '-fno-code -fwrite-interface'])
+test('T22807', [req_th, expect_broken(22807), unless(ghc_dynamic(), skip), extra_files(['T22807A.hs', 'T22807B.hs'])]
+ , makefile_test, ['T22807'])
=====================================
testsuite/tests/rename/should_fail/T14907b.stderr
=====================================
@@ -1,9 +1,9 @@
-T14907b.hs:5:1: error: [GHC-69639]
- Illegal binding of built-in syntax: ()
+T14907b.hs:5:1: error: [GHC-58805]
+ Illegal binding of an existing name: ()
-T14907b.hs:6:1: error: [GHC-69639]
- Illegal binding of built-in syntax: (,)
+T14907b.hs:6:1: error: [GHC-58805]
+ Illegal binding of an existing name: (,)
-T14907b.hs:7:1: error: [GHC-69639]
- Illegal binding of built-in syntax: (,,)
+T14907b.hs:7:1: error: [GHC-58805]
+ Illegal binding of an existing name: (,,)
=====================================
testsuite/tests/rename/should_fail/T22839.hs
=====================================
@@ -0,0 +1,5 @@
+module T22839 where
+
+data []
+
+data (->)
=====================================
testsuite/tests/rename/should_fail/T22839.stderr
=====================================
@@ -0,0 +1,6 @@
+
+T22839.hs:3:1: error: [GHC-58805]
+ Illegal binding of an existing name: []
+
+T22839.hs:5:1: error: [GHC-58805]
+ Illegal binding of an existing name: ->
=====================================
testsuite/tests/rename/should_fail/all.T
=====================================
@@ -183,3 +183,4 @@ test('T21605a', normal, compile_fail, [''])
test('T21605b', normal, compile_fail, [''])
test('T21605c', normal, compile_fail, [''])
test('T21605d', normal, compile_fail, [''])
+test('T22839', normal, compile_fail, [''])
=====================================
testsuite/tests/rename/should_fail/rnfail042.stderr
=====================================
@@ -1,12 +1,12 @@
-rnfail042.hs:5:11: error: [GHC-69639]
- Illegal binding of built-in syntax: ()
+rnfail042.hs:5:11: error: [GHC-58805]
+ Illegal binding of an existing name: ()
-rnfail042.hs:6:10: error: [GHC-69639]
- Illegal binding of built-in syntax: (,,,)
+rnfail042.hs:6:10: error: [GHC-58805]
+ Illegal binding of an existing name: (,,,)
-rnfail042.hs:7:12: error: [GHC-69639]
- Illegal binding of built-in syntax: []
+rnfail042.hs:7:12: error: [GHC-58805]
+ Illegal binding of an existing name: []
-rnfail042.hs:8:13: error: [GHC-69639]
- Illegal binding of built-in syntax: :
+rnfail042.hs:8:13: error: [GHC-58805]
+ Illegal binding of an existing name: :
=====================================
testsuite/tests/th/T13968.stderr
=====================================
@@ -1,3 +1,3 @@
-T13968.hs:6:2: error: [GHC-40027]
- Cannot redefine a Name retrieved by a Template Haskell quote: succ
+T13968.hs:6:2: error: [GHC-58805]
+ Illegal binding of an existing name: succ
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2a028403d4908f60a3eebb7d4c15c291b95c2e8b...afc9d4c7bad05b17612b2572d96458bde68aa5dd
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2a028403d4908f60a3eebb7d4c15c291b95c2e8b...afc9d4c7bad05b17612b2572d96458bde68aa5dd
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/20230127/2421d26b/attachment-0001.html>
More information about the ghc-commits
mailing list