--- /dev/null
+{-# OPTIONS_GHC -fdefer-type-errors #-}
+{-# LANGUAGE ImpredicativeTypes #-}
+
+module T9834 where
+import Control.Applicative
+import Data.Functor.Identity
+
+type Nat f g = forall a. f a -> g a
+
+newtype Comp p q a = Comp (p (q a))
+
+liftOuter :: (Functor p, Applicative q) => p a -> (Comp p q) a
+liftOuter pa = Comp (pure <$> pa)
+
+runIdComp :: Functor p => Comp p Identity a -> p a
+runIdComp (Comp p) = runIdentity <$> p
+
+wrapIdComp :: Applicative p => (forall q. Applicative q => Nat (Comp p q) (Comp p q)) -> p a -> p a
+wrapIdComp f = runIdComp . f . liftOuter
+
+class Applicative p => ApplicativeFix p where
+ afix :: (forall q. Applicative q => (Comp p q) a -> (Comp p q) a) -> p a
+ afix = wrapIdComp
\ No newline at end of file
--- /dev/null
+
+T9834.hs:23:10: Warning:
+ Couldn't match type ‘p’ with ‘(->) (p a0)’
+ ‘p’ is a rigid type variable bound by
+ the class declaration for ‘ApplicativeFix’ at T9834.hs:21:39
+ Expected type: (forall (q :: * -> *).
+ Applicative q =>
+ Comp p q a -> Comp p q a)
+ -> p a
+ Actual type: (forall (q :: * -> *).
+ Applicative q =>
+ Nat (Comp p q) (Comp p q))
+ -> p a0 -> p a0
+ Relevant bindings include
+ afix :: (forall (q :: * -> *).
+ Applicative q =>
+ Comp p q a -> Comp p q a)
+ -> p a
+ (bound at T9834.hs:23:3)
+ In the expression: wrapIdComp
+ In an equation for ‘afix’: afix = wrapIdComp
+
+T9834.hs:23:10: Warning:
+ Couldn't match type ‘a’ with ‘p a0’
+ ‘a’ is a rigid type variable bound by
+ the type signature for
+ afix :: (forall (q :: * -> *).
+ Applicative q =>
+ Comp p q a -> Comp p q a)
+ -> p a
+ at T9834.hs:22:11
+ Expected type: (forall (q :: * -> *).
+ Applicative q =>
+ Comp p q a -> Comp p q a)
+ -> p a
+ Actual type: (forall (q :: * -> *).
+ Applicative q =>
+ Nat (Comp p q) (Comp p q))
+ -> p a0 -> p a0
+ Relevant bindings include
+ afix :: (forall (q :: * -> *).
+ Applicative q =>
+ Comp p q a -> Comp p q a)
+ -> p a
+ (bound at T9834.hs:23:3)
+ In the expression: wrapIdComp
+ In an equation for ‘afix’: afix = wrapIdComp
+
+T9834.hs:23:10: Warning:
+ Couldn't match type ‘a’ with ‘a1’
+ ‘a’ is a rigid type variable bound by
+ the type signature for
+ afix :: (forall (q :: * -> *).
+ Applicative q =>
+ Comp p q a -> Comp p q a)
+ -> p a
+ at T9834.hs:22:11
+ ‘a1’ is a rigid type variable bound by
+ a type expected by the context:
+ Applicative q => Comp p q a1 -> Comp p q a1
+ at T9834.hs:23:10
+ Expected type: Comp p q a1 -> Comp p q a1
+ Actual type: Comp p q a -> Comp p q a
+ Relevant bindings include
+ afix :: (forall (q :: * -> *).
+ Applicative q =>
+ Comp p q a -> Comp p q a)
+ -> p a
+ (bound at T9834.hs:23:3)
+ In the expression: wrapIdComp
+ In an equation for ‘afix’: afix = wrapIdComp