| Copyright | (c) Ashley Yakeley 2005 2006 2009 | 
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) | 
| Maintainer | Ashley Yakeley <ashley@semantic.org> | 
| Stability | stable | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.Fixed
Description
This module defines a Fixed type for working with fixed-point arithmetic.
 Fixed-point arithmetic represents fractional numbers with a fixed number of
 digits for their fractional part. This is different to the behaviour of the floating-point
 number types Float and Double, because the number of digits of the
 fractional part of Float and Double numbers depends on the size of the number.
 Fixed point arithmetic is frequently used in financial mathematics, where they
 are used for representing decimal currencies.
The type Fixed is used for fixed-point fractional numbers, which are internally
 represented as an Integer. The type Fixed takes one parameter, which should implement
 the typeclass HasResolution, to specify the number of digits of the fractional part.
 This module provides instances of the HasResolution typeclass for arbitrary typelevel
 natural numbers, and for some canonical important fixed-point representations.
This module also contains generalisations of div, mod, and divMod to
 work with any Real instance.
Automatic conversion between different Fixed can be performed through
 realToFrac, bear in mind that converting to a fixed with a smaller
 resolution will truncate the number, losing information.
>>>realToFrac (0.123456 :: Pico) :: Milli0.123
Synopsis
- newtype Fixed (a :: k) = MkFixed Integer
- class HasResolution (a :: k) where- resolution :: p a -> Integer
 
- showFixed :: forall {k} (a :: k). HasResolution a => Bool -> Fixed a -> String
- data E0
- type Uni = Fixed E0
- data E1
- type Deci = Fixed E1
- data E2
- type Centi = Fixed E2
- data E3
- type Milli = Fixed E3
- data E6
- type Micro = Fixed E6
- data E9
- type Nano = Fixed E9
- data E12
- type Pico = Fixed E12
- div' :: (Real a, Integral b) => a -> a -> b
- mod' :: Real a => a -> a -> a
- divMod' :: (Real a, Integral b) => a -> a -> (b, a)
The Fixed Type
newtype Fixed (a :: k) Source #
The type of fixed-point fractional numbers.
   The type parameter specifies the number of digits of the fractional part and should be an instance of the HasResolution typeclass.
Examples
MkFixed 12345 :: Fixed E3
Instances
| (Typeable k, Typeable a) => Data (Fixed a) Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixed a -> c (Fixed a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Fixed a) Source # toConstr :: Fixed a -> Constr Source # dataTypeOf :: Fixed a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Fixed a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Fixed a)) Source # gmapT :: (forall b. Data b => b -> b) -> Fixed a -> Fixed a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixed a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixed a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Fixed a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixed a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixed a -> m (Fixed a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixed a -> m (Fixed a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixed a -> m (Fixed a) Source # | |
| Enum (Fixed a) Source # | Recall that, for numeric types,  
 and likewise 
 In other words,  
 and similarly 
 This is worth bearing in mind when defining  [1..10] :: [Pico] evaluates to  However, this is not true. On the contrary, similarly to the above
 implementations of  [1.000000000000, 1.00000000001, 1.00000000002, ..., 10.000000000000] and contains  Since: base-2.1 | 
| Defined in Data.Fixed Methods succ :: Fixed a -> Fixed a Source # pred :: Fixed a -> Fixed a Source # toEnum :: Int -> Fixed a Source # fromEnum :: Fixed a -> Int Source # enumFrom :: Fixed a -> [Fixed a] Source # enumFromThen :: Fixed a -> Fixed a -> [Fixed a] Source # enumFromTo :: Fixed a -> Fixed a -> [Fixed a] Source # enumFromThenTo :: Fixed a -> Fixed a -> Fixed a -> [Fixed a] Source # | |
| HasResolution a => Num (Fixed a) Source # | Multiplication is not associative or distributive: 
 
 Since: base-2.1 | 
