ghc-internal-9.1001.0: Basic libraries
Copyright(c) The University of Glasgow 1994-2002
Portions obtained from hbc (c) Lennart Augusstson
Licensesee libraries/base/LICENSE
Maintainerghc-devs@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC Extensions)
Safe HaskellTrustworthy
LanguageHaskell2010

GHC.Internal.Float

Description

The types Float and Double, the classes Floating and RealFloat and casting between Word32 and Float and Word64 and Double.

Synopsis

Classes

class Fractional a => Floating a where Source #

Trigonometric and hyperbolic functions and related functions.

The Haskell Report defines no laws for Floating. However, (+), (*) and exp are customarily expected to define an exponential field and have the following properties:

  • exp (a + b) = exp a * exp b
  • exp (fromInteger 0) = fromInteger 1

Minimal complete definition

pi, exp, log, sin, cos, asin, acos, atan, sinh, cosh, asinh, acosh, atanh

Methods

pi :: a Source #

exp :: a -> a Source #

log :: a -> a Source #

sqrt :: a -> a Source #

(**) :: a -> a -> a infixr 8 Source #

logBase :: a -> a -> a Source #

sin :: a -> a Source #

cos :: a -> a Source #

tan :: a -> a Source #

asin :: a -> a Source #

acos :: a -> a Source #

atan :: a -> a Source #

sinh :: a -> a Source #

cosh :: a -> a Source #

tanh :: a -> a Source #

asinh :: a -> a Source #

acosh :: a -> a Source #

atanh :: a -> a Source #

log1p :: a -> a Source #

log1p x computes log (1 + x), but provides more precise results for small (absolute) values of x if possible.

@since base-4.9.0.0

expm1 :: a -> a Source #

expm1 x computes exp x - 1, but provides more precise results for small (absolute) values of x if possible.

@since base-4.9.0.0

log1pexp :: a -> a Source #

log1pexp x computes log (1 + exp x), but provides more precise results if possible.

Examples:

  • if x is a large negative number, log (1 + exp x) will be imprecise for the reasons given in log1p.
  • if exp x is close to -1, log (1 + exp x) will be imprecise for the reasons given in expm1.

@since base-4.9.0.0

log1mexp :: a -> a Source #

log1mexp x computes log (1 - exp x), but provides more precise results if possible.

Examples:

  • if x is a large negative number, log (1 - exp x) will be imprecise for the reasons given in log1p.
  • if exp x is close to 1, log (1 - exp x) will be imprecise for the reasons given in expm1.

@since base-4.9.0.0

Instances

