[GHC] #8428: Incorrect type formatting in error messages

GHC ghc-devs
Wed Oct 9 15:57:17 UTC 2013


#8428: Incorrect type formatting in error messages
------------------------------------+-------------------------------------
       Reporter:  klao              |             Owner:
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Compiler          |           Version:  7.6.3
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 I've been trying to write a type signature to something completely
 analogous to `runST . runIdentityT`, and failing miserably for a long
 time.

 At some point I had the following:

 {{{#!haskell
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ImpredicativeTypes #-}

 module Test where

 import Control.Monad.ST
 import Control.Monad.Trans.Identity

 runIdST :: IdentityT (forall s. ST s) a -> a
 runIdST = runST . runIdentityT
 }}}

 You can see that I was very confused about `forall` here (probably still
 am), but what makes it much worse is the error message with which this
 fails:

 {{{
 src/Test.hs:10:19:
     Couldn't match type `forall s. ST s a' with `forall s. ST s a'
     Expected type: IdentityT (forall s. ST s) a -> forall s. ST s a
       Actual type: IdentityT (forall s. ST s) a -> forall s. ST s a
     In the second argument of `(.)', namely `runIdentityT'
     In the expression: runST . runIdentityT
     In an equation for `runIdST': runIdST = runST . runIdentityT
 }}}

 It says it couldn't match `forall s. ST s a` with `forall s. ST s a`.
 What's up with that?!

 This has lead me to a long diversion. Finally, we found the right type for
 this function (and discovered that the problem is also in the `(.)`, which
 doesn't have the same special treatment as `($)`), and afterwards we
 realized, that types in the above error message ''are'' actually
 different.

 One is `(forall s. (ST s)) a`, and the other is `forall s. ((ST s) a)`.
 But they are presented in exactly the same way!

 The issue is in the `instance Outputable Type`, which has too simplistic
 precedence rules, I guess.

 Thanks to `@errge` for help with debugging this.

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



More information about the ghc-tickets mailing list