[Git][ghc/ghc][master] Add a regression test for #23903
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Tue Aug 29 16:10:30 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
3054fd6d by Krzysztof Gogolewski at 2023-08-29T12:09:08-04:00
Add a regression test for #23903
The bug has been fixed by commit bad2f8b8aa8424.
- - - - -
3 changed files:
- + testsuite/tests/rep-poly/T23903.hs
- + testsuite/tests/rep-poly/T23903.stderr
- testsuite/tests/rep-poly/all.T
Changes:
=====================================
testsuite/tests/rep-poly/T23903.hs
=====================================
@@ -0,0 +1,21 @@
+{-# LANGUAGE GHC2021, AllowAmbiguousTypes, DataKinds, MagicHash, TypeFamilies #-}
+module T23903 where
+
+import Data.Kind(Type)
+import GHC.Exts(Float#, Int#, RuntimeRep(FloatRep, IntRep), TYPE)
+
+type Rep :: Type -> RuntimeRep
+type family Rep t where
+ Rep Int = IntRep
+ Rep Float = FloatRep
+
+type Unbox :: forall (t :: Type) -> TYPE (Rep t)
+type family Unbox t where
+ Unbox Int = Int#
+ Unbox Float = Float#
+
+type family a #-> b where
+ a #-> b = Unbox a -> b
+
+f :: a #-> ()
+f _ = ()
=====================================
testsuite/tests/rep-poly/T23903.stderr
=====================================
@@ -0,0 +1,10 @@
+
+T23903.hs:21:1: error: [GHC-55287]
+ • The first pattern in the equation for ‘f’
+ does not have a fixed runtime representation.
+ Its type is:
+ p0 :: TYPE c0
+ Cannot unify ‘Rep a’ with the type variable ‘c0’
+ because the former is not a concrete ‘RuntimeRep’.
+ • The equation for ‘f’ has one value argument,
+ but its type ‘a #-> ()’ has none
=====================================
testsuite/tests/rep-poly/all.T
=====================================
@@ -36,6 +36,7 @@ test('T23051', normal, compile_fail, [''])
test('T23153', normal, compile_fail, [''])
test('T23154', normal, compile_fail, [''])
test('T23176', normal, compile_fail, ['-XPartialTypeSignatures -fdefer-out-of-scope-variables'])
+test('T23903', normal, compile_fail, [''])
test('EtaExpandDataCon', normal, compile, ['-O'])
test('EtaExpandStupid1', normal, compile, ['-Wno-deprecated-flags'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3054fd6df18ff32c4bf24d07d130102e52242c80
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3054fd6df18ff32c4bf24d07d130102e52242c80
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/20230829/90c60572/attachment-0001.html>
More information about the ghc-commits
mailing list