Type inference fails in connection with TypeFamilies, 'let', type equalities ...
The following example is a pretty involved use of type equality. It was accepted by GHC-8.0 and before, but GHC-8.2.0.20170505 cannot infer a type.
$ cat MonomorphismEquality.hs
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module MonomorphismEquality (run) where
newtype Value a = Value a
type family Repr (f :: * -> *) a :: *
type instance Repr f Int = f Int
class (Repr Value i ~ Value ir) => Native i ir where
instance Native Int Int where
fromInt :: (Native i ir) => i -> a
fromInt = undefined
apply :: (Int -> a -> a) -> a -> a
apply weight = id
run :: Float -> Float
run =
let weight = \clip v -> fromInt clip * v
in apply weight
$ ghc-8.0.2 -Wall MonomorphismEquality.hs
[1 of 1] Compiling MonomorphismEquality ( MonomorphismEquality.hs, MonomorphismEquality.o )
MonomorphismEquality.hs:6:19: warning: [-Wunused-top-binds]
Defined but not used: data constructor ‘Value’
MonomorphismEquality.hs:20:7: warning: [-Wunused-matches]
Defined but not used: ‘weight’
$ ghc-8.2.0.20170505 -Wall MonomorphismEquality.hs
[1 of 1] Compiling MonomorphismEquality ( MonomorphismEquality.hs, MonomorphismEquality.o )
MonomorphismEquality.hs:24:28: error:
• Ambiguous type variable ‘ir0’ arising from a use of ‘fromInt’
prevents the constraint ‘(Native Int ir0)’ from being solved.
Probable fix: use a type annotation to specify what ‘ir0’ should be.
These potential instance exist:
instance Native Int Int -- Defined at MonomorphismEquality.hs:13:10
• In the first argument of ‘(*)’, namely ‘fromInt clip’
In the expression: fromInt clip * v
In the expression: \ clip v -> fromInt clip * v
|
24 | let weight = \clip v -> fromInt clip * v
| ^^^^^^^^^^^^
Trac metadata
Trac field | Value |
---|---|
Version | 8.2.1-rc1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler (Type checker) |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |