[GHC] #11982: Typechecking fails for parallel monad comprehensions with polymorphic let
GHC
ghc-devs at haskell.org
Tue Apr 26 12:04:54 UTC 2016
#11982: Typechecking fails for parallel monad comprehensions with polymorphic let
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.3
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{
{-# LANGUAGE MonadComprehensions, ParallelListComp #-}
module Foo where
foo xs ys = [ (f y True, f x 'c')
| let f _ z = z, x <- xs
| y <- ys ]
}}}
This fails with
{{{
Foo.hs:5:52: error:
* Cannot instantiate unification variable `t0'
with a type involving foralls: forall t2 t3. t3 -> t2 -> t2
GHC doesn't yet support impredicative polymorphism
* In a stmt of a monad comprehension:
let f _ z = z, x <- xs | y <- ys
In the expression:
[(f y True, f x 'c') | let f _ z = z, x <- xs | y <- ys]
In an equation for `foo':
foo xs ys
= [(f y True, f x 'c') | let f _ z = z, x <- xs | y <- ys]
}}}
NB: `ApplicativeDo` has a related problem: the implementation is quite
different and has the effect of monomorphising the let-bound variable.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11982>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list