[GHC] #8214: 'Untouchable' error in list comprehension
GHC
ghc-devs at haskell.org
Mon Sep 2 14:42:26 CEST 2013
#8214: 'Untouchable' error in list comprehension
-------------------------------------------+-------------------------------
Reporter: MartijnVanSteenbergen | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type checker) | Version: 7.6.3
Keywords: | Operating System:
Architecture: Unknown/Multiple | Unknown/Multiple
Difficulty: Unknown | Type of failure:
Blocked By: | None/Unknown
Related Tickets: | Test Case:
| Blocking:
-------------------------------------------+-------------------------------
Hi,
I think this program should compile but it doesn't:
{{{
{-# LANGUAGE GADTs #-}
data X a where X :: X Int
foo :: Bool
foo = null [ () | X <- [] ]
}}}
It fails with:
{{{
Couldn't match expected type `a0' with actual type `()'
`a0' is untouchable
inside the constraints (t_g ~ Int)
bound at a pattern with constructor
X :: X Int,
in a pattern binding in
list comprehension
In the pattern: X
In a stmt of a list comprehension: X <- []
In the first argument of `null', namely `[() | X <- []]'
}}}
If I remove the type declaration GHC compiles without errors and happily
infers {{{foo :: Bool}}}.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8214>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list