Instances details
Floating CDouble Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Floating CFloat Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Floating Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Floating Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Floating a => Floating (Identity a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Floating a => Floating (Down a) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

pi :: Down a Source #

exp :: Down a -> Down a Source #

log :: Down a -> Down a Source #

sqrt :: Down a -> Down a Source #

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

logBase :: Down a -> Down a -> Down a Source #

sin :: Down a -> Down a Source #

cos :: Down a -> Down a Source #

tan :: Down a -> Down a Source #

asin :: Down a -> Down a Source #

acos :: Down a -> Down a Source #

atan :: Down a -> Down a Source #

sinh :: Down a -> Down a Source #

cosh :: Down a -> Down a Source #

tanh :: Down a -> Down a Source #

asinh :: Down a -> Down a Source #

acosh :: Down a -> Down a Source #

atanh :: Down a -> Down a Source #

log1p :: Down a -> Down a Source #

expm1 :: Down a -> Down a Source #

log1pexp :: Down a -> Down a Source #

log1mexp :: Down a -> Down a Source #

Floating a => Floating (Const a b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

pi :: Const a b Source #

exp :: Const a b -> Const a b Source #

log :: Const a b -> Const a b Source #

sqrt :: Const a b -> Const a b Source #

(**) :: Const a b -> Const a b -> Const a b Source #

logBase :: Const a b -> Const a b -> Const a b Source #

sin :: Const a b -> Const a b Source #

cos :: Const a b -> Const a b Source #

tan :: Const a b -> Const a b Source #

asin :: Const a b -> Const a b Source #

acos :: Const a b -> Const a b Source #

atan :: Const a b -> Const a b Source #

sinh :: Const a b -> Const a b Source #

cosh :: Const a b -> Const a b Source #

tanh :: Const a b -> Const a b Source #

asinh :: Const a b -> Const a b Source #

acosh :: Const a b -> Const a b Source #

atanh :: Const a b -> Const a b Source #

log1p :: Const a b -> Const a b Source #

expm1 :: Const a b -> Const a b Source #

log1pexp :: Const a b -> Const a b Source #

log1mexp :: Const a b -> Const a b Source #

class (RealFrac a, Floating a) => RealFloat a where Source #

Efficient, machine-independent access to the components of a floating-point number.

Methods

floatRadix :: a -> Integer Source #

a constant function, returning the radix of the representation (often 2)

floatDigits :: a -> Int Source #

a constant function, returning the number of digits of floatRadix in the significand

floatRange :: a -> (Int, Int) Source #

a constant function, returning the lowest and highest values the exponent may assume

decodeFloat :: a -> (Integer, Int) Source #

The function decodeFloat applied to a real floating-point number returns the significand expressed as an Integer and an appropriately scaled exponent (an Int). If decodeFloat x yields (m,n), then x is equal in value to m*b^^n, where b is the floating-point radix, and furthermore, either m and n are both zero or else b^(d-1) <= abs m < b^d, where d is the value of floatDigits x. In particular, decodeFloat 0 = (0,0). If the type contains a negative zero, also decodeFloat (-0.0) = (0,0). The result of decodeFloat x is unspecified if either of isNaN x or isInfinite x is True.

encodeFloat :: Integer -> Int -> a Source #

encodeFloat performs the inverse of decodeFloat in the sense that for finite x with the exception of -0.0, uncurry encodeFloat (decodeFloat x) = x. encodeFloat m n is one of the two closest representable floating-point numbers to m*b^^n (or ±Infinity if overflow occurs); usually the closer, but if m contains too many bits, the result may be rounded in the wrong direction.

exponent :: a -> Int Source #

exponent corresponds to the second component of decodeFloat. exponent 0 = 0 and for finite nonzero x, exponent x = snd (decodeFloat x) + floatDigits x. If x is a finite floating-point number, it is equal in value to significand x * b ^^ exponent x, where b is the floating-point radix. The behaviour is unspecified on infinite or NaN values.

significand :: a -> a Source #

The first component of decodeFloat, scaled to lie in the open interval (-1,1), either 0.0 or of absolute value >= 1/b, where b is the floating-point radix. The behaviour is unspecified on infinite or NaN values.

scaleFloat :: Int -> a -> a Source #

multiplies a floating-point number by an integer power of the radix

isNaN :: a -> Bool Source #

True if the argument is an IEEE "not-a-number" (NaN) value

isInfinite :: a -> Bool Source #

True if the argument is an IEEE infinity or negative infinity

isDenormalized :: a -> Bool Source #

True if the argument is too small to be represented in normalized format

isNegativeZero :: a -> Bool Source #

True if the argument is an IEEE negative zero

isIEEE :: a -> Bool Source #

True if the argument is an IEEE floating point number

atan2 :: a -> a -> a Source #

a version of arctangent taking two real floating-point arguments. For real floating x and y, atan2 y x computes the angle (from the positive x-axis) of the vector from the origin to the point (x,y). atan2 y x returns a value in the range [-pi, pi]. It follows the Common Lisp semantics for the origin when signed zeroes are supported. atan2 y 1, with y in a type that is RealFloat, should return the same value as atan y. A default definition of atan2 is provided, but implementors can provide a more accurate implementation.

Instances

Instances details
RealFloat CDouble Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

RealFloat CFloat Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

RealFloat Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

RealFloat Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

RealFloat a => RealFloat (Identity a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

RealFloat a => RealFloat (Down a) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Data.Ord

RealFloat a => RealFloat (Const a b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Float

data Float Source #

Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.

Constructors

F# Float# 

Instances

Instances details
Data Float Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Float -> c Float Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float Source #

toConstr :: Float -> Constr Source #

dataTypeOf :: Float -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Float) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) Source #

gmapT :: (forall b. Data b => b -> b) -> Float -> Float Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source #

Enum Float Source #

@since base-2.01

fromEnum just truncates its argument, beware of all sorts of overflows.

List generators have extremely peculiar behavior, mandated by Haskell Report 2010:

>>> [0..1.5 :: Float]
[0.0,1.0,2.0]
Instance details

Defined in GHC.Internal.Float

Floating Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

RealFloat Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Storable Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.Storable

Num Float Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:

>>> (0.1 + 0.1 :: Float) + 0.5 == 0.1 + (0.1 + 0.5)
False
>>> (0.1 + 0.2 :: Float) * 0.9 == 0.1 * 0.9 + 0.2 * 0.9
False
>>> (0.1 * 0.1 :: Float) * 0.9 == 0.1 * (0.1 * 0.9)
False
Instance details

Defined in GHC.Internal.Float

Read Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Fractional Float Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero.

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
>>> map (/ 0) [-1, 0, 1 :: Float]
[-Infinity,NaN,Infinity]
>>> map (* 0) $ map (/ 0) [-1, 0, 1 :: Float]
[NaN,NaN,NaN]
Instance details

Defined in GHC.Internal.Float

Real Float Source #

@since base-2.01

Beware that toRational generates garbage for non-finite arguments:

>>> toRational (1/0 :: Float)
340282366920938463463374607431768211456 % 1
>>> toRational (0/0 :: Float)
510423550381407695195061911147652317184 % 1
Instance details

Defined in GHC.Internal.Float

RealFrac Float Source #

@since base-2.01

Beware that results for non-finite arguments are garbage:

>>> [ f x | f <- [round, floor, ceiling], x <- [-1/0, 0/0, 1/0 :: Float] ] :: [Int]
[0,0,0,0,0,0,0,0,0]
>>> map properFraction [-1/0, 0/0, 1/0] :: [(Int, Float)]
[(0,0.0),(0,0.0),(0,0.0)]

and get even more non-sensical if you ask for Integer instead of Int.

Instance details

Defined in GHC.Internal.Float

Methods

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

truncate :: Integral b => Float -> b Source #

round :: Integral b => Float -> b Source #

ceiling :: Integral b => Float -> b Source #

floor :: Integral b => Float -> b Source #

Show Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Eq Float

Note that due to the presence of NaN, Float's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Float)
False

Also note that Float's Eq instance does not satisfy extensionality:

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
Instance details

Defined in GHC.Classes

Methods

(==) :: Float -> Float -> Bool Source #

(/=) :: Float -> Float -> Bool Source #

Ord Float

See instance Ord Double for discussion of deviations from IEEE 754 standard.

Instance details

Defined in GHC.Classes

Generic1 (URec Float :: k -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (URec Float :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Float :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: k -> Type)))

Methods

from1 :: forall (a :: k). URec Float a -> Rep1 (URec Float :: k -> Type) a Source #

to1 :: forall (a :: k). Rep1 (URec Float :: k -> Type) a -> URec Float a Source #

Foldable (UFloat :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => UFloat m -> m Source #

foldMap :: Monoid m => (a -> m) -> UFloat a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UFloat a -> m Source #

foldr :: (a -> b -> b) -> b -> UFloat a -> b Source #

foldr' :: (a -> b -> b) -> b -> UFloat a -> b Source #

foldl :: (b -> a -> b) -> b -> UFloat a -> b Source #

foldl' :: (b -> a -> b) -> b -> UFloat a -> b Source #

foldr1 :: (a -> a -> a) -> UFloat a -> a Source #

foldl1 :: (a -> a -> a) -> UFloat a -> a Source #

toList :: UFloat a -> [a] Source #

null :: UFloat a -> Bool Source #

length :: UFloat a -> Int Source #

elem :: Eq a => a -> UFloat a -> Bool Source #

maximum :: Ord a => UFloat a -> a Source #

minimum :: Ord a => UFloat a -> a Source #

sum :: Num a => UFloat a -> a Source #

product :: Num a => UFloat a -> a Source #

Traversable (UFloat :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UFloat a -> f (UFloat b) Source #

sequenceA :: Applicative f => UFloat (f a) -> f (UFloat a) Source #

mapM :: Monad m => (a -> m b) -> UFloat a -> m (UFloat b) Source #

sequence :: Monad m => UFloat (m a) -> m (UFloat a) Source #

Functor (URec Float :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b Source #

(<$) :: a -> URec Float b -> URec Float a Source #

Generic (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (URec Float p) 
Instance details

Defined in GHC.Internal.Generics

type Rep (URec Float p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: Type -> Type)))

Methods

from :: URec Float p -> Rep (URec Float p) x Source #

to :: Rep (URec Float p) x -> URec Float p Source #

Show (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

Eq (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Float p -> URec Float p -> Bool Source #

(/=) :: URec Float p -> URec Float p -> Bool Source #

Ord (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

data URec Float (p :: k) Source #

Used for marking occurrences of Float#

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

data URec Float (p :: k) = UFloat {}
type Rep1 (URec Float :: k -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Float :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: k -> Type)))
type Rep (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

type Rep (URec Float p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: Type -> Type)))

Conversion

integerToFloat# :: Integer -> Float# Source #

Convert an Integer to a Float#

naturalToFloat# :: Natural -> Float# Source #

Convert a Natural to a Float#

castWord32ToFloat :: Word32 -> Float Source #

castWord32ToFloat w does a bit-for-bit copy from an integral value to a floating-point value.

@since base-4.11.0.0

castFloatToWord32 :: Float -> Word32 Source #

castFloatToWord32 f does a bit-for-bit copy from a floating-point value to an integral value.

@since base-4.11.0.0

Operations

Predicate

Comparison

Arithmetic

Double

data Double Source #

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

Constructors

D# Double# 

Instances

Instances details
Data Double Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double Source #

toConstr :: Double -> Constr Source #

dataTypeOf :: Double -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) Source #

gmapT :: (forall b. Data b => b -> b) -> Double -> Double Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source #

Enum Double Source #

@since base-2.01

fromEnum just truncates its argument, beware of all sorts of overflows.

List generators have extremely peculiar behavior, mandated by Haskell Report 2010:

>>> [0..1.5]
[0.0,1.0,2.0]
Instance details

Defined in GHC.Internal.Float

Floating Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

RealFloat Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Storable Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.Storable

Num Double Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:

>>> (0.1 + 0.1) + 0.4 == 0.1 + (0.1 + 0.4)
False
>>> (0.1 + 0.2) * 0.3 == 0.1 * 0.3 + 0.2 * 0.3
False
>>> (0.1 * 0.1) * 0.3 == 0.1 * (0.1 * 0.3)
False
Instance details

Defined in GHC.Internal.Float

Read Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Fractional Double Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero.

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
>>> map (/ 0) [-1, 0, 1]
[-Infinity,NaN,Infinity]
>>> map (* 0) $ map (/ 0) [-1, 0, 1]
[NaN,NaN,NaN]
Instance details

Defined in GHC.Internal.Float

Real Double Source #

@since base-2.01

Beware that toRational generates garbage for non-finite arguments:

>>> toRational (1/0)
179769313 (and 300 more digits...) % 1
>>> toRational (0/0)
269653970 (and 300 more digits...) % 1
Instance details

Defined in GHC.Internal.Float

RealFrac Double Source #

@since base-2.01

Beware that results for non-finite arguments are garbage:

>>> [ f x | f <- [round, floor, ceiling], x <- [-1/0, 0/0, 1/0] ] :: [Int]
[0,0,0,0,0,0,0,0,0]
>>> map properFraction [-1/0, 0/0, 1/0] :: [(Int, Double)]
[(0,0.0),(0,0.0),(0,0.0)]

and get even more non-sensical if you ask for Integer instead of Int.

Instance details

Defined in GHC.Internal.Float

Show Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Eq Double

Note that due to the presence of NaN, Double's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Double)
False

Also note that Double's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
Instance details

Defined in GHC.Classes

Ord Double

IEEE 754 Double-precision type includes not only numbers, but also positive and negative infinities and a special element called NaN (which can be quiet or signal).

IEEE 754-2008, section 5.11 requires that if at least one of arguments of <=, <, >, >= is NaN then the result of the comparison is False, and instance Ord Double complies with this requirement. This violates the reflexivity: both NaN <= NaN and NaN >= NaN are False.

IEEE 754-2008, section 5.10 defines totalOrder predicate. Unfortunately, compare on Doubles violates the IEEE standard and does not define a total order. More specifically, both compare NaN x and compare x NaN always return GT.

Thus, users must be extremely cautious when using instance Ord Double. For instance, one should avoid ordered containers with keys represented by Double, because data loss and corruption may happen. An IEEE-compliant compare is available in fp-ieee package as TotallyOrdered newtype.

Moving further, the behaviour of min and max with regards to NaN is also non-compliant. IEEE 754-2008, section 5.3.1 defines that quiet NaN should be treated as a missing data by minNum and maxNum functions, for example, minNum(NaN, 1) = minNum(1, NaN) = 1. Some languages such as Java deviate from the standard implementing minNum(NaN, 1) = minNum(1, NaN) = NaN. However, min / max in base are even worse: min NaN 1 is 1, but min 1 NaN is NaN.

IEEE 754-2008 compliant min / max can be found in ieee754 package under minNum / maxNum names. Implementations compliant with minimumNumber / maximumNumber from a newer IEEE 754-2019, section 9.6 are available from fp-ieee package.

Instance details

Defined in GHC.Classes

Generic1 (URec Double :: k -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (URec Double :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Double :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: k -> Type)))

Methods

from1 :: forall (a :: k). URec Double a -> Rep1 (URec Double :: k -> Type) a Source #

to1 :: forall (a :: k). Rep1 (URec Double :: k -> Type) a -> URec Double a Source #

Foldable (UDouble :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => UDouble m -> m Source #

foldMap :: Monoid m => (a -> m) -> UDouble a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UDouble a -> m Source #

foldr :: (a -> b -> b) -> b -> UDouble a -> b Source #

foldr' :: (a -> b -> b) -> b -> UDouble a -> b Source #

foldl :: (b -> a -> b) -> b -> UDouble a -> b Source #

foldl' :: (b -> a -> b) -> b -> UDouble a -> b Source #

foldr1 :: (a -> a -> a) -> UDouble a -> a Source #

foldl1 :: (a -> a -> a) -> UDouble a -> a Source #

toList :: UDouble a -> [a] Source #

null :: UDouble a -> Bool Source #

length :: UDouble a -> Int Source #

elem :: Eq a => a -> UDouble a -> Bool Source #

maximum :: Ord a => UDouble a -> a Source #

minimum :: Ord a => UDouble a -> a Source #

sum :: Num a => UDouble a -> a Source #

product :: Num a => UDouble a -> a Source #

Traversable (UDouble :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UDouble a -> f (UDouble b) Source #

sequenceA :: Applicative f => UDouble (f a) -> f (UDouble a) Source #

mapM :: Monad m => (a -> m b) -> UDouble a -> m (UDouble b) Source #

sequence :: Monad m => UDouble (m a) -> m (UDouble a) Source #

Functor (URec Double :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b Source #

(<$) :: a -> URec Double b -> URec Double a Source #

Generic (URec Double p) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (URec Double p)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Double p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: Type -> Type)))

Methods

from :: URec Double p -> Rep (URec Double p) x Source #

to :: Rep (URec Double p) x -> URec Double p Source #

Show (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Double p -> URec Double p -> Bool Source #

(/=) :: URec Double p -> URec Double p -> Bool Source #

Ord (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

data URec Double (p :: k) Source #

Used for marking occurrences of Double#

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

data URec Double (p :: k) = UDouble {}
type Rep1 (URec Double :: k -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Double :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: k -> Type)))
type Rep (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Double p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: Type -> Type)))

