[Haskell-beginners] Explanation of double astrix
Tillmann Rendel
rendel at daimi.au.dk
Wed Sep 3 11:34:46 EDT 2008
Paul Johnston wrote:
> Was playing around with ghci and lambda expressions and:
>
> *Main> map (\x -> 2 * x) [1 ..3]
> [2,4,6]
>
> Then thinking back to Fortran (yes I'm not young anymore!)
>
> *Main> map (\x -> 2 ** x) [1 ..3]
> [2.0,4.0,8.0]
>
> Curious as to what is going on.
> *Main> :t (\x -> 2 ** x)
> (\x -> 2 ** x) :: (Floating t) => t -> t
> *Main> :t (\x -> 2 * x)
> (\x -> 2 * x) :: (Num t) => t -> t
>
>
> Somehow the type has gone from Num to Floating
> I am using the excellent (IMHO) tutorial by Hal Daume and the book by Graham
> Hutton but can find no clues.
Literal numbers are polymorphic in Haskell. Their type is
Prelude> :t 42
42 :: (Num t) => t
That means that for every type t which is an instance of type class Num,
42 has type t. ghci can inform us on the methods a type class provides,
and the instances currently in scope with the :info command.
Prelude> :info Num
class (Eq a, Show a) => Num a where
(+) :: a -> a -> a
(*) :: a -> a -> a
(-) :: a -> a -> a
negate :: a -> a
abs :: a -> a
signum :: a -> a
fromInteger :: Integer -> a
-- Defined in GHC.Num
instance Num Double -- Defined in GHC.Float
instance Num Float -- Defined in GHC.Float
instance Num Int -- Defined in GHC.Num
instance Num Integer -- Defined in GHC.Num
So 42 can be a floating point (Float or Double) or an integral number
(Int or Integer) depending on the typing context. There are many more
instances in the libraries. You can force a type using an explicit type
annotation.
Prelude> 42 :: Int
42
Prelude> 42 :: Float
42.0
The function (*) works on every Num instance, so 2 * 3 still can be any
Num instance.
Prelude> :t 2 * 3
2 * 3 :: (Num t) => t
But what happens if there is no typing context but you want to perform
an operation which depends on the actual type, like printing the value?
Most of the times, you will get an error message asking you to provide
an explicit type annotation, but for numeric types, there are special
defaulting rules which will choose a default instance. That is why ghci
can output something when confronted with 42, instead of asking which
type it should use.
Prelude> 42
42
Note that ghci seems to have choosen Int or Integer, not Float or
Double, since it outputs 42 and not 42.0. That also explains the
behavior of your test case with the (*) function.
Now to the (**) function.
Prelude> :t (**)
(**) :: (Floating a) => a -> a -> a
Compare this with the type of (*). (**) is only defined for floating
point numbers, not for integral numbers. We can look up what Floating
means with :info.
Prelude> :info Floating
class (Fractional a) => Floating a where
pi :: a
exp :: a -> a
sqrt :: a -> a
log :: a -> a
(**) :: a -> a -> a
logBase :: a -> a -> a
sin :: a -> a
tan :: a -> a
cos :: a -> a
asin :: a -> a
atan :: a -> a
acos :: a -> a
sinh :: a -> a
tanh :: a -> a
cosh :: a -> a
asinh :: a -> a
atanh :: a -> a
acosh :: a -> a
-- Defined in GHC.Float
instance Floating Double -- Defined in GHC.Float
instance Floating Float -- Defined in GHC.Float
If you use (**), you force your numbers to be of a type which is a
Floating instance, like Float or Double. And since Integer and Int are
not floating instances, they can no longer be choosen by the defaulting
mechanism. Instead, one of Double or Float is choosen, which prints a
trailing ".0". That explains the behavior of your test with (**).
If you want to compute the power of an integral number, you can use (^).
Prelude> :t (^)
(^) :: (Integral b, Num a) => a -> b -> a
While (**) works for floating point numbers, (^) works for any numeric
base type, and an integral exponent. You can use :info again to find out
which numeric types are integral.
Why do we need two exponentiation operators in Haskell with different types?
Using hoogle, the Haskell api search machine, you can access code and
documentation of (^) and (**) and see that (^) is implemented by calling
(*) repeatedly (in some clever way to avoid too much work), while (**)
is by default implemented as x ** y = exp (log x * y).
http://haskell.org/hoogle
Obviously, calling (*) multiple times works only for integral exponents
(since you cannot multiply a half times), and exp and log exists only
for floating point numbers, so these are two entirely different
implementations suitable for different situations.
Tillmann
More information about the Beginners
mailing list