#3163: quantified types fail to match in GADT case
-------------------------+--------------------------------------------------
Reporter: Scott Turner | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 6.10.1 | Severity: normal
Keywords: | Testcase:
Os: Linux | Architecture: x86
-------------------------+--------------------------------------------------
{{{
{-# LANGUAGE GADTs, RankNTypes, ImpredicativeTypes #-}
module Report (eval) where
data Taker a where
Unreached :: Taker (forall s. s)
eval :: a -> Taker a -> (forall t. t)
eval x c = case c of
Unreached -> x
}}}
I wanted the quantified types to match and the code to get past the type-
checker, as it would if the forall type annotations were replaced with any
ordinary type. However, ghc reported:
{{{
Couldn't match expected type `t'
against inferred type `forall s. s'
`t' is a rigid type variable bound by
the type signature for `eval' at ghc_report.hs:7:32
In the expression: x
In a case alternative: Unreached -> x
In the expression: case c of { Unreached -> x }
}}}
I was unable to get around this problem by adding type annotations.
However, I did get around it by using a similar type
{{{
data Z = Z (forall t.t)
}}}
instead of the bare forall type.
----
{{{
(yawl:~/programs/cat_type) scott% ghc -v -dcore-lint ghc_report.hs
Glasgow Haskell Compiler, Version 6.10.1, for Haskell 98, stage 2 booted
by GHC version 6.10.1
Using package config file: /usr/lib/ghc-6.10.1/./package.conf
hiding package base-3.0.3.0 to avoid conflict with later version
base-4.0.0.0
hiding package filepath-1.1.0.1 to avoid conflict with later version
filepath-1.1.0.2
hiding package Cabal-1.6.0.1 to avoid conflict with later version
Cabal-1.6.0.2
hiding package QuickCheck-1.2.0.0 to avoid conflict with later version
QuickCheck-2.1.0.1
hiding package parsec-2.1.0.1 to avoid conflict with later version
parsec-3.0.0
wired-in package ghc-prim mapped to ghc-prim-0.1.0.0
wired-in package integer mapped to integer-0.1.0.0
wired-in package base mapped to base-4.0.0.0
wired-in package rts mapped to rts-1.0
wired-in package haskell98 mapped to haskell98-1.0.1.0
wired-in package syb mapped to syb-0.1.0.0
wired-in package template-haskell mapped to template-haskell-2.3.0.0
wired-in package dph-seq[""] not found.
wired-in package dph-par[""] not found.
Hsc static flags: -static
Created temporary directory: /tmp/ghc26608_0
*** Checking old interface for main:Report:
*** Parser:
*** Renamer/typechecker:
ghc_report.hs:9:17:
Couldn't match expected type `t'
against inferred type `forall s. s'
`t' is a rigid type variable bound by
the type signature for `eval' at ghc_report.hs:7:32
In the expression: x
In a case alternative: Unreached -> x
In the expression: case c of { Unreached -> x }
*** Deleting temp files:
Deleting: /tmp/ghc26608_0/ghc26608_0.s
Warning: deleting non-existent /tmp/ghc26608_0/ghc26608_0.s
*** Deleting temp dirs:
Deleting: /tmp/ghc26608_0
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3163>
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