Conversion

integerToDouble# :: Integer -> Double# Source #

Convert an Integer to a Double#

naturalToDouble# :: Natural -> Double# Source #

Encode a Natural (mantissa) into a Double#

castWord64ToDouble :: Word64 -> Double Source #

castWord64ToDouble w does a bit-for-bit copy from an integral value to a floating-point value.

@since base-4.11.0.0

castDoubleToWord64 :: Double -> Word64 Source #

castDoubleToWord64 f does a bit-for-bit copy from a floating-point value to an integral value.

@since base-4.11.0.0

Operations

Predicate

Comparison

Arithmetic

Formatting

showFloat :: RealFloat a => a -> ShowS Source #

Show a signed RealFloat value to full precision using standard decimal notation for arguments whose absolute value lies between 0.1 and 9,999,999, and scientific notation otherwise.

showSignedFloat Source #

Arguments

:: RealFloat a 
=> (a -> ShowS)

a function that can show unsigned values

-> Int

the precedence of the enclosing context

-> a

the value to show

-> ShowS 

Operations

log1mexpOrd :: (Ord a, Floating a) => a -> a Source #

Default implementation for log1mexp requiring Ord to test against a threshold to decide which implementation variant to use.

roundTo :: Int -> Int -> [Int] -> (Int, [Int]) Source #

