Difference between revisions of "Converting numbers"

From HaskellWiki
Jump to navigation Jump to search
(realToFrac)
(don't use realToFrac for fractional types)
 
(4 intermediate revisions by 3 users not shown)
Line 1: Line 1:
Converting between numerical types in Haskell must be done explicitly. This is unlike languages (such as C or Java) which automatically cast between numerical types in certain situations.
+
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 integers and between integer types ==
+
== Converting from and between integral types (integer-like types) ==
   
Integral types are ones which may only contain whole numbers and not fractions. <hask>Int</hask> (fixed-size machine integers) and <hask>Integer</hask> (arbitrary precision integers) are the two Integral types in the standard Haskell libraries.
+
<hask>Integral</hask> types contain only whole numbers and not fractions. The most commonly used integral types are:
   
  +
* <hask>Integer</hask>, which are arbitrary-precision integers, often called "bignum" or "big-integers" in other languages, and
The workhorse for converting Integral types is <hask>fromIntegral</hask>, which will convert any integral type into any numeric type (e.g. <hask>Rational</hask>, <hask>Double</hask>, <hask>Int16</hask> ...):
 
  +
* <hask>Int</hask>, which fixed-width machine-specific integers with a minimum guaranteed range of <code>&minus;2<sup>29</sup></code> to <code>2<sup>29</sup> &minus; 1</code>. 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.
<haskell>
 
  +
 
The workhorse for converting from integral types is <hask>fromIntegral</hask>, which will convert from any <hask>Integral</hask> type into any <hask>Num</hask>eric type (which includes <hask>Int</hask>, <hask>Integer</hask>, <hask>Rational</hask>, and <hask>Double</hask>):
  +
  +
: <haskell>
 
fromIntegral :: (Num b, Integral a) => a -> b
 
fromIntegral :: (Num b, Integral a) => a -> b
 
</haskell>
 
</haskell>
   
For example, if you have an <hask>Int</hask> value <hask>n</hask>, you cannot take its square root by typing <hask>sqrt n</hask>, since <hask>sqrt</hask> may only be applied to Floating values. Instead, you must write <hask>sqrt (fromIntegral n)</hask> to explicitly convert <hask>n</hask> to a non-integral type.
+
For example, given an <hask>Int</hask> value <hask>n</hask>, one does not simply take its square root by typing <hask>sqrt n</hask>, since <hask>sqrt</hask> can only be applied to <hask>Floating</hask>-point numbers. Instead, one must write <hask>sqrt (fromIntegral n)</hask> to explicitly convert <hask>n</hask> to a floating-point number.
   
  +
There are special cases for converting from <hask>Integer</hask>s:
== Converting to Rational ==
 
   
  +
: <haskell>
To convert something to a <hask>Rational</hask> type, you can use the function <hask>toRational</hask>:
 
  +
fromInteger :: Num a => Integer -> a
<haskell>
 
toRational :: (Real a) => a -> Rational
 
 
</haskell>
 
</haskell>
Values of type <hask>Rational</hask> represent rational numbers exactly as the ratio of two <hask>Integer</hask>s. Applying <hask>toRational</hask> to an <hask>Integral</hask> value <hask>n</hask> will produce the rational number <hask>n % 1</hask>; applying <hask>toRational</hask> to a decimal (i.e. <hask>Fractional</hask> or <hask>Floating</hask>) value will produce a rational approximation.
 
   
  +
as well as for converting to <hask>Integer</hask>s:
You can also construct <hask>Rational</hask> values explicitly using the <hask>%</hask> operator.
 
   
  +
: <haskell>
== Converting to Integral ==
 
  +
toInteger:: Integral a => a -> Integer
 
</haskell>
   
  +
== Converting from real and between real-fractional types (rational-like types) ==
This is an inherently lossy transformation since integral types cannot express non-whole numbers. Depending on how you wish to convert, you might choose one of several methods.
 
   
  +
<hask>RealFrac</hask>tional types can contain either whole numbers or fractions. The most commonly used real-fractional types are:
* <hask>ceiling :: (RealFrac a, Integral b) => a -> b</hask>
 
* <hask>floor :: (RealFrac a, Integral b) => a -> b</hask>
 
* <hask>truncate :: (RealFrac a, Integral b) => a -> b</hask>
 
* <hask>round :: (RealFrac a, Integral b) => a -> b</hask>
 
   
  +
* <hask>Rational</hask>, which are [[Rational|arbitrary-precision fractions]], and
== Converting between float types ==
 
  +
* <hask>Double</hask>, which are double-precision floating-point numbers.
   
  +
<hask>Real</hask> types include both <hask>Integral</hask> and <hask>RealFrac</hask>tional types. The name "real" indicates that it excludes <hask>Complex</hask> numbers.
Say, conversion from Float to Double and back.
 
   
  +
The workhorse for converting from real types is <hask>realToFrac</hask>, which will convert from any <hask>Real</hask> type into any <hask>Fractional</hask> type (which includes <hask>Rational</hask> and <hask>Double</hask>):
* <hask>realToFrac :: (Real a, Fractional b) => a -> b</hask>
 
  +
* <hask>fromRational . toRational :: (Real a, Fractional b) => a -> b</hask>
 
  +
: <haskell>
 
realToFrac:: (Real a, Fractional b) => a -> b
 
</haskell>
  +
  +
It can also be used to convert between real-fractional types. (Warning: Avoid using <hask>realToFrac</hask> to convert between floating-point types; see [[#Converting between different floating-point precisions|below]].)
  +
  +
There are special cases for converting from <hask>Rational</hask>s:
  +
  +
: <haskell>
  +
fromRational :: Fractional a => Rational -> a
  +
</haskell>
  +
  +
as well as for converting to <hask>Rational</hask>s:
  +
  +
: <haskell>
 
toRational :: Real a => a -> Rational
  +
</haskell>
  +
  +
== 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:
  +
 
<haskell>
 
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
  +
</haskell>
  +
 
== Converting between different floating-point precisions ==
  +
  +
Conversion between <hask>Float</hask> and <hask>Double</hask> can be done using the GHC-specific functions in the [https://hackage.haskell.org/package/base/docs/src/GHC-Float.html GHC.Float module]:
  +
 
<haskell>
  +
float2Double :: Float -> Double
  +
double2Float :: Double -> Float
 
</haskell>
  +
  +
Avoid using <hask>realToFrac</hask> to convert between floating-point types as the intermediate type <hask>Rational</hask> is unable to represent exceptional values like infinity or NaN. See [https://ghc.haskell.org/trac/ghc/ticket/3676 GHC ticket #3676].
   
 
== Automatic conversion ==
 
== Automatic conversion ==
Line 42: Line 83:
 
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]].
 
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]].
   
== original ==
+
== Example ==
   
Hi, I am trying to write some funs 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 ill 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.
+
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.
 
<haskell>
 
<haskell>
 
coord1ToCoord2 :: (Int, Int) -> (Float, Float)
 
coord1ToCoord2 :: (Int, Int) -> (Float, Float)
Line 64: Line 105:
 
coord2ToCoord1 (1.0, 1.0) -> (500, 0)
 
coord2ToCoord1 (1.0, 1.0) -> (500, 0)
 
</haskell>
 
</haskell>
  +
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.
Ah. I realize what is messing me up.
 
   
  +
The solution here was to use fromIntegral and round :
When i saw an expression like
 
 
<haskell>
 
<haskell>
  +
coord1ToCoord2 :: (Int, Int) -> (Float, Float)
500 * 0.2
 
  +
coord1ToCoord2 (x, y) = (fromIntegral x/500, (500 - fromIntegral y)/500)
</haskell>
 
  +
i had assumed that 500 :: Integer because it didnt end in a .0. but it actually has type Double. so my problem was i would do something like this
 
  +
coord2ToCoord1 :: (Float, Float) -> (Int, Int)
<haskell>
 
  +
coord2ToCoord1 (x, y) = (round (500 * x), round (500 - 500 * y))
(toInteger (500 :: Int)) * 0.2
 
</haskell>
 
which of course the typechecker wouldnt accept. now that i have rid myself of my incorrect assumptions i see that i should be writing
 
<haskell>
 
(fromRational (toRational (500 :: Int)) * 0.2) :: Float
 
 
</haskell>
 
</haskell>
now that i have a better understanding i am able to write my funs. thank you for your help :)
 
   
 
[[Category:Mathematics]]
 
[[Category:Mathematics]]

Latest revision as of 01:28, 14 April 2016

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. (Warning: Avoid using realToFrac to convert between floating-point types; see below.)

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

Avoid using realToFrac to convert between floating-point types as the intermediate type Rational is unable to represent exceptional values like infinity or NaN. See GHC ticket #3676.

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))