[GHC] #7842: Incorrect checking of let-bindings in recursive do
GHC
ghc-devs at haskell.org
Fri Jun 21 21:16:11 CEST 2013
#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:
--------------------------------------+-------------------------------------
Comment(by wvv):
First, it is needed to add extension: Rank2Types:
{{{
{-# LANGUAGE RecursiveDo, Rank2Types #-}
bug :: IO (Char,Bool)
bug = mdo
a <- return b
let f = id
let g :: (forall a. (a -> a) ) -> (Char, Bool)
g f = (f 'a', f True)
b <- return a
return $ g f
}}}
but still error:
{{{
Couldn't match type `a0' with `a'
because type variable `a' would escape its scope
This (rigid, skolem) type variable is bound by
a type expected by the context: a -> a
The following variables have types that mention a0
f :: a0 -> a0 (bound at test2.hs:34:8)
Expected type: a -> a
Actual type: a0 -> a0
In the first argument of `g', namely `f'
In the second argument of `($)', namely `g f'
In a stmt of an 'mdo' block: return $ g f
}}}
Code
{{{
{-# LANGUAGE RecursiveDo, Rank2Types #-}
bug :: IO (Char,Bool)
bug = mdo
let f = id
let g :: (forall a. (a -> a) ) -> (Char, Bool)
g f = (f 'a', f True)
return $ g f
}}}
is OK.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7842#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list