[commit: ghc] master: Add regression test for #11766 (72835ff)

git at git.haskell.org git at git.haskell.org
Sat May 26 14:30:21 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/72835ff223e103c8a187f782146e5f452d74aef6/ghc

>---------------------------------------------------------------

commit 72835ff223e103c8a187f782146e5f452d74aef6
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Sat May 26 10:29:22 2018 -0400

    Add regression test for #11766


>---------------------------------------------------------------

72835ff223e103c8a187f782146e5f452d74aef6
 testsuite/tests/typecheck/should_compile/T11766.hs | 30 ++++++++++++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  1 +
 2 files changed, 31 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T11766.hs b/testsuite/tests/typecheck/should_compile/T11766.hs
new file mode 100644
index 0000000..123dec0
--- /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 afba48d..0d5b210 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, [''])



More information about the ghc-commits mailing list