[GHC] #12427: Type inference regression with RankNTypes (GHC 8.1)

GHC ghc-devs at haskell.org
Sat Jul 23 09:21:17 UTC 2016


#12427: Type inference regression with RankNTypes (GHC 8.1)
-------------------------------------+-------------------------------------
           Reporter:  thomie         |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.1
  (Type checker)                     |
           Keywords:  RankNTypes     |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following module compiles fine with ghc-8.0.1:
 {{{#!hs
 {-# LANGUAGE RankNTypes #-}

 module Acquire where

 newtype Acquire a = Acquire {unAcquire :: (forall b. b -> b) -> IO a}

 instance Functor Acquire where
     fmap = undefined

 instance Applicative Acquire where
     pure = undefined
     (<*>) = undefined

 instance Monad Acquire where
     Acquire f >>= g' = Acquire $ \restore -> do
         x <- f restore
         let Acquire g = g' x
         -- let g = unAcquire (g' x)
         g restore
 }}}

 HEAD (83e4f49577665278fe08fbaafe2239553f3c448e, ghc-8.1.20160720) reports:
 {{{
 Acquire.hs:17:21: error:
     • Couldn't match expected type ‘t’
                   with actual type ‘(forall b1. b1 -> b1) -> IO b’
       ‘t’ is a rigid type variable bound by
         the inferred type of g :: t at Acquire.hs:17:13-28
     • In the pattern: Acquire g
       In a pattern binding: Acquire g = g' x
       In the expression:
         do { x <- f restore;
              let Acquire g = g' x;
              g restore }
     • Relevant bindings include
         g' :: a -> Acquire b (bound at Acquire.hs:15:19)
         (>>=) :: Acquire a -> (a -> Acquire b) -> Acquire b
           (bound at Acquire.hs:15:15)
 }}}

 This example is reduced from the `recourcet` package on Hackage, module
 `Data.Acquire.Internal`.

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


More information about the ghc-tickets mailing list