Difference between revisions of "Generic number type"

From HaskellWiki
Jump to navigation Jump to search
m
(→‎See also: link to "converting numbers")
 
(7 intermediate revisions by 2 users not shown)
Line 15: Line 15:
 
However you will find that it is difficult to implement these methods in a way that is appropriate for each use case.
 
However you will find that it is difficult to implement these methods in a way that is appropriate for each use case.
 
There is simply no type that can emulate the others.
 
There is simply no type that can emulate the others.
Floating point numbers are imprecise - a/b*b=a does not hold in general.
+
Floating point numbers are imprecise - <hask>a/b*b==a</hask> does not hold in general.
Rationals are precise but pi and sqrt 2 are not rational.
+
Rationals are precise but <hask>pi</hask> and <hask>sqrt 2</hask> are not rational.
 
That is, when using <hask>GenericNumber</hask>s you will encounter exactly the problems
 
That is, when using <hask>GenericNumber</hask>s you will encounter exactly the problems
 
that all scripting language users have encountered so far (or ignored :-).
 
that all scripting language users have encountered so far (or ignored :-).
   
  +
A <hask>GenericNumber</hask> type would also negate the type safety that strongly typed numbers provide, putting the burden back on the programmer to make sure they are using numbers in a type-safe way. This can lead to subtle and hard-to-find bugs, for example, if some code ends up comparing two floating-point values for equality (usually a bad idea) without the programmer realizing it.
   
== Solutions ==
+
== Idiomatic solutions ==
   
It is strongly advised to carefully check whether a GenericNumber is indeed useful for your application.
+
It is strongly advised to carefully check whether a <hask>GenericNumber</hask> is indeed useful for your application.
 
So let's revisit some examples and their idiomatic solutions in plain Haskell 98.
 
So let's revisit some examples and their idiomatic solutions in plain Haskell 98.
   
 
=== average ===
 
=== average ===
   
You may find it cumbersome to write
+
You may find it cumbersome to manually [[Converting numbers|convert]] integers to fractional number types like in
 
<haskell>
 
<haskell>
 
average :: Fractional a => [a] -> a
 
average :: Fractional a => [a] -> a
Line 42: Line 43:
 
<haskell>
 
<haskell>
 
average :: Fractional a => [a] -> a
 
average :: Fractional a => [a] -> a
average xs = sum xs / genericlength xs
+
average xs = sum xs / genericLength xs
 
</haskell>
 
</haskell>
   
Line 62: Line 63:
 
1 % 3 :: Rational
 
1 % 3 :: Rational
 
1 % floor pi :: Rational
 
1 % floor pi :: Rational
  +
</haskell>
  +
  +
=== isSquare ===
  +
  +
It may seem irksome that <hask>fromIntegral</hask> is required in the function
  +
<haskell>
  +
isSquare :: (Integral a) => a -> Bool
  +
isSquare n = (round . sqrt $ fromIntegral n) ^ 2 == n
  +
</haskell>
  +
With a <hask>GenericNumber</hask> type, one could instead write
  +
<haskell>
  +
isSquare :: GenericNumber -> Bool
  +
isSquare n = (round . sqrt $ n) ^ 2 == n
  +
</haskell>
  +
but there is a subtle problem here: if the input happens to be represented internally by a non-integral type, this function will probably not work properly. This could be fixed by wrapping all occurrences of <hask>n</hask> by calls to <hask>round</hask>, but that's no easier (and less type-safe) than just including the call to <hask>fromIntegral</hask> in the first place. The point is that by using <hask>GenericNumber</hask> here, all opportunities for the type checker to warn you of problems is lost; now you, the programmer, must ensure that the underlying numeric types are always used correctly, which is made even harder by the fact that you can't inspect them.
  +
  +
=== squareRoot ===
  +
  +
Closely related is the (floor of the) square root of integers.
  +
It is tempting to implement
  +
<haskell>
  +
squareRoot :: Integer -> Integer
  +
squareRoot = floor . sqrt . (fromIntegral :: Integer -> Double)
  +
</haskell>
  +
or to convert to <hask>Double</hask> automatically in an implementation of <hask>sqrt</hask> for <hask>GenericNumber</hask>.
  +
This will not work for several reasons:
  +
* For a square number, <hask>sqrt</hask> may give a result slightly below an integer, which <hask>floor</hask> will round down to the next integer.
  +
* <hask>fromIntegral</hask> will not preserve the (arbitrary high) precision of <hask>Integer</hask>s and thus will not give precise results.
  +
* <hask>fromIntegral</hask> may exceed the maximum exponent of the floating point representation and fail with an overflow error or <hask>Infinity</hask> result.
  +
  +
That is, <hask>fromIntegral</hask> is of no help here.
  +
The most efficient way is to call the native implementation of the square root of GNU's multiprecision library.
  +
(How to do that?)
  +
The most portable way is to implement a square root algorithm from scratch.
  +
<haskell>
  +
(^!) :: Num a => a -> Int -> a
  +
(^!) x n = x^n
  +
  +
squareRoot :: Integer -> Integer
  +
squareRoot 0 = 0
  +
squareRoot 1 = 1
  +
squareRoot n =
  +
let twopows = iterate (^!2) 2
  +
(lowerRoot, lowerN) =
  +
last $ takeWhile ((n>=) . snd) $ zip (1:twopows) twopows
  +
newtonStep x = div (x + div n x) 2
  +
iters = iterate newtonStep (squareRoot (div n lowerN) * lowerRoot)
  +
isRoot r = r^!2 <= n && n < (r+1)^!2
  +
in head $ dropWhile (not . isRoot) iters
 
</haskell>
 
</haskell>
   
Line 67: Line 117:
 
== See also ==
 
== See also ==
   
  +
* [[Converting numbers]]
* Suggestions for implementing a generic number type: http://www.haskell.org/pipermail/haskell-cafe/2007-June/027092.html
+
* The discussion on haskell-cafe which provided the impetus for this page: http://www.haskell.org/pipermail/haskell-cafe/2007-June/027092.html
   
 
[[Category:FAQ]]
 
[[Category:FAQ]]

Latest revision as of 12:16, 29 December 2010

Problem

Question: Can I have a generic numeric data type in Haskell which covers Integer, Rational, Double and so on, like it is done in scripting languages like Perl and MatLab?

Answer: In principle you can define a type like

data GenericNumber =
    Integer Integer
  | Rational Rational
  | Double Double

and define appropriate instances for Num class et. al. However you will find that it is difficult to implement these methods in a way that is appropriate for each use case. There is simply no type that can emulate the others. Floating point numbers are imprecise - a/b*b==a does not hold in general. Rationals are precise but pi and sqrt 2 are not rational. That is, when using GenericNumbers you will encounter exactly the problems that all scripting language users have encountered so far (or ignored :-).

A GenericNumber type would also negate the type safety that strongly typed numbers provide, putting the burden back on the programmer to make sure they are using numbers in a type-safe way. This can lead to subtle and hard-to-find bugs, for example, if some code ends up comparing two floating-point values for equality (usually a bad idea) without the programmer realizing it.

Idiomatic solutions

It is strongly advised to carefully check whether a GenericNumber is indeed useful for your application. So let's revisit some examples and their idiomatic solutions in plain Haskell 98.

average

You may find it cumbersome to manually convert integers to fractional number types like in

average :: Fractional a => [a] -> a
average xs = sum xs / fromIntegral (length xs)

and you may prefer

average :: [GenericNumber] -> GenericNumber
average xs = sum xs / genericNumberLength xs

with an appropriate implementation of genericNumberLength. However, there is already Data.List.genericLength and you can write

average :: Fractional a => [a] -> a
average xs = sum xs / genericLength xs

ratios

You find it easy to write

1 / 3 :: Rational

but uncomfortable that

1 / floor pi :: Rational

does not work. The first example works, because the numeric literals 1 and 3 are interpreted as rationals itself. The second example fails, because floor always returns an Integral number type, where Rational is not an instance. You should use % instead. This constructs a fraction out of two integers:

1 % 3 :: Rational
1 % floor pi :: Rational

isSquare

It may seem irksome that fromIntegral is required in the function

isSquare :: (Integral a) => a -> Bool
isSquare n = (round . sqrt $ fromIntegral n) ^ 2 == n

With a GenericNumber type, one could instead write

isSquare :: GenericNumber -> Bool
isSquare n = (round . sqrt $ n) ^ 2 == n

but there is a subtle problem here: if the input happens to be represented internally by a non-integral type, this function will probably not work properly. This could be fixed by wrapping all occurrences of n by calls to round, but that's no easier (and less type-safe) than just including the call to fromIntegral in the first place. The point is that by using GenericNumber here, all opportunities for the type checker to warn you of problems is lost; now you, the programmer, must ensure that the underlying numeric types are always used correctly, which is made even harder by the fact that you can't inspect them.

squareRoot

Closely related is the (floor of the) square root of integers. It is tempting to implement

squareRoot :: Integer -> Integer
squareRoot = floor . sqrt . (fromIntegral :: Integer -> Double)

or to convert to Double automatically in an implementation of sqrt for GenericNumber. This will not work for several reasons:

  • For a square number, sqrt may give a result slightly below an integer, which floor will round down to the next integer.
  • fromIntegral will not preserve the (arbitrary high) precision of Integers and thus will not give precise results.
  • fromIntegral may exceed the maximum exponent of the floating point representation and fail with an overflow error or Infinity result.

That is, fromIntegral is of no help here. The most efficient way is to call the native implementation of the square root of GNU's multiprecision library. (How to do that?) The most portable way is to implement a square root algorithm from scratch.

(^!) :: Num a => a -> Int -> a
(^!) x n = x^n

squareRoot :: Integer -> Integer
squareRoot 0 = 0
squareRoot 1 = 1
squareRoot n =
   let twopows = iterate (^!2) 2
       (lowerRoot, lowerN) =
          last $ takeWhile ((n>=) . snd) $ zip (1:twopows) twopows
       newtonStep x = div (x + div n x) 2
       iters = iterate newtonStep (squareRoot (div n lowerN) * lowerRoot)
       isRoot r  =  r^!2 <= n && n < (r+1)^!2
   in  head $ dropWhile (not . isRoot) iters


See also