--- /dev/null
+{-# LANGUAGE RankNTypes #-}
+module T7264 where
+
+data Foo = Foo (forall r . r -> String)
+
+mmap :: (a->b) -> Maybe a -> Maybe b
+mmap f (Just x) = Just (f x)
+mmap f Nothing = Nothing
+
+-- mkFoo2 :: (forall r. r -> String) -> Maybe Foo
+-- Should be rejected because it requires instantiating
+-- mmap at a polymorphic type
+mkFoo2 val = mmap Foo (Just val)
--- /dev/null
+
+T7264.hs:13:19:
+ Couldn't match type `a' with `forall r. r -> String'
+ `a' is untouchable
+ inside the constraints ()
+ bound by the inferred type of mkFoo2 :: a -> Maybe Foo
+ at T7264.hs:13:1-32
+ `a' is a rigid type variable bound by
+ the inferred type of mkFoo2 :: a -> Maybe Foo at T7264.hs:13:1
+ Expected type: a -> Foo
+ Actual type: (forall r. r -> String) -> Foo
+ Relevant bindings include
+ mkFoo2 :: a -> Maybe Foo (bound at T7264.hs:13:1)
+ val :: a (bound at T7264.hs:13:8)
+ In the first argument of `mmap', namely `Foo'
+ In the expression: mmap Foo (Just val)
+ In an equation for `mkFoo2': mkFoo2 val = mmap Foo (Just val)
test('T7210', normal, compile_fail, [''])
test('T6161', normal, compile_fail, [''])
test('T7368', normal, compile_fail, [''])
+test('T7264', normal, compile_fail, [''])