diff --git a/testsuite/tests/typecheck/should_fail/T24064.hs b/testsuite/tests/typecheck/should_fail/T24064.hs new file mode 100644 index 0000000000000000000000000000000000000000..9153830cdf5eb70fd624a180713ece6427e64052 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T24064.hs @@ -0,0 +1,48 @@ +{-# LANGUAGE Haskell2010 #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeFamilies #-} + +module T24064 where + +class C1 b where + type F1 b + +class C2 (m :: * -> *) where + type F2 m + +class C3 r where + type F3 r + +class G t m where + g :: m a -> t m a + +data Y + +data X e a + +data H a + +data S a + +fun1 :: X e () +fun1 = undefined + +fun2 :: S () +fun2 = undefined + +fun3 :: H () +fun3 = undefined + +fun4 :: (F3 r ~ F1 (F2 m)) => r -> m () +fun4 = undefined + +test :: (C2 m, F2 m ~ Y) => m () +test = do + fun1 + fun2 + g fun3 + fun4 undefined + +main :: IO () +main = pure () diff --git a/testsuite/tests/typecheck/should_fail/T24064.stderr b/testsuite/tests/typecheck/should_fail/T24064.stderr new file mode 100644 index 0000000000000000000000000000000000000000..2b252dca782c72fa3df0a0b8407ccc2cf6b5deed --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T24064.stderr @@ -0,0 +1,26 @@ + +T24064.hs:42:3: error: [GHC-25897] + • Could not deduce ‘m ~ X e0’ + from the context: (C2 m, F2 m ~ Y) + bound by the type signature for: + test :: forall (m :: * -> *). (C2 m, F2 m ~ Y) => m () + at T24064.hs:40:1-32 + Expected: m () + Actual: X e0 () + ‘m’ is a rigid type variable bound by + the type signature for: + test :: forall (m :: * -> *). (C2 m, F2 m ~ Y) => m () + at T24064.hs:40:1-32 + • In a stmt of a 'do' block: fun1 + In the expression: + do fun1 + fun2 + g fun3 + fun4 undefined + In an equation for ‘test’: + test + = do fun1 + fun2 + g fun3 + .... + • Relevant bindings include test :: m () (bound at T24064.hs:41:1) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 92bdeb40cb071629954020bd92568bc6d5d03bbc..7db8f53be6e38eae994f09108d1038ff6101e8ef 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -704,3 +704,4 @@ test('T22478c', normal, compile_fail, ['']) test('T23776', normal, compile, ['']) # to become an error in GHC 9.12 test('T17940', normal, compile_fail, ['']) test('ErrorIndexLinks', normal, compile_fail, ['-fprint-error-index-links=always']) +test('T24064', normal, compile_fail, [''])