summaryrefslogtreecommitdiff
path: root/testsuite
diff options
context:
space:
mode:
authorMatthew Pickering <matthewtpickering@gmail.com>2022-12-01 16:58:34 +0000
committerMarge Bot <ben+marge-bot@smart-cactus.org>2022-12-08 22:47:59 -0500
commit1d3a8b8ec98e6eedf8943e19780ec374c2491e7f (patch)
treef601c5c12ce7030f18e0bb335f4e5617267191e4 /testsuite
parent3144e8ff1bac77f850a6188f6eef20de09915053 (diff)
downloadhaskell-1d3a8b8ec98e6eedf8943e19780ec374c2491e7f.tar.gz
Typeable: Fix module locations of some definitions in GHC.Types
There was some confusion in Data.Typeable about which module certain wired-in things were defined in. Just because something is wired-in doesn't mean it comes from GHC.Prim, in particular things like LiftedRep and RuntimeRep are defined in GHC.Types and that's the end of the story. Things like Int#, Float# etc are defined in GHC.Prim as they have no Haskell definition site at all so we need to generate type representations for them (which live in GHC.Types). Fixes #22510
Diffstat (limited to 'testsuite')
-rw-r--r--testsuite/tests/typecheck/should_run/T22510.hs36
-rw-r--r--testsuite/tests/typecheck/should_run/T22510.stdout16
-rwxr-xr-xtestsuite/tests/typecheck/should_run/all.T1
3 files changed, 53 insertions, 0 deletions
diff --git a/testsuite/tests/typecheck/should_run/T22510.hs b/testsuite/tests/typecheck/should_run/T22510.hs
new file mode 100644
index 0000000000..201e7da742
--- /dev/null
+++ b/testsuite/tests/typecheck/should_run/T22510.hs
@@ -0,0 +1,36 @@
+{-# LANGUAGE MagicHash, UnboxedTuples, UnboxedSums, ScopedTypeVariables, TypeApplications, AllowAmbiguousTypes #-}
+module Main where
+
+import Type.Reflection
+import Data.Proxy
+import GHC.Types
+import GHC.Prim
+
+moduleOf :: forall a . Typeable a => String
+moduleOf = case someTypeRep (Proxy @a) of
+ SomeTypeRep tr -> (show tr ++ ": " ++ (tyConModule $ typeRepTyCon tr))
+
+main = do
+ -- These are in GHC.Types
+ putStrLn $ moduleOf @Levity
+ putStrLn $ moduleOf @'Lifted
+ putStrLn $ moduleOf @RuntimeRep
+ putStrLn $ moduleOf @'IntRep
+ putStrLn $ moduleOf @'BoxedRep
+ putStrLn $ moduleOf @'Lifted
+ putStrLn $ moduleOf @VecCount
+ putStrLn $ moduleOf @'Vec2
+ putStrLn $ moduleOf @VecElem
+ putStrLn $ moduleOf @'Int8ElemRep
+
+ -- This is from GHC.Tuple
+ putStrLn $ moduleOf @((),())
+
+ -- These are in GHC.Prim
+ putStrLn $ moduleOf @(# () , () #)
+-- putStrLn $ moduleOf @(# () | () #)
+--
+ putStrLn $ moduleOf @(Int64#)
+ putStrLn $ moduleOf @(Word64#)
+ putStrLn $ moduleOf @TYPE
+ putStrLn $ moduleOf @CONSTRAINT
diff --git a/testsuite/tests/typecheck/should_run/T22510.stdout b/testsuite/tests/typecheck/should_run/T22510.stdout
new file mode 100644
index 0000000000..56f6aa096c
--- /dev/null
+++ b/testsuite/tests/typecheck/should_run/T22510.stdout
@@ -0,0 +1,16 @@
+Levity: GHC.Types
+'Lifted: GHC.Types
+RuntimeRep: GHC.Types
+'IntRep: GHC.Types
+'BoxedRep: GHC.Types
+'Lifted: GHC.Types
+VecCount: GHC.Types
+'Vec2: GHC.Types
+VecElem: GHC.Types
+'Int8ElemRep: GHC.Types
+((),()): GHC.Tuple.Prim
+(#,#) ('BoxedRep 'Lifted) ('BoxedRep 'Lifted) () (): GHC.Prim
+Int64#: GHC.Prim
+Word64#: GHC.Prim
+TYPE: GHC.Prim
+CONSTRAINT: GHC.Prim
diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T
index b4e04a118c..b99efb15c2 100755
--- a/testsuite/tests/typecheck/should_run/all.T
+++ b/testsuite/tests/typecheck/should_run/all.T
@@ -163,3 +163,4 @@ test('T19397M3', extra_files(['T19397S.hs']), compile_and_run, ['-main-is foo'])
test('T19397M4', extra_files(['T19397S.hs']), compile_and_run, ['-main-is foo'])
test('T19667', normal, compile_and_run, ['-fhpc'])
test('T20768', normal, compile_and_run, [''])
+test('T22510', normal, compile_and_run, [''])