diff --git a/testsuite/tests/typecheck/should_compile/T11766.hs b/testsuite/tests/typecheck/should_compile/T11766.hs new file mode 100644 index 0000000000000000000000000000000000000000..123dec0ad69667084aea440d2d89e7bf208b334d --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T11766.hs @@ -0,0 +1,30 @@ +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE UndecidableInstances #-} +module T11766 where + +import Data.Maybe (isJust) + +data Wrapper a = Wrapper a deriving (Show) + +class Resolution a +instance Resolution (Wrapper a) + +class (Resolution b, Resolution d) => C a b c d | a -> b, c -> d, a d -> c, b c -> a where + cfun :: (b -> d) -> a -> c + +instance {-# OVERLAPPABLE #-} (Resolution b, Resolution d, a ~ b, c ~ d) => C a b c d where + cfun = ($) + +instance {-# OVERLAPPING #-} (C b c d e) => C (Maybe a -> b) c (Maybe a -> d) e where + cfun f b = \x -> cfun f (b x) + +foo :: Maybe a -> Wrapper Bool +foo = Wrapper . isJust + +t1 = cfun id foo $! Nothing +t2 = let f = cfun id foo in f Nothing +t3 = cfun id foo Nothing +t4 = cfun id foo $ Nothing diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index afba48d93ee2015403c02c1f41e83293da84d2e7..0d5b21017f1498d0bcdc9e08a1f509ef0ab5c62f 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -499,6 +499,7 @@ test('T11401', normal, compile, ['']) test('T11699', normal, compile, ['']) test('T11512', normal, compile, ['']) test('T11754', normal, compile, ['']) +test('T11766', normal, compile, ['']) test('T11811', normal, compile, ['']) test('T11793', normal, compile, ['']) test('T11348', normal, compile, [''])