#5595: Type error: expected type = actual type ???
---------------------------------+------------------------------------------
    Reporter:  basvandijk        |       Owner:                           
        Type:  bug               |      Status:  new                      
    Priority:  normal            |   Component:  Compiler                 
     Version:  7.2.1             |    Keywords:                           
    Testcase:                    |   Blockedby:                           
          Os:  Unknown/Multiple  |    Blocking:                           
Architecture:  Unknown/Multiple  |     Failure:  GHC rejects valid program
---------------------------------+------------------------------------------
 As [http://www.haskell.org/pipermail/glasgow-haskell-
 users/2011-October/021109.html mentioned] on the glasgow-haskell-users
 mailinglist, I'm working on a new design of
 [http://hackage.haskell.org/package/monad-control monad-control]. 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 α
 }}}

 Note that when I change the associated type synonym to a associated data
 type the error disappears.

 Is this a bug in GHC?

 I'm using ghc-7.2.1.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5595>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to