
#12431: Type checker rejects valid program -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (Type checker) | Keywords: | 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: -------------------------------------+------------------------------------- Since at least 6e280c2c5b2903ae38f4da15a41ea94793907407 GHC fails to compile `resourcet` due to a likely erroneous type error. Here is a minimal case that reproduces the error, {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE FlexibleContexts #-} module Hi where import Control.Monad (liftM, ap) data Allocated a = Allocated a newtype Acquire a = Acquire ((forall b. IO b -> IO b) -> IO (Allocated a)) instance Functor Acquire where fmap = liftM instance Applicative Acquire where pure a = Acquire (\_ -> return (Allocated a)) (<*>) = ap instance Monad Acquire where return = pure Acquire f >>= g' = Acquire $ \restore -> do Allocated x <- f restore let Acquire g = g' x Allocated y <- g restore return $! Allocated y }}} This fails with, {{{ $ ghc Hi.hs [1 of 1] Compiling Hi ( Hi.hs, Hi.o ) Hi.hs:22:21: error: • Couldn't match expected type ‘t’ with actual type ‘(forall b1. IO b1 -> IO b1) -> IO (Allocated b)’ ‘t’ is a rigid type variable bound by the inferred type of g :: t at Hi.hs:22:13-28 • In the pattern: Acquire g In a pattern binding: Acquire g = g' x In the expression: do { Allocated x <- f restore; let Acquire g = g' x; Allocated y <- g restore; return $! Allocated y } • Relevant bindings include g' :: a -> Acquire b (bound at Hi.hs:20:19) (>>=) :: Acquire a -> (a -> Acquire b) -> Acquire b (bound at Hi.hs:20:15) }}} Despite compiling with 8.0.1 and earlier versions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12431 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler