Converting numbers

From HaskellWiki
Jump to navigation Jump to search

Conversion between numerical types in Haskell must be done explicitly. This is unlike many traditional languages (such as C or Java) that automatically coerce between numerical types.

Converting from and between integral types (integer-like types)

Integral types contain only whole numbers and not fractions. The most commonly used integral types are:

  • Integer, which are arbitrary-precision integers, often called "bignum" or "big-integers" in other languages, and
  • Int, which fixed-width machine-specific integers with a minimum guaranteed range of −229 to 229 − 1. In practice, its range can be much larger: on the x86-64 version of Glasgow Haskell Compiler, it can store any signed 64-bit integer.

The workhorse for converting from integral types is fromIntegral, which will convert from any Integral type into any Numeric type (which includes Int, Integer, Rational, and Double):

fromIntegral :: (Num b, Integral a) => a -> b

For example, given an Int value n, one does not simply take its square root by typing sqrt n, since sqrt can only be applied to Floating-point numbers. Instead, one must write sqrt (fromIntegral n) to explicitly convert n to a floating-point number.

There are special cases for converting from Integers:

fromInteger :: Num a => Integer -> a

as well as for converting to Integers:

toInteger:: Integral a => a -> Integer

Converting from real and between real-fractional types (rational-like types)

RealFractional types can contain either whole numbers or fractions. The most commonly used real-fractional types are:

Real types include both Integral and RealFractional types. The name "real" indicates that it excludes Complex numbers.

The workhorse for converting from real types is realToFrac, which will convert from any Real type into any Fractional type (which includes Rational and Double):

realToFrac:: (Real a, Fractional b) => a -> b

It can also be used to convert between real-fractional types.

There are special cases for converting from Rationals:

fromRational :: Fractional a => Rational -> a

as well as for converting to Rationals:

toRational :: Real a => a -> Rational

Converting from real-fractional numbers to integral numbers

This is an inherently lossy transformation since integral types cannot express non-whole numbers. Depending on how you wish to convert, you may choose any of the following:

ceiling  :: (RealFrac a, Integral b) => a -> b
floor    :: (RealFrac a, Integral b) => a -> b
truncate :: (RealFrac a, Integral b) => a -> b
round    :: (RealFrac a, Integral b) => a -> b

Converting between different floating-point precisions

Conversion between Float and Double can be done using the GHC-specific functions in the GHC.Float module:

float2Double :: Float -> Double
double2Float :: Double -> Float

Automatic conversion

Repeatedly people ask for automatic conversion between numbers. This is usually not a good idea; for more information, refer to the thoughts about a Generic number type.

Example

Hi, I am trying to write some functions that convert between two coordinate systems. The first coordinate system, which ill call coord1, starts in the upper left at (0, 0) and ends in the lower right at (500, 500). Coordinates in coord1 have type (Int, Int). The second coord system, which I'll call coord2, starts in the lower left at (0.0, 0.0) and ends in the upper right at (1.0, 1.0). Coords in coord2 have type (Float, Float). I was hoping someone could help me figure out how I can rewrite the two functions below so that the type checker will accept them.

 coord1ToCoord2 :: (Int, Int) -> (Float, Float)
 coord1ToCoord2 (x, y) = (x/500, (500-y)/500)

 coord2ToCoord1 :: (Float, Float) -> (Int, Int)
 coord2ToCoord1 (x, y) = (500/(1/x), 500 - 500/(1/y))

examples of what i want. i think i have the logic right :)

 coord1ToCoord2 (0, 0) -> (0.0, 1.0)
 coord1ToCoord2 (250, 250) -> (0.5, 0.5)
 coord1ToCoord2 (350, 350) -> (0.7, 0.3)
 coord1ToCoord2 (500, 500) -> (1.0, 0.0)

 coord2ToCoord1 (0.0, 0.0) -> (0, 500)
 coord2ToCoord1 (0.5, 0.5) -> (250, 250)
 coord2ToCoord1 (0.7, 0.7) -> (350, 150)
 coord2ToCoord1 (1.0, 1.0) -> (500, 0)

One of the thing that confused me was that I expected 500 to be an Int, but in fact the literals are automatically converted to a correct Num instance.

The solution here was to use fromIntegral and round :

coord1ToCoord2 :: (Int, Int) -> (Float, Float)
coord1ToCoord2 (x, y) = (fromIntegral x/500, (500 - fromIntegral y)/500)

coord2ToCoord1 :: (Float, Float) -> (Int, Int)
coord2ToCoord1 (x, y) = (round (500 * x), round (500 - 500 * y))