floatToDigits :: RealFloat a => Integer -> a -> ([Int], Int) Source #

floatToDigits takes a base and a non-negative RealFloat number, and returns a list of digits and an exponent. In particular, if x>=0, and

floatToDigits base x = ([d1,d2,...,dn], e)

then

  1. n >= 1
  2. x = 0.d1d2...dn * (base**e)
  3. 0 <= di <= base-1

integerToBinaryFloat' :: RealFloat a => Integer -> a Source #

Converts a positive integer to a floating-point value.

The value nearest to the argument will be returned. If there are two such values, the one with an even significand will be returned (i.e. IEEE roundTiesToEven).

The argument must be strictly positive, and floatRadix (undefined :: a) must be 2.

fromRat :: RealFloat a => Rational -> a Source #

Converts a Rational value into any type in class RealFloat.

Monomorphic equality operators

See GHC.Classes#matching_overloaded_methods_in_rules

Internal

These may vanish in a future release

clamp :: Int -> Int -> Int Source #

Used to prevent exponent over/underflow when encoding floating point numbers. This is also the same as

\(x,y) -> max (-x) (min x y)

Example

Expand
>>> clamp (-10) 5
10

@since base-4.13.0.0

stgDoubleToWord64 :: Double# -> Word64# Source #

Deprecated: Use castDoubleToWord64# instead

