Problems With Type Inference on (^) - haskell

So, I'm trying to write my own replacement for Prelude, and I have (^) implemented as such:
{-# LANGUAGE RebindableSyntax #-}
class Semigroup s where
infixl 7 *
(*) :: s -> s -> s
class (Semigroup m) => Monoid m where
one :: m
class (Ring a) => Numeric a where
fromIntegral :: (Integral i) => i -> a
fromFloating :: (Floating f) => f -> a
class (EuclideanDomain i, Numeric i, Enum i, Ord i) => Integral i where
toInteger :: i -> Integer
quot :: i -> i -> i
quot a b = let (q,r) = (quotRem a b) in q
rem :: i -> i -> i
rem a b = let (q,r) = (quotRem a b) in r
quotRem :: i -> i -> (i, i)
quotRem a b = let q = quot a b; r = rem a b in (q, r)
-- . . .
infixr 8 ^
(^) :: (Monoid m, Integral i) => m -> i -> m
(^) x i
| i == 0 = one
| True = let (d, m) = (divMod i 2)
rec = (x*x) ^ d in
if m == one then x*rec else rec
(Note that the Integral used here is one I defined, not the one in Prelude, although it is similar. Also, one is a polymorphic constant that's the identity under the monoidal operation.)
Numeric types are monoids, so I can try to do, say 2^3, but then the typechecker gives me:
*AlgebraicPrelude> 2^3
<interactive>:16:1: error:
* Could not deduce (Integral i0) arising from a use of `^'
from the context: Numeric m
bound by the inferred type of it :: Numeric m => m
at <interactive>:16:1-3
The type variable `i0' is ambiguous
These potential instances exist:
instance Integral Integer -- Defined at Numbers.hs:190:10
instance Integral Int -- Defined at Numbers.hs:207:10
* In the expression: 2 ^ 3
In an equation for `it': it = 2 ^ 3
<interactive>:16:3: error:
* Could not deduce (Numeric i0) arising from the literal `3'
from the context: Numeric m
bound by the inferred type of it :: Numeric m => m
at <interactive>:16:1-3
The type variable `i0' is ambiguous
These potential instances exist:
instance Numeric Integer -- Defined at Numbers.hs:294:10
instance Numeric Complex -- Defined at Numbers.hs:110:10
instance Numeric Rational -- Defined at Numbers.hs:306:10
...plus four others
(use -fprint-potential-instances to see them all)
* In the second argument of `(^)', namely `3'
In the expression: 2 ^ 3
In an equation for `it': it = 2 ^ 3
I get that this arises because Int and Integer are both Integral types, but then why is it that in normal Prelude I can do this just fine? :
Prelude> :t (2^)
(2^) :: (Num a, Integral b) => b -> a
Prelude> :t 3
3 :: Num p => p
Prelude> 2^3
8
Even though the signatures for partial application in mine look identical?
*AlgebraicPrelude> :t (2^)
(2^) :: (Numeric m, Integral i) => i -> m
*AlgebraicPrelude> :t 3
3 :: Numeric a => a
How would I make it so that 2^3 would in fact work, and thus give 8?

A Hindley-Milner type system doesn't really like having to default anything. In such a system, you want types to be either properly fixed (rigid, skolem) or properly polymorphic, but the concept of “this is, like, an integer... but if you prefer, I can also cast it to something else” as many other languages have doesn't really work out.
Consequently, Haskell sucks at defaulting. It doesn't have first-class support for that, only a pretty hacky ad-hoc, hard-coded mechanism which mainly deals with built-in number types, but fails at anything more involved.
You therefore should try to not rely on defaulting. My opinion is that the standard signature for ^ is unreasonable; a better signature would be
(^) :: Num a => a -> Int -> a
The Int is probably controversial – of course Integer would be safer in a sense; however, an exponent too big to fit in Int generally means the results will be totally off the scale anyway and couldn't feasibly be calculated by iterated multiplication; so this kind of expresses the intend pretty well. And it gives best performance for the extremely common situation where you just write x^2 or similar, which is something where you very definitely don't want to have to put an extra signature in the exponent.
In the rather fewer cases where you have a concrete e.g. Integer number and want to use it in the exponent, you can always shove in an explicit fromIntegral. That's not nice, but rather less of an inconvenience.
As a general rule, I try to avoid† any function-arguments that are more polymorphic than the results. Haskell's polymorphism works best “backwards”, i.e. the opposite way as in dynamic language: the caller requests what type the result should be, and the compiler figures out from this what the arguments should be. This works pretty much always, because as soon as the result is somehow used in the main program, the types in the whole computation have to be linked to a tree structure.
OTOH, inferring the type of the result is often problematic: arguments may be optional, may themselves be linked only to the result, or given as polymorphic constants like Haskell number literals. So, if i doesn't turn up in the result of ^, avoid letting in occur in the arguments either.
†“Avoid” doesn't mean I don't ever write them, I just don't do so unless there's a good reason.

Related

Why does ghc warn that ^2 requires "defaulting the constraint to type 'Integer'?

If I compile the following source file with ghc -Wall:
main = putStr . show $ squareOfSum 5
squareOfSum :: Integral a => a -> a
squareOfSum n = (^2) $ sum [1..n]
I get:
powerTypes.hs:4:18: warning: [-Wtype-defaults]
• Defaulting the following constraints to type ‘Integer’
(Integral b0) arising from a use of ‘^’ at powerTypes.hs:4:18-19
(Num b0) arising from the literal ‘2’ at powerTypes.hs:4:19
• In the expression: (^ 2)
In the expression: (^ 2) $ sum [1 .. n]
In an equation for ‘squareOfSum’:
squareOfSum n = (^ 2) $ sum [1 .. n]
|
4 | squareOfSum n = (^2) $ sum [1..n]
| ^^
I understand that the type of (^) is:
Prelude> :t (^)
(^) :: (Integral b, Num a) => a -> b -> a
which means it works for any a^b provided a is a Num and b is an Integral. I also understand the type hierarchy to be:
Num --> Integral --> Int or Integer
where --> denotes "includes" and the first two are typeclasses while the last two are types.
Why does ghc not conclusively infer that 2 is an Int, instead of "defaulting the constraints to Integer". Why is ghc defaulting anything? Is replacing 2 with 2 :: Int a good way to resolve this warning?
In Haskell, numeric literals have a polymorphic type
2 :: Num a => a
This means that the expression 2 can be used to generate a value in any numeric type. For instance, all these expression type-check:
2 :: Int
2 :: Integer
2 :: Float
2 :: Double
2 :: MyCustomTypeForWhichIDefinedANumInstance
Technically, each time we use 2 we would have to write 2 :: T to choose the actual numeric type T we want. Fortunately, this is often not needed since type inference can frequently deduce T from the context. E.g.,
foo :: Int -> Int
foo x = x + 2
Here, x is an Int because of the type annotation, and + requires both operands to have the same type, hence Haskell infers 2 :: Int. Technically, this is because (+) has type
(+) :: Num a => a -> a -> a
Sometimes, however, type inference can not deduce T from the context. Consider this example involving a custom type class:
class C a where bar :: a -> String
instance C Int where bar x = "Int: " ++ show x
instance C Integer where bar x = "Integer: " ++ show x
test :: String
test = bar 2
What is the value of test? Well, if 2 is an Int, then we have test = "Int: 2". If it is an Integer, then we have test = "Integer: 2". If it's another numeric type T, we can not find an instance for C T.
This code is inherently ambiguous. In such a case, Haskell mandates that numeric types that can not be deduced are defaulted to Integer (the programmer can change this default to another type, but it's not relevant now). Hence we have test = "Integer: 2".
While this mechanism makes our code type check, it might cause an unintended result: for all we know, the programmer might have wanted 2 :: Int instead. Because of this, GHC chooses the default, but warns about it.
In your code, (^) can work with any Integral type for the exponent. But, in principle, x ^ (2::Int) and x ^ (2::Integer) could lead to different results. We know this is not the case since we know the semantics of (^), but for the compiler (^) is only a random function with that type, which could behave differently on Int and Integer. Consider, e.g.,
a ^ n = if n + 3000000000 < 0 then 0 else 1
When n = 2, if we use n :: Int the if guard could be true on a 32 bit system. This is not the case when using n :: Integer which never overflows.
The standard solution, in these cases, is to resolve the warning using something like x ^ (2 :: Int).

Why is `succ i` valid where `i :: Num a => a` (and not an `Enum a`)?

This seems to apply to both GHCi and GHC. I'll show an example with GHCi first.
Given i type has been inferred as follows:
Prelude> i = 1
Prelude> :t i
i :: Num p => p
Given that succ is a function defined on Enum:
Prelude> :i Enum
class Enum a where
succ :: a -> a
pred :: a -> a
-- …OMITTED…
and that Num is not a 'subclass' (if I can use that term) of Enum:
class Num a where
(+) :: a -> a -> a
(-) :: a -> a -> a
-- …OMITTED…
why succ i does not return an error?
Prelude> succ i
2 -- works, no error
I would expect :type i to be inferred to something like:
Prelude> i = 1
Prelude> :type i
i :: (Enum p, Num p) => p
(I'm using 'GHC v. 8.6.3')
ADDITION:
After reading #RobinZigmond comment and #AlexeyRomanov answer I have noticed that 1 could be interpreted as one of many types and one of many classes.
Thanks to #AlexeyRomanov answer I understand much more about the defaulting-rules used to decide what type to use for ambiguous expressions.
However I don't feel that Alexey answer addresses exactly my question. My question is about the type of i. It's not about the type of succ i.
It's about the mismatch between succ argument type (an Enum a) and the apparent type of i (a Num a).
I'm now starting to realise that my question must stem from a wrong assumption: 'that once i is inferred to be i :: Num a => a, then i can be nothing else'. Hence I was puzzled to see succ i was evaluated without errors.
GHC also seems to be inferring Enum a in addition to what was explicitly declared.
x :: Num a => a
x = 1
y = succ x -- works
However it is not adding Enum a when the type variable appears as a function:
my_succ :: Num a => a -> a
my_succ z = succ z -- fails compilation
To me it seems that the type constraints attached to a function are stricter to the ones applied to a variable.
GHC is saying my_succ :: forall a. Num a => a -> a and given
forall a doesn't appear in the type-signature of neither i nor x I thought that meant GHC is not going to infer any more classes for my_succ types.
But this seems again wrong: I've checked this idea with the following (first time I type RankNTypes) and apparently GHC still infers Enum a:
{-# LANGUAGE RankNTypes #-}
x :: forall a. Num a => a
x = 1
y = succ x
So it seems that inference rules for functions are stricter than the ones for variables?
Yes, succ i's type is inferred as you expect:
Prelude> :t succ i
succ i :: (Enum a, Num a) => a
This type is ambiguous, but it satisfies the conditions in the defaulting rules for GHCi:
Find all the unsolved constraints. Then:
Find those that are of form (C a) where a is a type variable, and partition those constraints into groups that share a common type variable a.
In this case, there's only one group: (Enum a, Num a).
Keep only the groups in which at least one of the classes is an interactive class (defined below).
This group is kept, because Num is an interactive class.
Now, for each remaining group G, try each type ty from the default-type list in turn; if setting a = ty would allow the constraints in G to be completely solved. If so, default a to ty.
The unit type () and the list type [] are added to the start of the standard list of types which are tried when doing type defaulting.
The default default-type list (sic) is (with the additions from the last clause) default ((), [], Integer, Double).
So when you do Prelude> succ i to actually evaluate this expression (note :t doesn't evaluate the expression it gets), a is set to Integer (first of this list satisfying the constraints), and the result is printed as 2.
You can see it's the reason by changing the default:
Prelude> default (Double)
Prelude> succ 1
2.0
For the updated question:
I'm now starting to realise that my question must stem from a wrong assumption: 'that once i is inferred to be i :: Num a => a, then i can be nothing else'. Hence I was puzzled to see succ i was evaluated without errors.
i can be nothing else (i.e. nothing that doesn't fit this type), but it can be used with less general (more specific) types: Integer, Int. Even with many of them in an expression at once:
Prelude> (i :: Double) ^ (i :: Integer)
1.0
And these uses don't affect the type of i itself: it's already defined and its type fixed. OK so far?
Well, adding constraints also makes the type more specific, so (Num a, Enum a) => a is more specific than (Num a) => a:
Prelude> i :: (Num a, Enum a) => a
1
Because of course any type a that satisfies both constraints in (Num a, Enum a) satisfies just Num a.
However it is not adding Enum a when the type variable appears as a function:
That's because you specified a signature which doesn't allow it to. If you don't give a signature, there's no reason to infer Num constraint. But e.g.
Prelude> f x = succ x + 1
will infer the type with both constraints:
Prelude> :t f
f :: (Num a, Enum a) => a -> a
So it seems that inference rules for functions are stricter than the ones for variables?
It's actually the other way around due to the monomorphism restriction (not in GHCi, by default). You've actually been a bit lucky not to run into it here, but the answer is already long enough. Searching for the term should give you explanations.
GHC is saying my_succ :: forall a. Num a => a -> a and given forall a doesn't appear in the type-signature of neither i nor x.
That's a red herring. I am not sure why it's shown in one case and not the other, but all of them have that forall a behind the scenes:
Haskell type signatures are implicitly quantified. When the language option ExplicitForAll is used, the keyword forall allows us to say exactly what this means. For example:
g :: b -> b
means this:
g :: forall b. (b -> b)
(Also, you just need ExplicitForAll and not RankNTypes to write down forall a. Num a => a.)

Haskell, multiple type classes for one argument

This is an example in Learn You A Haskell, chapter on higher order functions:
compareWithHundred :: (Num a, Ord a) => a -> Ordering
compareWithHundred x = compare 100 x
While the idea of the function is clear for me, I'm not sure why type signature is (Num a, Ord a). We only pass integer that is to be compared to the function, of type Int. What Ord stands for here, and why is implicitly passed argument in type signature?
That's not the only possible signature for this signature. It happens to be the most general one. compareWithHundred :: Int -> Ordering is actually a possible instantiation – the polymorphic a argument can be instatiated with any orderable number type, which does sure enough include Int, but also Integer, Rational, Double...
Prelude> let compareWithHundred :: (Num a, Ord a) => a -> Ordering; compareWithHundred x = compare 100 x
Prelude> compareWithHundred (99 :: Int)
GT
Prelude> compareWithHundred (100.3 :: Double)
LT
Not all number types permit you to order-compare them though – the classical example where this is not possible are complex numbers (which have “more than one direction” in which you could order them).
Prelude Data.Complex> compareWithHundred (100 :+ 30 :: Complex Double)
<interactive>:10:1:
No instance for (Ord (Complex Double))
arising from a use of ‘compareWithHundred’
In the expression: compareWithHundred (100 :+ 30 :: Complex Double)
In an equation for ‘it’:
it = compareWithHundred (100 :+ 30 :: Complex Double)
Hence you need to require both that the argument is a number (so there exists a value 100 which to compare with) and that the argument is in the Ord class. This combined constrained is written (Num a, Ord a).
I have something to add, in case you couldn't gather something from leftaroundabout's thorough answer.
Everything to the left of => in a type signature is a constraint. Read the type like this:
compareWithHundred :: (Num a, Ord a) => a -> Ordering
^^^^^^^^^^^^^^ ^ ^^^^^^^^
constraints | |
argument type |
result type
So you only pass one argument to the function because there is only one argument in the type signature, a. a is a type variable, and can be replaced with any type as long as that type satisfies the constraints.
The Num a says that whatever you replace a with has to be numeric (so it can be Int, Integer, Double, ...), and the Ord a says that it has to be comparable. leftroundabout's answer goes into more detail about why you need both, I just wanted to make sure you knew how to read the signature.
So it's perfectly legal in one sense to say compareWithHundred "foobar", the type checker says that that expression's type is Ordering, but then it will fail later when it tries to check that there is a Num String instance.
I hope this helps.

How can a instance with Num type class coercion to Fractional implicitly?

I tested the numeric coercion by using GHCI:
>> let c = 1 :: Integer
>> 1 / 2
0.5
>> c / 2
<interactive>:15:1: error:
• No instance for (Fractional Integer) arising from a use of ‘/’
• In the expression: c / 2
In an equation for ‘it’: it = c / 2
>> :t (/)
(/) :: Fractional a => a -> a -> a -- (/) needs Fractional type
>> (fromInteger c) / 2
0.5
>>:t fromInteger
fromInteger :: Num a => Integer -> a -- Just convert the Integer to Num not to Fractional
I can use fromInteger function to convert a Integer type to Num (fromInteger has the type fromInteger :: Num a => Integer -> a), but I cannot understand that how can the type Num be converted to Fractional implicitly?
I know that if an instance has type Fractional it must have type Num (class Num a => Fractional a where), but does it necessary that if an instance has type Num it can be used as an instance with Fractional type?
#mnoronha Thanks for your detailed reply. There is only one question confuse me. I know the reason that type a cannot be used in function (/) is that type a is with type Integer which is not an instance of type class Fractional (the function (/) requires that the type of arguments must be instance of Fractional). What I don't understand is that even by calling fromInteger to convert the type integer to atype which be an instance of Num, it does not mean a type be an instance of Fractional (because Fractional type class is more constrained than Num type class, so a type may not implement some functions required by Fractional type class). If a type does not fully fit the condition Fractional type class requires, how can it be use in the function (/) which asks the arguments type be instance of Fractional. Sorry for not native speaker and really thanks for your patience!
I tested that if a type only fits the parent type class, it cannot be used in a function which requires more constrained type class.
{-# LANGUAGE OverloadedStrings #-}
module Main where
class ParentAPI a where
printPar :: int -> a -> String
class (ParentAPI a) => SubAPI a where
printSub :: a -> String
data ParentDT = ParentDT Int
instance ParentAPI ParentDT where
printPar i p = "par"
testF :: (SubAPI a) => a -> String
testF a = printSub a
main = do
let m = testF $ ParentDT 10000
return ()
====
test-typeclass.hs:19:11: error:
• No instance for (SubAPI ParentDT) arising from a use of ‘testF’
• In the expression: testF $ ParentDT 10000
In an equation for ‘m’: m = testF $ ParentDT 10000
In the expression:
do { let m = testF $ ParentDT 10000;
return () }
I have found a doc explaining the numeric overloading ambiguity very clearly and may help others with the same confusion.
https://www.haskell.org/tutorial/numbers.html
First, note that both Fractional and Num are not types, but type classes. You can read more about them in the documentation or elsewhere, but the basic idea is that they define behaviors for types. Num is the most inclusive numeric typeclass, defining behaviors functions like (+), negate, which are common to pretty much all "numeric types." Fractional is a more constrained type class that describes "fractional numbers, supporting real division."
If we look at the type class definition for Fractional, we see that it is actually defined as a subclass of Num. That is, for a type a to be an have an instance Fractional, it must first be a member of the typeclass Num:
class Num a => Fractional a where
Let's consider some type that is constrained by Fractional. We know it implements the basic behaviors common to all members of Num. However, we can't expect it to implement behaviors from other type classes unless multiple constraints are specified (ex. (Num a, Ord a) => a. Take, for example, the function div :: Integral a => a -> a -> a (integral division). If we try to apply the function with an argument that is constrained by the typeclass Fractional (ex. 1.2 :: Fractional t => t), we encounter an error. Type classes restrict the sort of values a function deals with, allowing us to write more specific and useful functions for types that share behaviors.
Now let's look at the more general typeclass, Num. If we have a type variable a that is only constrained by Num a => a, we know that it will implement the (few) basic behaviors included in the Num type class definition, but we'd need more context to know more. What does this mean practically? We know from our Fractional class declaration that functions defined in the Fractional type class are applied to Num types. However, these Num types are a subset of all possible Num types.
The importance of all this, ultimately, has to do with the ground types (where type class constraints are most commonly seen in functions). a represents a type, with the notation Num a => a telling us that a is a type that includes an instance of the type class Num. a could be any of the types that include the instance (ex. Int, Natural). Thus, if we give a value a general type Num a => a, we know it can implement functions for every type where there is a type class defined. For example:
ghci>> let a = 3 :: (Num a => a)
ghci>> a / 2
1.5
Whereas if we'd defined a as a specific type or in terms of a more constrained type class, we would have not been able to expect the same results:
ghci>> let a = 3 :: Integral a => a
ghci>> a / 2
-- Error: ambiguous type variable
or
ghci>> let a = 3 :: Integer
ghci>> a / 2
-- Error: No instance for (Fractional Integer) arising from a use of ‘/’
(Edit responding to followup question)
This is definitely not the most concrete explanation, so readers feel free to suggest something more rigorous.
Suppose we have a function a that is just a type class constrained version of the id function:
a :: Num a => a -> a
a = id
Let's look at type signatures for some applications of the function:
ghci>> :t (a 3)
(a 3) :: Num a => a
ghci>> :t (a 3.2)
(a 3.2) :: Fractional a => a
While our function had the general type signature, as a result of its application the the type of the application is more restricted.
Now, let's look at the function fromIntegral :: (Num b, Integral a) => a -> b. Here, the return type is the general Num b, and this will be true regardless of input. I think the best way to think of this difference is in terms of precision. fromIntegral takes a more constrained type and makes it less constrained, so we know we'll always expect the result will be constrained by the type class from the signature. However, if we give an input constraint, the actual input could be more restricted than the constraint and the resulting type would reflect that.
The reason why this works comes down to the way universal quantification works. To help explain this I am going to add in explicit forall to the type signatures (which you can do yourself if you enable -XExplicitForAll or any other forall related extension), but if you just removed them (forall a. ... becomes just ...), everything will work fine.
The thing to remember is that when a function involves a type constrained by a typeclass, then what that means is that you can input/output ANY type within that typeclass, so it's actually better to have a less constrained typeclass.
So:
fromInteger :: forall a. Num a => Integer -> a
fromInteger 5 :: forall a. Num a => a
Means that you have a value that is of EVERY Num type. So not only can you use it in a function taking it in a Fractional, you could use it in a function that only takes in MyWeirdTypeclass a => ... as long as there is one single type that implements both Num and MyWeirdTypeclass. Hence why you can get the following just fine:
fromInteger 5 / 2 :: forall a. Fractional a => a
Now of course once you decide to divide by 2, it now wants the output type to be Fractional, and thus 5 and 2 will be interpreted as some Fractional type, so we won't run into issues where we try to divide Int values, as trying to make the above have type Int will fail to type check.
This is really powerful and awesome, but very much unfamiliar, as generally other languages either don't support this, or only support it for input arguments (e.g print in most languages can take in any printable type).
Now you may be curious when the whole superclass / subclass stuff comes into play, so when you are defining a function that takes in something of type Num a => a, then because a user can pass in ANY Num type, you are correct that in this situation you cannot use functions defined on some subclass of Num, only things that work on ALL Num values, like *:
double :: forall a. Num a => a -> a
double n = n * 2 -- in here `n` really has type `exists a. Num a => a`
So the following does not type check, and it wouldn't type check in any language, because you don't know that the argument is a Fractional.
halve :: Num a => a -> a
halve n = n / 2 -- in here `n` really has type `exists a. Num a => a`
What we have up above with fromInteger 5 / 2 is more equivalent to the following, higher rank function, note that the forall within parenthesis is required, and you need to use -XRankNTypes:
halve :: forall b. Fractional b => (forall a. Num a => a) -> b
halve n = n / 2 -- in here `n` has type `forall a. Num a => a`
Since this time you are taking in EVERY Num type (just like the fromInteger 5 you were dealing with before), not just ANY Num type. Now the downside of this function (and one reason why no one wants it) is that you really do have to pass in something of EVERY Num type:
halve (2 :: Int) -- does not work
halve (3 :: Integer) -- does not work
halve (1 :: Double) -- does not work
halve (4 :: Num a => a) -- works!
halve (fromInteger 5) -- also works!
I hope that clears things up a little. All you need for the fromInteger 5 / 2 to work is that there exists ONE single type that is both a Num and a Fractional, or in other words just a Fractional, since Fractional implies Num. Type defaulting doesn't help much with clearing up this confusion, as what you may not realize is that GHC is just arbitrarily picking Double, it could have picked any Fractional.

The case of the disappearing constraint: Oddities of a higher-rank type

All the experiments described below were done with GHC 8.0.1.
This question is a follow-up to RankNTypes with type aliases confusion. The issue there boiled down to the types of functions like this one...
{-# LANGUAGE RankNTypes #-}
sleight1 :: a -> (Num a => [a]) -> a
sleight1 x (y:_) = x + y
... which are rejected by the type checker...
ThinAir.hs:4:13: error:
* No instance for (Num a) arising from a pattern
Possible fix:
add (Num a) to the context of
the type signature for:
sleight1 :: a -> (Num a => [a]) -> a
* In the pattern: y : _
In an equation for `sleight1': sleight1 x (y : _) = x + y
... because the higher-rank constraint Num a cannot be moved outside of the type of the second argument (as would be possible if we had a -> a -> (Num a => [a]) instead). That being so, we end up trying to add a higher-rank constraint to a variable already quantified over the whole thing, that is:
sleight1 :: forall a. a -> (Num a => [a]) -> a
With this recapitulation done, we might try to simplify the example a bit. Let's replace (+) with something that doesn't require Num, and uncouple the type of the problematic argument from that of the result:
sleight2 :: a -> (Num b => b) -> a
sleight2 x y = const x y
This doesn't work just like before (save for a slight change in the error message):
ThinAir.hs:7:24: error:
* No instance for (Num b) arising from a use of `y'
Possible fix:
add (Num b) to the context of
the type signature for:
sleight2 :: a -> (Num b => b) -> a
* In the second argument of `const', namely `y'
In the expression: const x y
In an equation for `sleight2': sleight2 x y = const x y
Failed, modules loaded: none.
Using const here, however, is perhaps unnecessary, so we might try writing the implementation ourselves:
sleight3 :: a -> (Num b => b) -> a
sleight3 x y = x
Surprisingly, this actually works!
Prelude> :r
[1 of 1] Compiling Main ( ThinAir.hs, interpreted )
Ok, modules loaded: Main.
*Main> :t sleight3
sleight3 :: a -> (Num b => b) -> a
*Main> sleight3 1 2
1
Even more bizarrely, there seems to be no actual Num constraint on the second argument:
*Main> sleight3 1 "wat"
1
I'm not quite sure about how to make that intelligible. Perhaps we might say that, just like we can juggle undefined as long as we never evaluate it, an unsatisfiable constraint can stick around in a type just fine as long as it is not used for unification anywhere in the right-hand side. That, however, feels like a pretty weak analogy, specially given that non-strictness as we usually understand it is a notion involving values, and not types. Furthermore, that leaves us no closer from grasping how in the world String unifies with Num b => b -- assuming that such a thing actually happens, something which I'm not at all sure of. What, then, is an accurate description of what is going on when a constraint seemingly vanishes in this manner?
Oh, it gets even weirder:
Prelude> sleight3 1 ("wat"+"man")
1
Prelude Data.Void> sleight3 1 (37 :: Void)
1
See, there is an actual Num constraint on that argument. Only, because (as chi already commented) the b is in a covariant position, this is not a constraint you have to provide when calling sleight3. Rather, you can just pick any type b, then whatever it is, sleight3 will provide a Num instance for it!
Well, clearly that's bogus. sleight3 can't provide such a num instance for strings, and most definitely not for Void. But it also doesn't actually need to because, quite like you said, the argument for which that constraint would apply is never evaluated. Recall that a constrained-polymorphic value is essentially just a function of a dictionary argument. sleight3 simply promises to provide such a dictionary before it actually gets to use y, but then it doesn't use y in any way, so it's fine.
It's basically the same as with a function like this:
defiant :: (Void -> Int) -> String
defiant f = "Haha"
Again, the argument function clearly can not possibly yield an Int because there doesn't exist a Void value to evaluate it with. But this isn't needed either, because f is simply ignored!
By contrast, sleight2 x y = const x y does kinda sorta use y: the second argument to const is just a rank-0 type, so the compiler needs to resolve any needed dictionaries at that point. Even if const ultimately also throws y away, it still “forces” enough of this value to make it evident that it's not well-typed.

Resources