[commit: ghc] master: Don't expose (~#), (~R#), (~P#) from GHC.Prim (5926b6e)

git at git.haskell.org git at git.haskell.org
Fri Jun 8 00:08:59 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/5926b6ed0dcc86f8fd6038fdcc5e2ba2856f40ce/ghc

>---------------------------------------------------------------

commit 5926b6ed0dcc86f8fd6038fdcc5e2ba2856f40ce
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Thu Jun 7 13:30:28 2018 -0400

    Don't expose (~#), (~R#), (~P#) from GHC.Prim
    
    Currently, the primitive `(~#)`, `(~R#)`, and `(~P#)` type
    constructors are wired in to be exported from `GHC.Prim`. This has
    some unfortunate consequences, however. It turns out that `(~#)` is
    actually a legal infix identifier, so users can make use of unboxed
    equalities in strange ways in user code (see #15209). The other two,
    `(~R#)` and `(~P#)`, can't be used in source code, but they can be
    observed with GHCi's `:browse` command, which is somewhat unnerving.
    
    The fix for both of these problems is simple: just don't wire them
    to be exported from `GHC.Prim`.
    
    Test Plan: make test TEST="T12023 T15209"
    
    Reviewers: bgamari, dfeuer
    
    Reviewed By: bgamari, dfeuer
    
    Subscribers: rwbarton, thomie, carter, dfeuer
    
    GHC Trac Issues: #12023, #15209
    
    Differential Revision: https://phabricator.haskell.org/D4801


>---------------------------------------------------------------

5926b6ed0dcc86f8fd6038fdcc5e2ba2856f40ce
 compiler/prelude/PrelInfo.hs                       |  2 +-
 compiler/prelude/TysPrim.hs                        | 22 +++++++++++++++++-----
 testsuite/tests/ghci/scripts/Makefile              |  5 +++++
 testsuite/tests/ghci/scripts/T12023.script         |  1 +
 .../tests/ghci/scripts/T12023.stdout               |  0
 testsuite/tests/ghci/scripts/all.T                 |  2 ++
 testsuite/tests/parser/should_fail/T15209.hs       |  7 +++++++
 testsuite/tests/parser/should_fail/T15209.stderr   |  2 ++
 testsuite/tests/parser/should_fail/all.T           |  1 +
 9 files changed, 36 insertions(+), 6 deletions(-)

diff --git a/compiler/prelude/PrelInfo.hs b/compiler/prelude/PrelInfo.hs
index 8d1f140..2a5fad6 100644
--- a/compiler/prelude/PrelInfo.hs
+++ b/compiler/prelude/PrelInfo.hs
@@ -252,7 +252,7 @@ ghcPrimExports
  = map (avail . idName) ghcPrimIds ++
    map (avail . idName . primOpId) allThePrimOps ++
    [ AvailTC n [n] []
-   | tc <- funTyCon : primTyCons, let n = tyConName tc  ]
+   | tc <- funTyCon : exposedPrimTyCons, let n = tyConName tc  ]
 
 {-
 ************************************************************************
diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs
index f7a51a5..ff61878 100644
--- a/compiler/prelude/TysPrim.hs
+++ b/compiler/prelude/TysPrim.hs
@@ -30,7 +30,7 @@ module TysPrim(
         tYPE, primRepToRuntimeRep,
 
         funTyCon, funTyConName,
-        primTyCons,
+        unexposedPrimTyCons, exposedPrimTyCons, primTyCons,
 
         charPrimTyCon,          charPrimTy, charPrimTyConName,
         intPrimTyCon,           intPrimTy, intPrimTyConName,
@@ -118,7 +118,22 @@ import Data.Char
 -}
 
 primTyCons :: [TyCon]
-primTyCons
+primTyCons = unexposedPrimTyCons ++ exposedPrimTyCons
+
+-- | Primitive 'TyCon's that are defined in "GHC.Prim" but not exposed.
+-- It's important to keep these separate as we don't want users to be able to
+-- write them (see Trac #15209) or see them in GHCi's @:browse@ output
+-- (see Trac #12023).
+unexposedPrimTyCons :: [TyCon]
+unexposedPrimTyCons
+  = [ eqPrimTyCon
+    , eqReprPrimTyCon
+    , eqPhantPrimTyCon
+    ]
+
+-- | Primitive 'TyCon's that are defined in, and exported from, "GHC.Prim".
+exposedPrimTyCons :: [TyCon]
+exposedPrimTyCons
   = [ addrPrimTyCon
     , arrayPrimTyCon
     , byteArrayPrimTyCon
@@ -150,9 +165,6 @@ primTyCons
     , wordPrimTyCon
     , word32PrimTyCon
     , word64PrimTyCon
-    , eqPrimTyCon
-    , eqReprPrimTyCon
-    , eqPhantPrimTyCon
 
     , tYPETyCon
 
diff --git a/testsuite/tests/ghci/scripts/Makefile b/testsuite/tests/ghci/scripts/Makefile
index 5f84865..40ba561 100644
--- a/testsuite/tests/ghci/scripts/Makefile
+++ b/testsuite/tests/ghci/scripts/Makefile
@@ -61,3 +61,8 @@ T11389:
 	# (without -v0)
 	'$(TEST_HC)' $(filter-out -v0,$(TEST_HC_OPTS_INTERACTIVE)) \
             -ghci-script T11389.script < /dev/null | grep 'configuration'
+
+.PHONY: T12023
+T12023:
+	-'$(TEST_HC)' $(TEST_HC_OPTS_INTERACTIVE) \
+	    -ghci-script T12023.script < /dev/null | grep -c -E '(~#|~R#|~P#)'
diff --git a/testsuite/tests/ghci/scripts/T12023.script b/testsuite/tests/ghci/scripts/T12023.script
new file mode 100644
index 0000000..c7552fe
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T12023.script
@@ -0,0 +1 @@
+:browse GHC.Prim
diff --git a/libraries/base/tests/dynamic005.stdout b/testsuite/tests/ghci/scripts/T12023.stdout
similarity index 100%
copy from libraries/base/tests/dynamic005.stdout
copy to testsuite/tests/ghci/scripts/T12023.stdout
diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T
index f4b4177..e803522 100755
--- a/testsuite/tests/ghci/scripts/all.T
+++ b/testsuite/tests/ghci/scripts/all.T
@@ -239,6 +239,8 @@ test('T12007', normal, ghci_script, ['T12007.script'])
 test('T11975', normal, ghci_script, ['T11975.script'])
 test('T10963', normal, ghci_script, ['T10963.script'])
 test('T11721', normal, ghci_script, ['T11721.script'])
+test('T12023', normal, run_command,
+               ['$MAKE -s --no-print-directory T12023'])
 test('T12520', normal, ghci_script, ['T12520.script'])
 test('T12091', [extra_run_opts('-fobject-code')], ghci_script,
      ['T12091.script'])
diff --git a/testsuite/tests/parser/should_fail/T15209.hs b/testsuite/tests/parser/should_fail/T15209.hs
new file mode 100644
index 0000000..1679d80
--- /dev/null
+++ b/testsuite/tests/parser/should_fail/T15209.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE GADTs, TypeOperators #-}
+module T15209 where
+
+import GHC.Prim
+
+foo :: a ~# Int -> ()
+foo = ()
diff --git a/testsuite/tests/parser/should_fail/T15209.stderr b/testsuite/tests/parser/should_fail/T15209.stderr
new file mode 100644
index 0000000..f5418fa
--- /dev/null
+++ b/testsuite/tests/parser/should_fail/T15209.stderr
@@ -0,0 +1,2 @@
+
+T15209.hs:6:8: error: Not in scope: type constructor or class ‘~#’
diff --git a/testsuite/tests/parser/should_fail/all.T b/testsuite/tests/parser/should_fail/all.T
index 01075f2..9fcc3ba 100644
--- a/testsuite/tests/parser/should_fail/all.T
+++ b/testsuite/tests/parser/should_fail/all.T
@@ -110,6 +110,7 @@ test('T13450', normal, compile_fail, [''])
 test('T13450TH', normal, compile_fail, [''])
 test('T14588', normal, compile_fail, [''])
 test('T14740', normal, compile_fail, [''])
+test('T15209', normal, compile_fail, [''])
 
 test('NoNumericUnderscores0', normal, compile_fail, [''])
 test('NoNumericUnderscores1', normal, compile_fail, [''])



More information about the ghc-commits mailing list