stgFloatToWord32 :: Float# -> Word32# Source #

Deprecated: Use castFloatToWord32# instead

stgWord64ToDouble :: Word64# -> Double# Source #

Deprecated: Use castWord64ToDouble# instead

stgWord32ToFloat :: Word32# -> Float# Source #

Deprecated: Use castWord32ToFloat# instead

Orphan instances

Enum Double Source #

@since base-2.01

fromEnum just truncates its argument, beware of all sorts of overflows.

List generators have extremely peculiar behavior, mandated by Haskell Report 2010:

>>> [0..1.5]
[0.0,1.0,2.0]
Instance details

Enum Float Source #

@since base-2.01

fromEnum just truncates its argument, beware of all sorts of overflows.

List generators have extremely peculiar behavior, mandated by Haskell Report 2010:

>>> [0..1.5 :: Float]
[0.0,1.0,2.0]
Instance details

Num Double Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:

>>> (0.1 + 0.1) + 0.4 == 0.1 + (0.1 + 0.4)
False
>>> (0.1 + 0.2) * 0.3 == 0.1 * 0.3 + 0.2 * 0.3
False
>>> (0.1 * 0.1) * 0.3 == 0.1 * (0.1 * 0.3)
False
Instance details

Num Float Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:

>>> (0.1 + 0.1 :: Float) + 0.5 == 0.1 + (0.1 + 0.5)
False
>>> (0.1 + 0.2 :: Float) * 0.9 == 0.1 * 0.9 + 0.2 * 0.9
False
>>> (0.1 * 0.1 :: Float) * 0.9 == 0.1 * (0.1 * 0.9)
False
Instance details

