base-4.15.0.0: Basic libraries
Copyright(c) Ashley Yakeley 2005 2006 2009
LicenseBSD-style (see the file libraries/base/LICENSE)
MaintainerAshley Yakeley <ashley@semantic.org>
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Fixed

Description

This module defines a "Fixed" type for fixed-precision arithmetic. The parameter to Fixed is any type that's an instance of HasResolution. HasResolution has a single method that gives the resolution of the Fixed type.

This module also contains generalisations of div, mod, and divMod to work with any Real instance.

Synopsis

Documentation

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

newtype Fixed (a :: k) Source #

The type parameter should be an instance of HasResolution.

Constructors

MkFixed Integer 

Instances

Instances details
Enum (Fixed a) #

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) == 1.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 #

Eq (Fixed a) #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

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

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

HasResolution a => Fractional (Fixed a) #

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 #

(Typeable k, Typeable a) => Data (Fixed a) #

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 #

HasResolution a => Num (Fixed a) #

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 #

Ord (Fixed a) #

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 #

HasResolution a => Read (Fixed a) #

Since: base-4.3.0.0

Instance details

Defined in Data.Fixed

HasResolution a => Real (Fixed a) #

Since: base-2.1

Instance details

Defined in Data.Fixed

HasResolution a => RealFrac (Fixed a) #

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

Since: base-2.1

Instance details

Defined in Data.Fixed

class HasResolution (a :: k) where Source #

Methods

resolution :: p a -> Integer Source #

Instances

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

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 E12 #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

resolution :: p E12 -> Integer Source #

HasResolution E9 #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E9 -> Integer Source #

HasResolution E6 #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

resolution :: p E6 -> Integer Source #

HasResolution E3 #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E3 -> Integer Source #

HasResolution E2 #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E2 -> Integer Source #

HasResolution E1 #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E1 -> Integer Source #

HasResolution E0 #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E0 -> Integer Source #

showFixed :: HasResolution a => Bool -> Fixed a -> String Source #

First arg is whether to chop off trailing zeros

data E0 Source #

Instances

Instances details
HasResolution E0 #

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

data E1 Source #

Instances

Instances details
HasResolution E1 #

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

data E2 Source #

Instances

Instances details
HasResolution E2 #

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

data E3 Source #

Instances

Instances details
HasResolution E3 #

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

data E6 Source #

Instances

Instances details
HasResolution E6 #

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

data E9 Source #

Instances

Instances details
HasResolution E9 #

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

data E12 Source #

Instances

Instances details
HasResolution E12 #

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