Skip to content
Snippets Groups Projects
Commit 9b0d901b authored by Simon Peyton Jones's avatar Simon Peyton Jones Committed by Ben Gamari
Browse files

Regression test for Trac #10390

parent 3f3ac1cb
No related merge requests found
{-# LANGUAGE RankNTypes #-}
module T10390 where
class ApPair r where
apPair :: (forall a . (ApPair a, Num a) => Maybe a) -> Maybe r
instance (ApPair a, ApPair b) => ApPair (a,b) where
apPair = apPair'
apPair' :: (ApPair b, ApPair c)
=> (forall a . (Num a, ApPair a) => Maybe a) -> Maybe (b,c)
-- NB constraints in a different order to apPair
apPair' f = let (Just a) = apPair f
(Just b) = apPair f
in Just $ (a, b)
......@@ -446,3 +446,4 @@ test('T10109', normal, compile, [''])
test('T10335', normal, compile, [''])
test('T10489', normal, compile, [''])
test('T10564', normal, compile, [''])
test('T10390', 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