Instance resolution error message unclear, because of missing kind information
consider the following modules:
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)
#-}
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:
• 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?
Trac metadata
Trac field | Value |
---|---|
Version | 8.6.3 |
Type | FeatureRequest |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |