[GHC] #11642: Typechecker doesn't use evidence available from pattern synonym?
GHC
ghc-devs at haskell.org
Thu Feb 25 16:27:00 UTC 2016
#11642: Typechecker doesn't use evidence available from pattern synonym?
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner:
Type: bug | Status: new
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 7.10.3
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Either that or I am missing something...
Consider the following,
{{{#!hs
{-# LANGUAGE GADTs, PolyKinds, PatternSynonyms, RankNTypes,
TypeOperators, ViewPatterns #-}
module Test where
data TypeRep (a :: k) where
TypeCon :: String -> TypeRep a
TypeApp :: TypeRep f -> TypeRep x -> TypeRep (f x)
data TypeRepX where
TypeRepX :: TypeRep a -> TypeRepX
data (a :: k1) :~~: (b :: k2) where
HRefl :: a :~~: a
trArrow :: TypeRep (->)
trArrow = undefined
eqTypeRep :: TypeRep (a :: k1) -> TypeRep (b :: k2) -> Maybe (a :~~: b)
eqTypeRep = undefined
typeRepKind :: forall (k :: *). forall (a :: k). TypeRep a -> TypeRep k
typeRepKind = undefined
pattern TRFun :: forall fun. ()
=> forall arg res. (fun ~ (arg -> res))
=> TypeRep arg
-> TypeRep res
-> TypeRep fun
pattern TRFun arg res <- TypeApp (TypeApp (eqTypeRep trArrow -> Just
HRefl) arg) res
buildApp :: TypeRepX -> TypeRepX -> TypeRepX
buildApp (TypeRepX f) (TypeRepX x) =
case typeRepKind f of
TRFun arg _ ->
case eqTypeRep arg x of
Just HRefl ->
TypeRepX $ TypeApp f x
}}}
This fails with,
{{{
$ ghc Test.hs -fprint-explicit-kinds
[1 of 1] Compiling Test ( Test.hs, Test.o )
Test.hs:38:30: error:
• Expected kind ‘TypeRep (k1 -> res) a’,
but ‘f’ has kind ‘TypeRep k a’
• In the first argument of ‘TypeApp’, namely ‘f’
In the second argument of ‘($)’, namely ‘TypeApp f x’
In the expression: TypeRepX $ TypeApp f x
• Relevant bindings include
arg :: TypeRep * arg (bound at Test.hs:35:11)
}}}
That is, the typechecker doesn't believe that `f`'s type (why is it saying
"kind" here?), `TypeRep k a`, will unify with `TypeRep (k1 -> res) a`,
despite the `TRFun` pattern match, which should have brought into scope
that `k ~ (arg -> res)`.
This was tested with a recent snapshot from `ghc-8.0`
(23baff798aca5856650508ad0f7727045efe3680).
Am I missing something here or is this a bug?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11642>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list