Fractional Double Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero.

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
>>> map (/ 0) [-1, 0, 1]
[-Infinity,NaN,Infinity]
>>> map (* 0) $ map (/ 0) [-1, 0, 1]
[NaN,NaN,NaN]
Instance details

Fractional Float Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero.

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
>>> map (/ 0) [-1, 0, 1 :: Float]
[-Infinity,NaN,Infinity]
>>> map (* 0) $ map (/ 0) [-1, 0, 1 :: Float]
[NaN,NaN,NaN]
Instance details

Real Double Source #

@since base-2.01

Beware that toRational generates garbage for non-finite arguments:

>>> toRational (1/0)
179769313 (and 300 more digits...) % 1
>>> toRational (0/0)
269653970 (and 300 more digits...) % 1
Instance details

Real Float Source #

@since base-2.01

Beware that toRational generates garbage for non-finite arguments:

>>> toRational (1/0 :: Float)
340282366920938463463374607431768211456 % 1
>>> toRational (0/0 :: Float)
510423550381407695195061911147652317184 % 1
Instance details

RealFrac Double Source #

@since base-2.01

Beware that results for non-finite arguments are garbage:

>>> [ f x | f <- [round, floor, ceiling], x <- [-1/0, 0/0, 1/0] ] :: [Int]
[0,0,0,0,0,0,0,0,0]
>>> map properFraction [-1/0, 0/0, 1/0] :: [(Int, Double)]
[(0,0.0),(0,0.0),(0,0.0)]

and get even more non-sensical if you ask for Integer instead of Int.

Instance details

RealFrac Float Source #

@since base-2.01

Beware that results for non-finite arguments are garbage:

>>> [ f x | f <- [round, floor, ceiling], x <- [-1/0, 0/0, 1/0 :: Float] ] :: [Int]
[0,0,0,0,0,0,0,0,0]
>>> map properFraction [-1/0, 0/0, 1/0] :: [(Int, Float)]
[(0,0.0),(0,0.0),(0,0.0)]

and get even more non-sensical if you ask for Integer instead of Int.

Instance details

Methods

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

truncate :: Integral b => Float -> b Source #

round :: Integral b => Float -> b Source #

ceiling :: Integral b => Float -> b Source #

floor :: Integral b => Float -> b Source #

Show Double Source #

@since base-2.01

Instance details

Show Float Source #

@since base-2.01

Instance details