[commit: ghc] ghc-7.10: GHC.Prim.Constraint is not built-in syntax (f6c690b)
git at git.haskell.org
git at git.haskell.org
Tue Apr 14 13:17:49 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-7.10
Link : http://ghc.haskell.org/trac/ghc/changeset/f6c690ba6491e0e943bd07763c0063a55ff0c760/ghc
>---------------------------------------------------------------
commit f6c690ba6491e0e943bd07763c0063a55ff0c760
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Apr 7 13:55:43 2015 +0100
GHC.Prim.Constraint is not built-in syntax
This fixes Trac #10233
(cherry picked from commit 74d2c33a1f4ebe3de090bc73d08910bbdd31f8f1)
>---------------------------------------------------------------
f6c690ba6491e0e943bd07763c0063a55ff0c760
compiler/prelude/TysPrim.hs | 33 ++++++++++++++++++---------------
testsuite/tests/module/T10233.hs | 2 ++
testsuite/tests/module/T10233a.hs | 3 +++
testsuite/tests/module/all.T | 2 ++
4 files changed, 25 insertions(+), 15 deletions(-)
diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs
index e8542eb..6cb1006 100644
--- a/compiler/prelude/TysPrim.hs
+++ b/compiler/prelude/TysPrim.hs
@@ -10,8 +10,6 @@
-- | This module defines TyCons that can't be expressed in Haskell.
-- They are all, therefore, wired-in TyCons. C.f module TysWiredIn
module TysPrim(
- mkPrimTyConName, -- For implicit parameters in TysWiredIn only
-
tyVarList, alphaTyVars, betaTyVars, alphaTyVar, betaTyVar, gammaTyVar, deltaTyVar,
alphaTy, betaTy, gammaTy, deltaTy,
openAlphaTy, openBetaTy, openAlphaTyVar, openBetaTyVar, openAlphaTyVars,
@@ -330,21 +328,26 @@ constraintKindTyCon = mkKindTyCon constraintKindTyConName superKind
-- ... and now their names
-- If you edit these, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.lhs
-superKindTyConName = mkPrimTyConName (fsLit "BOX") superKindTyConKey superKindTyCon
-anyKindTyConName = mkPrimTyConName (fsLit "AnyK") anyKindTyConKey anyKindTyCon
-liftedTypeKindTyConName = mkPrimTyConName (fsLit "*") liftedTypeKindTyConKey liftedTypeKindTyCon
-openTypeKindTyConName = mkPrimTyConName (fsLit "OpenKind") openTypeKindTyConKey openTypeKindTyCon
-unliftedTypeKindTyConName = mkPrimTyConName (fsLit "#") unliftedTypeKindTyConKey unliftedTypeKindTyCon
-constraintKindTyConName = mkPrimTyConName (fsLit "Constraint") constraintKindTyConKey constraintKindTyCon
+-- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+superKindTyConName = mkPrimTyConName (fsLit "BOX") superKindTyConKey superKindTyCon
+anyKindTyConName = mkPrimTyConName (fsLit "AnyK") anyKindTyConKey anyKindTyCon
+liftedTypeKindTyConName = mkPrimTyConName (fsLit "*") liftedTypeKindTyConKey liftedTypeKindTyCon
+openTypeKindTyConName = mkPrimTyConName (fsLit "OpenKind") openTypeKindTyConKey openTypeKindTyCon
+unliftedTypeKindTyConName = mkPrimTyConName (fsLit "#") unliftedTypeKindTyConKey unliftedTypeKindTyCon
mkPrimTyConName :: FastString -> Unique -> TyCon -> Name
-mkPrimTyConName occ key tycon = mkWiredInName gHC_PRIM (mkTcOccFS occ)
- key
- (ATyCon tycon)
- BuiltInSyntax
- -- All of the super kinds and kinds are defined in Prim and use BuiltInSyntax,
- -- because they are never in scope in the source
+mkPrimTyConName = mkPrimTcName BuiltInSyntax
+ -- All of the super kinds and kinds are defined in Prim,
+ -- and use BuiltInSyntax, because they are never in scope in the source
+
+constraintKindTyConName -- Unlike the others, Constraint does *not* use BuiltInSyntax,
+ -- and can be imported/exported like any other type constructor
+ = mkPrimTcName UserSyntax (fsLit "Constraint") constraintKindTyConKey constraintKindTyCon
+
+
+mkPrimTcName :: BuiltInSyntax -> FastString -> Unique -> TyCon -> Name
+mkPrimTcName built_in_syntax occ key tycon
+ = mkWiredInName gHC_PRIM (mkTcOccFS occ) key (ATyCon tycon) built_in_syntax
kindTyConType :: TyCon -> Type
kindTyConType kind = TyConApp kind [] -- mkTyConApp isn't defined yet
diff --git a/testsuite/tests/module/T10233.hs b/testsuite/tests/module/T10233.hs
new file mode 100644
index 0000000..965b413
--- /dev/null
+++ b/testsuite/tests/module/T10233.hs
@@ -0,0 +1,2 @@
+module T10233 where
+import T10233a( Constraint, Int )
diff --git a/testsuite/tests/module/T10233a.hs b/testsuite/tests/module/T10233a.hs
new file mode 100644
index 0000000..b3282d9
--- /dev/null
+++ b/testsuite/tests/module/T10233a.hs
@@ -0,0 +1,3 @@
+module T10233a ( module GHC.Exts ) where
+import GHC.Exts ( Constraint, Int )
+
diff --git a/testsuite/tests/module/all.T b/testsuite/tests/module/all.T
index 58632be..2e4aedd 100644
--- a/testsuite/tests/module/all.T
+++ b/testsuite/tests/module/all.T
@@ -345,3 +345,5 @@ test('T414b', normal, compile, [''])
test('T3776', normal, compile, [''])
test('T9061', normal, compile, [''])
test('T9997', normal, compile, [''])
+test('T10233', extra_clean(['T01233a.hi', 'T01233a.o']),
+ multimod_compile, ['T10233', '-v0'])
More information about the ghc-commits
mailing list