[GHC] #8214: 'Untouchable' error in list comprehension

#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

#8214: 'Untouchable' error in list comprehension ----------------------------------------------+---------------------------- Reporter: MartijnVanSteenbergen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Changes (by MartijnVanSteenbergen): * failure: None/Unknown => GHC rejects valid program -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8214#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8214: 'Untouchable' error in list comprehension ----------------------------------------------+---------------------------- Reporter: MartijnVanSteenbergen | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.3 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: The error message is obscure (I'm sorry about that) but it's right. Consider these two variants {{{ foo1 = map (\X -> ()) [] foo2 = map f [] where f X = () }}} (Incidentally, in HEAD it makes no difference whether or not `foo` has a signature `foo :: Bool`, nor `foo1` or `foo2`.) It's easiest to think about `foo2`. What is `f`'s type? Well, you say, `f :: X a -> ()`. But suppose X had been defined {{{ data X1 a where X :: X () }}} Then `f` could also have type `f :: X a -> a`. This is the classic example of not having most general types for GADTs. GHC isn't clever enough to exploit the fact that in the particular example you give there is only one type; the [http://haskell.org/haskellwiki/Simonpj/Talk:OutsideIn Outside-In algorithm] rejects `f`. In `foo` the question is "what is the type of `[ () | X <- [] ]`. If we had type `X1` then it could be `[()]` or `forall a. [a]`. In this case it doesn't matter what the answer is, but if there was overloading involved it might. Solution: tell GHC which type the list has, thus: {{{ foo = null ([ () | X <- [] ] :: [()]) }}} This looks a bit stupid in this very cut-down example, but I suspect it'd make more sense in a real program. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8214#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8214: 'Untouchable' error in list comprehension ----------------------------------------------+---------------------------- Reporter: MartijnVanSteenbergen | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.3 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Comment (by MartijnVanSteenbergen): Alright Simon, thank you for explaining, this makes sense. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8214#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC