diff --git a/testsuite/tests/rep-poly/T23903.hs b/testsuite/tests/rep-poly/T23903.hs new file mode 100644 index 0000000000000000000000000000000000000000..6f204a029e681688c0f2ff3301f9f04bef0a7bb5 --- /dev/null +++ b/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 _ = () diff --git a/testsuite/tests/rep-poly/T23903.stderr b/testsuite/tests/rep-poly/T23903.stderr new file mode 100644 index 0000000000000000000000000000000000000000..72743fa1539078ce67659ccf88b248c877b9a181 --- /dev/null +++ b/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 diff --git a/testsuite/tests/rep-poly/all.T b/testsuite/tests/rep-poly/all.T index 4515cf2bc742af782f161b4ec8e479e14f2c4183..32a1fa15fab75220a71df3a4c80e654241da8263 100644 --- a/testsuite/tests/rep-poly/all.T +++ b/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'])