[GHC] #11186: Give strong preference to type variable names in scope when reporting hole contexts
GHC
ghc-devs at haskell.org
Sat Dec 19 06:10:54 UTC 2015
#11186: Give strong preference to type variable names in scope when reporting hole
contexts
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.2
checker) |
Resolution: | Keywords: typed-holes
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by dfeuer):
Replying to [comment:1 simonpj]:
> Can you give a concrete example?
I finally found one, attempting to figure out how to write something like
`reverse` for type-aligned lists. In this case, I use a pattern signature
to name an existentially quantified type, but GHC's message doesn't seem
to respect that.
{{{#!hs
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
module TAList where
import Control.Category
import Prelude hiding ((.), id)
data TAList (cat :: k -> k -> *) (x :: k) (z :: k) where
Nil :: TAList cat x x
(:<) :: cat b c -> TAList cat a b -> TAList cat a c
infixr 5 :<
newtype Op cat x y = Op {op :: cat y x}
reverseOntoTA :: TAList cat b d -> TAList (Op cat) d a -> TAList (Op cat)
d a
reverseOntoTA Nil ys = ys
reverseOntoTA ((x :: cat c d) :< (xs :: TAList cat b c)) ys = _
}}}
I named the unknown type variable `c`, but GHC says:
{{{
Relevant bindings include
ys :: TAList (Op cat) d a (bound at TAList.hs:32:58)
xs :: TAList cat b b1 (bound at TAList.hs:32:35)
x :: cat b1 d (bound at TAList.hs:32:17)
reverseOntoTA :: TAList cat b d
-> TAList (Op cat) d a -> TAList (Op cat) d a
}}}
That is, it's decided to name that variable `b1` instead.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11186#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list