Skip to content
Snippets Groups Projects
Commit 72835ff2 authored by Ryan Scott's avatar Ryan Scott
Browse files

Add regression test for #11766

parent 11eed2f4
No related merge requests found
{-# 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
......@@ -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, [''])
......
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