[GHC] #10443: Regression in forall typechecking

GHC ghc-devs at haskell.org
Sun May 24 15:07:54 UTC 2015


#10443: Regression in forall typechecking
-------------------------------------+-------------------------------------
              Reporter:  alanz       |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  high        |         Milestone:  7.10.2
             Component:  Compiler    |           Version:  7.10.1
  (Type checker)                     |  Operating System:  Unknown/Multiple
              Keywords:              |   Type of failure:  GHC rejects
          Architecture:              |  valid program
  Unknown/Multiple                   |        Blocked By:
             Test Case:              |   Related Tickets:
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 The following bug showed up when trying to install ghc-mod against the
 current ghc-7.10 branch

 Ths code below, from
 https://github.com/DanielG/ghc-
 mod/blob/b52c0a5d767282369f2748c5ec070b802ed8e23c/Language/Haskell/GhcMod/Monad/Types.hs#L346

 {{{#!hs
 instance (MonadBaseControl IO m) => MonadBaseControl IO (GhcModT m) where
     type StM (GhcModT m) a =
           StM (StateT GhcModState
                 (ErrorT GhcModError
                   (JournalT GhcModLog
                     (ReaderT GhcModEnv m) ) ) ) a
     liftBaseWith f = GhcModT . liftBaseWith $ \runInBase ->
         f $ runInBase . unGhcModT

     restoreM = GhcModT . restoreM
     {-# INLINE liftBaseWith #-}
     {-# INLINE restoreM #-}
 }}}

 Which compiles fine with GHC 7.10.1 now has the error

 {{{
 Language/Haskell/GhcMod/Monad/Types.hs:346:13:
     Couldn't match expected type ‘StateT
                                     GhcModState
                                     (ErrorT GhcModError (JournalT
 GhcModLog (ReaderT GhcModEnv m)))
                                     a1
                                   -> IO (StM m (Either GhcModError (a1,
 GhcModState), GhcModLog))’
                 with actual type ‘forall a2.
                                   StateT
                                     GhcModState
                                     (ErrorT GhcModError (JournalT
 GhcModLog (ReaderT GhcModEnv m)))
                                     a2
                                   -> IO
                                        (StM
                                           (StateT
                                              GhcModState
                                              (ErrorT
                                                 GhcModError
                                                 (JournalT GhcModLog
 (ReaderT GhcModEnv m))))
                                           a2)’
     Relevant bindings include
       runInBase :: forall a.
                    StateT
                      GhcModState
                      (ErrorT GhcModError (JournalT GhcModLog (ReaderT
 GhcModEnv m)))
                      a
                    -> IO
                         (StM
                            (StateT
                               GhcModState
                               (ErrorT GhcModError (JournalT GhcModLog
 (ReaderT GhcModEnv m))))
                            a)
         (bound at Language/Haskell/GhcMod/Monad/Types.hs:345:48)
       f :: RunInBase (GhcModT m) IO -> IO a
         (bound at Language/Haskell/GhcMod/Monad/Types.hs:345:18)
       liftBaseWith :: (RunInBase (GhcModT m) IO -> IO a) -> GhcModT m a
         (bound at Language/Haskell/GhcMod/Monad/Types.hs:345:5)
     In the first argument of ‘(.)’, namely ‘runInBase’
     In the second argument of ‘($)’, namely ‘runInBase . unGhcModT’
 }}}

 A laborious git bisect tracked it down to

 {{{
 681d82c0d44f06f0b958b75778c30b0910df982b is the first bad commit
 commit 681d82c0d44f06f0b958b75778c30b0910df982b
 Author: Simon Peyton Jones <simonpj at microsoft.com>
 Date:   Tue Apr 7 14:45:04 2015 +0100

     Look inside synonyms for foralls when unifying

     This fixes Trac #10194

     (cherry picked from commit 553c5182156c5e4c15e3bd1c17c6d83a95a6c408)

 :040000 040000 1f0e62661ed1c48a9cbfab72ca3e38bb9e501412
 ef6786fdb952d3446121b27b56f6103533d52356 M      compiler
 :040000 040000 d607f1bff94578b0677df9cba01371dad6b26a32
 ac715cec4fd8d43a53ecee132eae2b4c0c65e31a M      testsuite
 }}}

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


More information about the ghc-tickets mailing list