Skip to content
Snippets Groups Projects
Commit 3054fd6d authored by Krzysztof Gogolewski's avatar Krzysztof Gogolewski Committed by Marge Bot
Browse files

Add a regression test for #23903

The bug has been fixed by commit bad2f8b8.
parent b60d6576
No related branches found
No related tags found
No related merge requests found
{-# 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 _ = ()
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
......@@ -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'])
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment