base-4.20.0.0: Core data structures and operations
Copyright(c) Ashley Yakeley 2005 2006 2009
LicenseBSD-style (see the file libraries/base/LICENSE)
MaintainerAshley Yakeley <ashley@semantic.org>
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

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) :: Milli
0.123
Synopsis

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

Expand
 MkFixed 12345 :: Fixed E3

Constructors

MkFixed Integer 

Instances

Instances details
(Typeable k, Typeable a) => Data (Fixed a) Source #

Since: base-4.1.0.0

Instance details

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, succ and pred typically add and subtract 1, respectively. This is not true in the case of Fixed, whose successor and predecessor functions intuitively return the "next" and "previous" values in the enumeration. The results of these functions thus depend on the resolution of the Fixed value. For example, when enumerating values of resolution 10^-3 of type Milli = Fixed E3,

>>> succ (0.000 :: Milli)
0.001

and likewise

>>> pred (0.000 :: Milli)
-0.001

In other words, succ and pred increment and decrement a fixed-precision value by the least amount such that the value's resolution is unchanged. For example, 10^-12 is the smallest (positive) amount that can be added to a value of type Pico = Fixed E12 without changing its resolution, and so

>>> succ (0.000000000000 :: Pico)
0.000000000001

and similarly

>>> pred (0.000000000000 :: Pico)
-0.000000000001

This is worth bearing in mind when defining Fixed arithmetic sequences. In particular, you may be forgiven for thinking the sequence

  [1..10] :: [Pico]

evaluates to [1, 2, 3, 4, 5, 6, 7, 8, 9, 10] :: [Pico].

However, this is not true. On the contrary, similarly to the above implementations of succ and pred, enumFromTo :: Pico -> Pico -> [Pico] has a "step size" of 10^-12. Hence, the list [1..10] :: [Pico] has the form

  [1.000000000000, 1.00000000001, 1.00000000002, ..., 10.000000000000]

and contains 9 * 10^12 + 1 values.

Since: base-2.1

Instance details

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:

>>> (0.2 * 0.6 :: Deci) * 0.9 == 0.2 * (0.6 * 0.9)
False
>>> (0.1 + 0.1 :: Deci) * 0.5 == 0.1 * 0.5 + 0.1 * 0.5
False

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

(+) :: Fixed a -> Fixed a -> Fixed a Source #

(-) :: Fixed a -> Fixed a -> Fixed a Source #

(*) :: Fixed a -> Fixed a -> Fixed a Source #

negate :: Fixed a -> Fixed a Source #

abs :: Fixed a -> Fixed a Source #

signum :: Fixed a -> Fixed a Source #

fromInteger :: Integer -> Fixed a Source #

HasResolution a => Read (Fixed a) Source #

Since: base-4.3.0.0

Instance details

Defined in Data.Fixed

HasResolution a => Fractional (Fixed a) Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

(/) :: Fixed a -> Fixed a -> Fixed a Source #

recip :: Fixed a -> Fixed a Source #

fromRational :: Rational -> Fixed a Source #

HasResolution a => Real (Fixed a) Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

HasResolution a => RealFrac (Fixed a) Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

properFraction :: Integral b => Fixed a -> (b, Fixed a) Source #

truncate :: Integral b => Fixed a -> b Source #

round :: Integral b => Fixed a -> b Source #

ceiling :: Integral b => Fixed a -> b Source #

floor :: Integral b => Fixed a -> b Source #

HasResolution a => Show (Fixed a) Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Eq (Fixed a) Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

(==) :: Fixed a -> Fixed a -> Bool Source #

(/=) :: Fixed a -> Fixed a -> Bool Source #

Ord (Fixed a) Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

compare :: Fixed a -> Fixed a -> Ordering Source #

(<) :: Fixed a -> Fixed a -> Bool Source #

(<=) :: Fixed a -> Fixed a -> Bool Source #

(>) :: Fixed a -> Fixed a -> Bool Source #

(>=) :: Fixed a -> Fixed a -> Bool Source #

max :: Fixed a -> Fixed a -> Fixed a Source #

min :: Fixed a -> Fixed a -> Fixed a Source #

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

Instances details
KnownNat n => HasResolution (n :: Nat) Source #