| Defined in Data.Fixed | |
| HasResolution a => Read (Fixed a) Source # | Since: base-4.3.0.0 | 
| HasResolution a => Fractional (Fixed a) Source # | Since: base-2.1 | 
| HasResolution a => Real (Fixed a) Source # | Since: base-2.1 | 
| Defined in Data.Fixed Methods toRational :: Fixed a -> Rational Source # | |
| HasResolution a => RealFrac (Fixed a) Source # | Since: base-2.1 | 
| HasResolution a => Show (Fixed a) Source # | Since: base-2.1 | 
| Eq (Fixed a) Source # | Since: base-2.1 | 
| Ord (Fixed a) Source # | Since: base-2.1 | 
class HasResolution (a :: k) where Source #
Types which can be used as a resolution argument to the Fixed type constructor must implement the HasResolution  typeclass.
Methods
resolution :: p a -> Integer Source #
Provide the resolution for a fixed-point fractional number.
Instances
| KnownNat n => HasResolution (n :: Nat) Source # | For example,  | 
| Defined in Data.Fixed Methods resolution :: p n -> Integer Source # | |
| HasResolution E0 Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods resolution :: p E0 -> Integer Source # | |
| HasResolution E1 Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods resolution :: p E1 -> Integer Source # | |
| HasResolution E12 Source # | Since: base-2.1 | 
| Defined in Data.Fixed Methods resolution :: p E12 -> Integer Source # | |
| HasResolution E2 Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods resolution :: p E2 -> Integer Source # | |
| HasResolution E3 Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods resolution :: p E3 -> Integer Source # | |
| HasResolution E6 Source # | Since: base-2.1 | 
| Defined in Data.Fixed Methods resolution :: p E6 -> Integer Source # | |
| HasResolution E9 Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods resolution :: p E9 -> Integer Source # | |
showFixed :: forall {k} (a :: k). HasResolution a => Bool -> Fixed a -> String Source #
First arg is whether to chop off trailing zeros
Examples
>>>showFixed True (MkFixed 10000 :: Fixed E3)"10"
>>>showFixed False (MkFixed 10000 :: Fixed E3)"10.000"
Resolution / Scaling Factors
The resolution or scaling factor determines the number of digits in the fractional part.
| Resolution | Scaling Factor | Synonym for "Fixed EX" | show (12345 :: Fixed EX) | 
|---|---|---|---|
| E0 | 1/1 | Uni | 12345.0 | 
| E1 | 1/10 | Deci | 1234.5 | 
| E2 | 1/100 | Centi | 123.45 | 
| E3 | 1/1 000 | Milli | 12.345 | 
| E6 | 1/1 000 000 | Micro | 0.012345 | 
| E9 | 1/1 000 000 000 | Nano | 0.000012345 | 
| E12 | 1/1 000 000 000 000 | Pico | 0.000000012345 | 
1/1
Resolution of 1, this works the same as Integer.
Instances
| HasResolution E0 Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods resolution :: p E0 -> Integer Source # | |
Resolution of 1, this works the same as Integer.
Examples
>>>show (MkFixed 12345 :: Fixed E0)"12345.0"
>>>show (MkFixed 12345 :: Uni)"12345.0"
1/10
Resolution of 10^-1 = .1
Instances
| HasResolution E1 Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods resolution :: p E1 -> Integer Source # | |
Resolution of 10^-1 = .1
Examples
>>>show (MkFixed 12345 :: Fixed E1)"1234.5"
>>>show (MkFixed 12345 :: Deci)"1234.5"
1/100
Resolution of 10^-2 = .01, useful for many monetary currencies
Instances
| HasResolution E2 Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods resolution :: p E2 -> Integer Source # | |
type Centi = Fixed E2 Source #
Resolution of 10^-2 = .01, useful for many monetary currencies
Examples
>>>show (MkFixed 12345 :: Fixed E2)"123.45"
>>>show (MkFixed 12345 :: Centi)"123.45"
1/1 000
Resolution of 10^-3 = .001
Instances
| HasResolution E3 Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods resolution :: p E3 -> Integer Source # | |
type Milli = Fixed E3 Source #
Resolution of 10^-3 = .001
Examples
>>>show (MkFixed 12345 :: Fixed E3)"12.345"
>>>show (MkFixed 12345 :: Milli)"12.345"
1/1 000 000
Resolution of 10^-6 = .000001
Instances
| HasResolution E6 Source # | Since: base-2.1 | 
| Defined in Data.Fixed Methods resolution :: p E6 -> Integer Source # | |
type Micro = Fixed E6 Source #
Resolution of 10^-6 = .000001
Examples
>>>show (MkFixed 12345 :: Fixed E6)"0.012345"
>>>show (MkFixed 12345 :: Micro)"0.012345"
1/1 000 000 000
Resolution of 10^-9 = .000000001
Instances
| HasResolution E9 Source # | Since: base-4.1.0.0 | 
| Defined in Data.Fixed Methods resolution :: p E9 -> Integer Source # | |
Resolution of 10^-9 = .000000001
Examples
>>>show (MkFixed 12345 :: Fixed E9)"0.000012345"
>>>show (MkFixed 12345 :: Nano)"0.000012345"
1/1 000 000 000 000
Resolution of 10^-12 = .000000000001
Instances
| HasResolution E12 Source # | Since: base-2.1 | 
| Defined in Data.Fixed Methods resolution :: p E12 -> Integer Source # | |
type Pico = Fixed E12 Source #
Resolution of 10^-12 = .000000000001
Examples
>>>show (MkFixed 12345 :: Fixed E12)"0.000000012345"
>>>show (MkFixed 12345 :: Pico)"0.000000012345"