#5678: Unexpected cryptic GADT type error
-----------------------------------+----------------------------------------
Reporter: mikhail.vorozhtsov | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.3 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
-----------------------------------+----------------------------------------
Consider the following module:
{{{
{-# LANGUAGE GADTs #-}
module Bug where
import Control.Monad (void)
data D = D
data G a where
G :: G Int
ok :: (Functor m, Monad m) => m ()
ok = void $ case D of D -> return "xyz"
bad :: (Functor m, Monad m) => m ()
bad = void $ case G of G -> return "xyz"
}}}
Function "ok" is accepted by GHC, but function "bad" triggers a cryptic
type error:
{{{
Bug.hs:16:24:
Couldn't match type `a0' with `[Char]'
`a0' is untouchable
inside the constraints (Int ~ Int)
bound at a pattern with constructor
G :: G Int,
in a case alternative
In the pattern: G
In a case alternative: G -> return "xyz"
In the second argument of `($)', namely
`case G of { G -> return "xyz" }'
}}}
I hope this is a bug in typechecker. Tested on 7.2.2 and 7.3.20111130.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5678>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs