Type error: Expected type: T. Actual type T ???

Hello, I'm working on a new design of monad-control[1]. However I get a type error I don't understand. Here's an isolated example: {-# LANGUAGE UnicodeSyntax, RankNTypes, TypeFamilies #-} class MonadTransControl t where type St t ∷ * → * liftControl ∷ Monad m ⇒ (Run t → m α) → t m α restore ∷ Monad o ⇒ St t γ → t o γ type Run t = ∀ n β. Monad n ⇒ t n β → n (St t β) foo :: (Monad m, MonadTransControl t) => (Run t -> m α) -> t m α foo f = liftControl f Type checking 'foo' this gives the following error: Couldn't match expected type `Run t' with actual type `Run t' Expected type: Run t -> m α Actual type: Run t -> m α In the first argument of `liftControl', namely `f' In the expression: liftControl f When I remove the type annotation of 'foo' the program type checks. But when I ask ghci the type of 'foo' it tells me it's the same type:
:t foo foo :: (Monad m, MonadTransControl t) => (Run t -> m α) -> t m α
Is this a bug in GHC? I'm using ghc-7.2.1. Regards, Bas [1] http://hackage.haskell.org/package/monad-control

On Sat, Oct 29, 2011 at 16:18, Bas van Dijk
type Run t = ∀ n β. Monad n ⇒ t n β → n (St t β)
foo :: (Monad m, MonadTransControl t) => (Run t -> m α) -> t m α foo f = liftControl f
Type checking 'foo' this gives the following error:
Couldn't match expected type `Run t' with actual type `Run t'
I *think* this might be odd reporting combined with an expected behavior: since the forall is embedded in the "type" declaration, the "t" inside the parens is not the same as the one outside (because each one has its own "forall" associated with it). If the type is inferred, the inference gets the association right, but the explicit "forall" from the definition of (Run t) used inside the parens tells ghc that they should be different. (I *think* this might mean manually expanding "Run t" and moving the "forall" to the outer scope, but now we're into territory I don't understand very well.) -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On 10/29/11 7:33 PM, Brandon Allbery wrote:
On Sat, Oct 29, 2011 at 16:18, Bas van Dijk
wrote: type Run t = ∀ n β. Monad n ⇒ t n β → n (St t β)
foo :: (Monad m, MonadTransControl t) => (Run t -> m α) -> t m α foo f = liftControl f
Type checking 'foo' this gives the following error:
Couldn't match expected type `Run t' with actual type `Run t'
I *think* this might be odd reporting combined with an expected behavior: since the forall is embedded in the "type" declaration, the "t" inside the parens is not the same as the one outside (because each one has its own "forall" associated with it).
But t is an argument to the type alias, not quantified in it. Shouldn't the type of foo be: forall t m a . (Monad m, MonadTransControl t) => (Run t -> m a) -> t m a ? -- Live well, ~wren

On 30 October 2011 02:29, wren ng thornton
... Shouldn't the type of foo be:
forall t m a . (Monad m, MonadTransControl t) => (Run t -> m a) -> t m a
?
Yes, that's the proper quantification. One more fact: when I change the associated type synonym to a associated data type the error disappears. Bas

I reported this in the issue tracker: http://hackage.haskell.org/trac/ghc/ticket/5595 Bas
participants (3)
-
Bas van Dijk
-
Brandon Allbery
-
wren ng thornton