[Git][ghc/ghc][master] Regression test for #16627.

Marge Bot gitlab at gitlab.haskell.org
Wed May 8 19:53:36 UTC 2019



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
4c86187c by Richard Eisenberg at 2019-05-08T19:47:33Z
Regression test for #16627.

test: typecheck/should_fail/T16627

- - - - -


3 changed files:

- + testsuite/tests/typecheck/should_fail/T16627.hs
- + testsuite/tests/typecheck/should_fail/T16627.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
testsuite/tests/typecheck/should_fail/T16627.hs
=====================================
@@ -0,0 +1,14 @@
+{-# language TypeInType, ScopedTypeVariables #-}
+module Silly where
+import Type.Reflection (Typeable, typeRep, TypeRep)
+import Type.Reflection.Unsafe (mkTrApp)
+import GHC.Exts (TYPE, RuntimeRep (..))
+import Data.Kind (Type)
+
+mkTrFun :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep)
+                  (a :: TYPE r1) (b :: TYPE r2).
+           TypeRep a -> TypeRep b -> TypeRep ((a -> b) :: Type)
+mkTrFun a b = typeRep `mkTrApp` a `mkTrApp` b
+
+-- originally reported that there was no (Typeable LiftedRep) instance,
+-- presumably to overeager RuntimeRep defaulting


=====================================
testsuite/tests/typecheck/should_fail/T16627.stderr
=====================================
@@ -0,0 +1,6 @@
+
+T16627.hs:11:15: error:
+    • No instance for (Typeable r1) arising from a use of ‘typeRep’
+    • In the first argument of ‘mkTrApp’, namely ‘typeRep’
+      In the first argument of ‘mkTrApp’, namely ‘typeRep `mkTrApp` a’
+      In the expression: typeRep `mkTrApp` a `mkTrApp` b


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -514,3 +514,4 @@ test('T16255', normal, compile_fail, [''])
 test('T16204c', normal, compile_fail, [''])
 test('T16394', normal, compile_fail, [''])
 test('T16414', normal, compile_fail, [''])
+test('T16627', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/4c86187ccd49309c1d6b32d05b164822a803d3e2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/4c86187ccd49309c1d6b32d05b164822a803d3e2
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/20190508/0e01cb72/attachment-0001.html>


More information about the ghc-commits mailing list