[commit: ghc] ghc-8.0: Add test for Data.Typeable.typeOf (5497ee4)
git at git.haskell.org
git at git.haskell.org
Thu Jan 21 12:27:43 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.0
Link : http://ghc.haskell.org/trac/ghc/changeset/5497ee440faa88cbd6142665079b35b52424f12e/ghc
>---------------------------------------------------------------
commit 5497ee440faa88cbd6142665079b35b52424f12e
Author: Ben Gamari <bgamari.foss at gmail.com>
Date: Wed Jan 13 14:53:21 2016 +0100
Add test for Data.Typeable.typeOf
Test Plan: Validate
Reviewers: goldfire, austin
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1770
GHC Trac Issues: #11120
>---------------------------------------------------------------
5497ee440faa88cbd6142665079b35b52424f12e
testsuite/tests/typecheck/should_run/TypeOf.hs | 34 ++++++++++++++++++++++
testsuite/tests/typecheck/should_run/TypeOf.stdout | 23 +++++++++++++++
testsuite/tests/typecheck/should_run/all.T | 1 +
3 files changed, 58 insertions(+)
diff --git a/testsuite/tests/typecheck/should_run/TypeOf.hs b/testsuite/tests/typecheck/should_run/TypeOf.hs
new file mode 100644
index 0000000..12184e7
--- /dev/null
+++ b/testsuite/tests/typecheck/should_run/TypeOf.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE DataKinds #-}
+
+import Data.Typeable
+import GHC.Types
+
+-- Test that Typeable works for various wired-in types.
+-- See, for instance, #11120.
+
+main :: IO ()
+main = do
+ print $ typeOf "hello world"
+ print $ typeOf '4'
+ print $ typeOf (42 :: Int)
+ print $ typeOf (42 :: Word)
+ print $ typeOf (3.1415 :: Double)
+ print $ typeOf (return () :: IO ())
+ print $ typeOf ('a', 1::Int, "hello")
+ print $ typeOf (typeOf "hi")
+ print $ typeOf True
+ print $ typeOf EQ
+ print $ typeOf (id :: Int -> Int)
+
+ print $ typeOf (Proxy :: Proxy (Eq Int))
+ print $ typeOf (Proxy :: Proxy (Int, Int))
+ print $ typeOf (Proxy :: Proxy "hello world")
+ print $ typeOf (Proxy :: Proxy 1)
+ print $ typeOf (Proxy :: Proxy [1,2,3])
+ print $ typeOf (Proxy :: Proxy 'EQ)
+ print $ typeOf (Proxy :: Proxy TYPE)
+ print $ typeOf (Proxy :: Proxy (TYPE 'Lifted))
+ print $ typeOf (Proxy :: Proxy *)
+ print $ typeOf (Proxy :: Proxy ★)
+ print $ typeOf (Proxy :: Proxy 'Lifted)
+ print $ typeOf (Proxy :: Proxy (~~))
diff --git a/testsuite/tests/typecheck/should_run/TypeOf.stdout b/testsuite/tests/typecheck/should_run/TypeOf.stdout
new file mode 100644
index 0000000..ffc2133
--- /dev/null
+++ b/testsuite/tests/typecheck/should_run/TypeOf.stdout
@@ -0,0 +1,23 @@
+[Char]
+Char
+Int
+Word
+Double
+IO ()
+(Char,Int,[Char])
+TypeRep
+Bool
+Ordering
+Int -> Int
+Proxy Constraint (Eq Int)
+Proxy Constraint (Int,Int)
+Proxy Symbol "hello world"
+Proxy Nat 1
+Proxy [Nat] (': Nat 1 (': Nat 2 (': Nat 3 '[])))
+Proxy Ordering 'EQ
+Proxy (Levity -> Constraint) TYPE
+Proxy Constraint Constraint
+Proxy Constraint Constraint
+Proxy Constraint Constraint
+Proxy Levity 'Lifted
+Proxy (Constraint -> Constraint -> Constraint) ~~
diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T
index 8c60777..cfd35e4 100755
--- a/testsuite/tests/typecheck/should_run/all.T
+++ b/testsuite/tests/typecheck/should_run/all.T
@@ -113,4 +113,5 @@ test('T9858d', normal, compile_and_run, [''])
test('T10284', exit_code(1), compile_and_run, [''])
test('T11049', exit_code(1), compile_and_run, [''])
test('T11230', normal, compile_and_run, [''])
+test('TypeOf', normal, compile_and_run, [''])
test('T11120', normal, compile_and_run, [''])
More information about the ghc-commits
mailing list