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

GHC.Float

Description

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

Synopsis

Documentation

integerToFloat# :: Integer -> Float# Source #

Convert an Integer to a Float#

integerToDouble# :: Integer -> Double# Source #

Convert an Integer to a Double#

naturalToFloat# :: Natural -> Float# Source #

Convert a Natural to a Float#

naturalToDouble# :: Natural -> Double# Source #

Encode a Natural (mantissa) into a Double#

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 Foreign.C.Types

Floating CFloat Source # 
Instance details

Defined in Foreign.C.Types

Floating Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Floating Float Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFloat a => Floating (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Floating a => Floating (Identity a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Floating a => Floating (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in 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 (Op a b) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

pi :: Op a b Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in 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 Foreign.C.Types

RealFloat CFloat Source # 
Instance details

Defined in Foreign.C.Types

RealFloat Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFloat Float Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFloat a => RealFloat (Identity a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

RealFloat a => RealFloat (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

castDoubleToWord64 :: Double -> Word64 Source #

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

Since: base-4.10.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.10.0.0

castWord32ToFloat :: Word32 -> Float Source #

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

Since: base-4.10.0.0

castWord64ToDouble :: Word64 -> Double Source #

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

Since: base-4.10.0.0

clamp :: 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

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

Converts a Rational value into any type in class RealFloat.

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.

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 #

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 

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

Storable Float Source #

Since: base-2.1

Instance details

Defined in Foreign.Storable

Enum Float Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Floating Float Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFloat Float Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Num Float Source #

Note that due to the presence of NaN, not all elements of Float have an additive inverse.

>>> 0/0 + (negate 0/0 :: Float)
NaN

Also note that due to the presence of -0, Float's Num instance doesn't have an additive identity

>>> 0 + (-0 :: Float)
0.0

Since: base-2.1

Instance details

Defined in GHC.Float

Read Float Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Fractional Float Source #

Note that due to the presence of NaN, not all elements of Float have an multiplicative inverse.

>>> 0/0 * (recip 0/0 :: Float)
NaN

Since: base-2.1

Instance details

Defined in GHC.Float

Real Float Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFrac Float Source #

Since: base-2.1

Instance details

Defined in GHC.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.1

Instance details

Defined in GHC.Float

PrintfArg Float Source #

Since: base-2.1

Instance details

Defined in Text.Printf

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

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

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

Also note that, due to the same, Ord's operator interactions are not respected by Float's instance:

>>> (0/0 :: Float) > 1
False
>>> compare (0/0 :: Float) 1
GT
Instance details

Defined in GHC.Classes

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Since: base-4.9.0.0

Instance details

Defined in 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 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 LiftedRep -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.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.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type Source #

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

Eq (URec Float p) Source # 
Instance details

Defined in GHC.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.Generics

data URec Float (p :: k) Source #

Used for marking occurrences of Float#

Since: base-4.9.0.0

Instance details

Defined in GHC.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.Generics

type Rep1 (URec Float :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" '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.Generics

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

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

Storable Double Source #

Since: base-2.1

Instance details

Defined in Foreign.Storable

Enum Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Floating Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFloat Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Num Double Source #

Note that due to the presence of NaN, not all elements of Double have an additive inverse.

>>> 0/0 + (negate 0/0 :: Double)
NaN

Also note that due to the presence of -0, Double's Num instance doesn't have an additive identity

>>> 0 + (-0 :: Double)
0.0

Since: base-2.1

Instance details

Defined in GHC.Float

Read Double Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Fractional Double Source #

Note that due to the presence of NaN, not all elements of Double have an multiplicative inverse.

>>> 0/0 * (recip 0/0 :: Double)
NaN

Since: base-2.1

Instance details

Defined in GHC.Float

Real Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFrac Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Show Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

PrintfArg Double Source #

Since: base-2.1

Instance details

Defined in Text.Printf

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

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

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

Also note that, due to the same, Ord's operator interactions are not respected by Double's instance:

>>> (0/0 :: Double) > 1
False
>>> compare (0/0 :: Double) 1
GT
Instance details

Defined in GHC.Classes

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Since: base-4.9.0.0

Instance details

Defined in 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 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 LiftedRep -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.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.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type Source #

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

Eq (URec Double p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.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.Generics

data URec Double (p :: k) Source #

Used for marking occurrences of Double#

Since: base-4.9.0.0

Instance details

Defined in GHC.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.Generics

type Rep1 (URec Double :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" '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.Generics

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

Monomorphic equality operators

See GHC.Classes#matching_overloaded_methods_in_rules

Orphan instances

Enum Double Source #

Since: base-2.1

Instance details

Enum Float Source #

Since: base-2.1

Instance details

Num Double Source #

Note that due to the presence of NaN, not all elements of Double have an additive inverse.

>>> 0/0 + (negate 0/0 :: Double)
NaN

Also note that due to the presence of -0, Double's Num instance doesn't have an additive identity

>>> 0 + (-0 :: Double)
0.0

Since: base-2.1

Instance details

Num Float Source #

Note that due to the presence of NaN, not all elements of Float have an additive inverse.

>>> 0/0 + (negate 0/0 :: Float)
NaN

Also note that due to the presence of -0, Float's Num instance doesn't have an additive identity

>>> 0 + (-0 :: Float)
0.0

Since: base-2.1

Instance details

Fractional Double Source #

Note that due to the presence of NaN, not all elements of Double have an multiplicative inverse.

>>> 0/0 * (recip 0/0 :: Double)
NaN

Since: base-2.1

Instance details

Fractional Float Source #

Note that due to the presence of NaN, not all elements of Float have an multiplicative inverse.

>>> 0/0 * (recip 0/0 :: Float)
NaN

Since: base-2.1

Instance details

Real Double Source #

Since: base-2.1

Instance details

Real Float Source #

Since: base-2.1

Instance details

RealFrac Double Source #

Since: base-2.1

Instance details

RealFrac Float Source #

Since: base-2.1

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

Instance details

Show Float Source #

Since: base-2.1

Instance details