
#7842: Incorrect checking of let-bindings in recursive do --------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: normal | Component: Compiler (Type checker) Version: 7.7 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: GHC rejects valid program | Blockedby: Blocking: | Related: --------------------------------------+------------------------------------- I have run into a problem with the type-checking of recursive do blocks, which reduces to the following example: {{{ {-# LANGUAGE RecursiveDo #-} module Bug where bug :: (Int -> IO Int) -> IO (Bool, Char) bug m = mdo i <- m i1 -- RECURSION let i1 :: Int i1 = i -- RECURSION -- This appears to be monomorphic, despite the type signature. f :: b -> b f x = x return (f True, f 'a') }}} This program is rejected with the errors shown below. The problem appears to be that somehow `f` has become monomorphic, despite its type-signature. This seems to happen only when `f` is part of a `let` block that is also involved in the recursion. Here is the error reported by GHC 7.7.20130215: {{{ Bug.hs:15:23: Couldn't match expected type `Char' with actual type `Bool' In the return type of a call of `f' In the expression: f 'a' In the first argument of `return', namely `(f True, f 'a')' Bug.hs:15:25: Couldn't match expected type `Bool' with actual type `Char' In the first argument of `f', namely 'a' In the expression: f 'a' In the first argument of `return', namely `(f True, f 'a')' }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7842 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler