2
votes

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

2

2 Answers

4
votes

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.

0
votes

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.