For example, Fixed 1000 will give you a Fixed with a resolution of 1000.

Instance details

Defined in Data.Fixed

Methods

resolution :: p n -> Integer Source #

HasResolution E0 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E0 -> Integer Source #

HasResolution E1 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E1 -> Integer Source #

HasResolution E12 Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

resolution :: p E12 -> Integer Source #

HasResolution E2 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E2 -> Integer Source #

HasResolution E3 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E3 -> Integer Source #

HasResolution E6 Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

resolution :: p E6 -> Integer Source #

HasResolution E9 Source #

Since: base-4.1.0.0

Instance details

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

Expand
>>> 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.

ResolutionScaling FactorSynonym for "Fixed EX"show (12345 :: Fixed EX)
E01/1Uni12345.0
E11/10Deci1234.5
E21/100Centi123.45
E31/1 000Milli12.345
E61/1 000 000Micro0.012345
E91/1 000 000 000Nano0.000012345
E121/1 000 000 000 000Pico0.000000012345

1/1

data E0 Source #

Resolution of 1, this works the same as Integer.

Instances

Instances details
HasResolution E0 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E0 -> Integer Source #

type Uni = Fixed E0 Source #

Resolution of 1, this works the same as Integer.

Examples

Expand
>>> show (MkFixed 12345 :: Fixed E0)
"12345.0"
>>> show (MkFixed 12345 :: Uni)
"12345.0"

1/10

data E1 Source #

Resolution of 10^-1 = .1

Instances

Instances details
HasResolution E1 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E1 -> Integer Source #

type Deci = Fixed E1 Source #

Resolution of 10^-1 = .1

Examples

Expand
>>> show (MkFixed 12345 :: Fixed E1)
"1234.5"
>>> show (MkFixed 12345 :: Deci)
"1234.5"

1/100

data E2 Source #

Resolution of 10^-2 = .01, useful for many monetary currencies

Instances

Instances details
HasResolution E2 Source #

Since: base-4.1.0.0

Instance details

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

Expand
>>> show (MkFixed 12345 :: Fixed E2)
"123.45"
>>> show (MkFixed 12345 :: Centi)
"123.45"

1/1 000

data E3 Source #

Resolution of 10^-3 = .001

Instances

Instances details
HasResolution E3 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E3 -> Integer Source #

type Milli = Fixed E3 Source #

Resolution of 10^-3 = .001

Examples

Expand
>>> show (MkFixed 12345 :: Fixed E3)
"12.345"
>>> show (MkFixed 12345 :: Milli)
"12.345"

1/1 000 000

data E6 Source #

Resolution of 10^-6 = .000001

Instances

Instances details
HasResolution E6 Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

resolution :: p E6 -> Integer Source #

type Micro = Fixed E6 Source #

Resolution of 10^-6 = .000001

Examples

Expand
>>> show (MkFixed 12345 :: Fixed E6)
"0.012345"
>>> show (MkFixed 12345 :: Micro)
"0.012345"

1/1 000 000 000

data E9 Source #

Resolution of 10^-9 = .000000001

Instances

Instances details
HasResolution E9 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E9 -> Integer Source #

type Nano = Fixed E9 Source #

Resolution of 10^-9 = .000000001

Examples

Expand
>>> show (MkFixed 12345 :: Fixed E9)
"0.000012345"
>>> show (MkFixed 12345 :: Nano)
"0.000012345"

1/1 000 000 000 000

data E12 Source #

Resolution of 10^-12 = .000000000001

Instances

Instances details
HasResolution E12 Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

resolution :: p E12 -> Integer Source #

type Pico = Fixed E12 Source #

Resolution of 10^-12 = .000000000001

Examples

Expand
>>> show (MkFixed 12345 :: Fixed E12)
"0.000000012345"
>>> show (MkFixed 12345 :: Pico)
"0.000000012345"

Generalized Functions on Real's

div' :: (Real a, Integral b) => a -> a -> b Source #

Generalisation of div to any instance of Real

mod' :: Real a => a -> a -> a Source #

Generalisation of mod to any instance of Real

divMod' :: (Real a, Integral b) => a -> a -> (b, a) Source #

Generalisation of divMod to any instance of Real