[GHC] #16050: Instance resolution error message unclear, because of missing kind information
GHC
ghc-devs at haskell.org
Fri Dec 14 21:52:22 UTC 2018
#16050: Instance resolution error message unclear, because of missing kind
information
-------------------------------------+-------------------------------------
Reporter: chessai | Owner: (none)
Type: feature | Status: new
request |
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
consider the following modules:
{{{#!hs
module A where
(.) :: forall (a :: TYPE 'UnliftedRep) (b :: TYPE 'UnliftedRep) (c :: TYPE
'UnliftedRep).
(b -> c)
-> (a -> b)
-> (a -> c)
(.) f g = \x -> f (g x)
data UList (a :: TYPE 'UnliftedRep) where
UNil :: UList a
UCons :: a -> UList a -> UList a
mapFB :: forall (a :: TYPE 'UnliftedRep)
(elt :: TYPE 'UnliftedRep)
(lst :: Type).
(elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
mapFB c f = \x ys -> c (f x) ys
{-# RULES
"mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f . g)
#-}
}}}
{{{#!hs
module B where
import Control.Category ((.))
data UList (a :: TYPE 'UnliftedRep) where
UNil :: UList a
UCons :: a -> UList a -> UList a
mapFB :: forall (a :: TYPE 'UnliftedRep)
(elt :: TYPE 'UnliftedRep)
(lst :: Type).
(elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
mapFB c f = \x ys -> c (f x) ys
{-# RULES
"mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f . g)
#-}
}}}
Module 'A' works fine. Module 'B', fails with the following error:
{{{#!hs
• No instance for (Category (->)) arising from a use of ‘.’
• In the second argument of ‘mapFB’, namely ‘(f . g)’
In the expression: mapFB c (f . g)
When checking the transformation rule "mapFB"
|
line| "mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f . g)
| ^^^
}}}
I expected this failure because of the kind mismatch; the category
instance for `(->)` obviously requires that it be kinded `Type -> Type ->
Type`. However, it confused someone I am teaching, who said to me that
they didn't understand the error, since they expected it to work as `(->)`
does indeed have a Category instance. (They are very unfamiliar with
Levity-Polymorphism).
My question is this: Would it be preferable to include such kind
information in the error message?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16050>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list