Difference between revisions of "Converting numbers"

From HaskellWiki
Jump to navigation Jump to search
(ported from hawiki)
 
(8 intermediate revisions by 4 users not shown)
Line 1: Line 1:
Converting between numerical types in haskell must be done explicitly, this is unlike languages like C which automatically cast between numerical types in certain situations.
+
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.
   
  +
== Converting from integers and between integer types ==
= Integral types =
 
   
Integral types are ones which may only contain whole numbers and not fractions such as 'Int' and 'Integer' in the standard haskell libraries.
+
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.
   
the workhorse is 'fromIntegral' which will convert any integral type into another.
+
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> ...):
  +
<haskell>
  +
fromIntegral :: (Num b, Integral a) => a -> b
  +
</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.
= Rational types =
 
   
  +
== Converting to Rational ==
toRational
 
fromRational
 
   
  +
To convert something to a <hask>Rational</hask> type, you can use the function <hask>toRational</hask>:
= Going back and forth =
 
  +
<haskell>
  +
toRational :: (Real a) => a -> Rational
  +
</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.
   
  +
You can also construct <hask>Rational</hask> values explicitly using the <hask>%</hask> operator.
== Integral type to rational type ==
 
   
 
== Converting to Integral ==
toRational
 
   
 
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.
== Rational to Integral ==
 
   
  +
* <hask>ceiling :: (RealFrac a, Integral b) => a -> b</hask>
this is inherently a 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>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>
   
  +
== Converting between float types ==
* ceiling
 
* floor
 
* truncate
 
* round
 
   
  +
Say, conversion from Float to Double and back.
= original =
 
   
  +
* <hask>import GHC.Float</hask>
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). coords 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 funs below so that the type checker will accept them.
 
  +
* <hask>:t float2Double</hask>
{{{
 
  +
* <hask>float2Double :: Float -> Double</hask>
  +
* <hask>:t double2Float</hask>
  +
* <hask>double2Float :: Double -> Float</hask>
  +
  +
== 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.
  +
<haskell>
 
coord1ToCoord2 :: (Int, Int) -> (Float, Float)
 
coord1ToCoord2 :: (Int, Int) -> (Float, Float)
 
coord1ToCoord2 (x, y) = (x/500, (500-y)/500)
 
coord1ToCoord2 (x, y) = (x/500, (500-y)/500)
Line 36: Line 54:
 
coord2ToCoord1 :: (Float, Float) -> (Int, Int)
 
coord2ToCoord1 :: (Float, Float) -> (Int, Int)
 
coord2ToCoord1 (x, y) = (500/(1/x), 500 - 500/(1/y))
 
coord2ToCoord1 (x, y) = (500/(1/x), 500 - 500/(1/y))
  +
</haskell>
}}}
 
 
examples of what i want. i think i have the logic right :)
 
examples of what i want. i think i have the logic right :)
  +
<haskell>
{{{
 
 
coord1ToCoord2 (0, 0) -> (0.0, 1.0)
 
coord1ToCoord2 (0, 0) -> (0.0, 1.0)
 
coord1ToCoord2 (250, 250) -> (0.5, 0.5)
 
coord1ToCoord2 (250, 250) -> (0.5, 0.5)
Line 48: Line 66:
 
coord2ToCoord1 (0.7, 0.7) -> (350, 150)
 
coord2ToCoord1 (0.7, 0.7) -> (350, 150)
 
coord2ToCoord1 (1.0, 1.0) -> (500, 0)
 
coord2ToCoord1 (1.0, 1.0) -> (500, 0)
  +
</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 :
  +
<haskell>
  +
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))
  +
</haskell>
   
  +
[[Category:Mathematics]]
when i saw an expression like
 
  +
[[Category:FAQ]]
{{{
 
  +
[[Category:Idioms]]
500 * 0.2
 
}}}
 
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
 
{{{
 
(toInteger (500 :: Int)) * 0.2
 
}}}
 
which of course the typechecker wouldnt accept. now that i have rid myself of my incorrect assumptions i see that i should be writing
 
{{{
 
(fromRational (toRational (500 :: Int)) * 0.2) :: Float
 
}}}
 
now that i have a better understanding i am able to write my funs. thank you for your help :)
 

Revision as of 02:54, 4 July 2011

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.

Converting from integers and between integer types

Integral types are ones which may only contain whole numbers and not fractions. Int (fixed-size machine integers) and Integer (arbitrary precision integers) are the two Integral types in the standard Haskell libraries.

The workhorse for converting Integral types is fromIntegral, which will convert any integral type into any numeric type (e.g. Rational, Double, Int16 ...):

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

For example, if you have an Int value n, you cannot take its square root by typing sqrt n, since sqrt may only be applied to Floating values. Instead, you must write sqrt (fromIntegral n) to explicitly convert n to a non-integral type.

Converting to Rational

To convert something to a Rational type, you can use the function toRational:

toRational :: (Real a) => a -> Rational

Values of type Rational represent rational numbers exactly as the ratio of two Integers. Applying toRational to an Integral value n will produce the rational number n % 1; applying toRational to a decimal (i.e. Fractional or Floating) value will produce a rational approximation.

You can also construct Rational values explicitly using the % operator.

Converting to Integral

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.

  • 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 float types

Say, conversion from Float to Double and back.

  • import GHC.Float
  • :t float2Double
  • float2Double :: Float -> Double
  • :t double2Float
  • 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))