| Copyright | (c) The University of Glasgow 1994-2002 | 
|---|---|
| License | see libraries/base/LICENSE | 
| Maintainer | ghc-devs@haskell.org | 
| Stability | internal | 
| Portability | non-portable (GHC Extensions) | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
GHC.Real
Synopsis
- class (Num a, Ord a) => Real a where- toRational :: a -> Rational
 
- class (Real a, Enum a) => Integral a where
- class Num a => Fractional a where- (/) :: a -> a -> a
- recip :: a -> a
- fromRational :: Rational -> a
 
- class (Real a, Fractional a) => RealFrac a where
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- showSigned :: Real a => (a -> ShowS) -> Int -> a -> ShowS
- even :: Integral a => a -> Bool
- odd :: Integral a => a -> Bool
- (^) :: (Num a, Integral b) => a -> b -> a
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- gcd :: Integral a => a -> a -> a
- lcm :: Integral a => a -> a -> a
- data Ratio a = !a :% !a
- type Rational = Ratio Integer
- infinity :: Rational
- notANumber :: Rational
- numericEnumFrom :: Fractional a => a -> [a]
- numericEnumFromThen :: Fractional a => a -> a -> [a]
- numericEnumFromTo :: (Ord a, Fractional a) => a -> a -> [a]
- numericEnumFromThenTo :: (Ord a, Fractional a) => a -> a -> a -> [a]
- integralEnumFrom :: (Integral a, Bounded a) => a -> [a]
- integralEnumFromThen :: (Integral a, Bounded a) => a -> a -> [a]
- integralEnumFromTo :: Integral a => a -> a -> [a]
- integralEnumFromThenTo :: Integral a => a -> a -> a -> [a]
- (%) :: Integral a => a -> a -> Ratio a
- numerator :: Ratio a -> a
- denominator :: Ratio a -> a
- reduce :: Integral a => a -> a -> Ratio a
- ratioPrec :: Int
- ratioPrec1 :: Int
- divZeroError :: a
- ratioZeroDenominatorError :: a
- overflowError :: a
- underflowError :: a
- mkRationalBase2 :: Rational -> Integer -> Rational
- mkRationalBase10 :: Rational -> Integer -> Rational
- data FractionalExponentBase
- (^%^) :: Integral a => Rational -> a -> Rational
- (^^%^^) :: Integral a => Rational -> a -> Rational
- mkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> Rational
- powImpl :: (Num a, Integral b) => a -> b -> a
- powImplAcc :: (Num a, Integral b) => a -> b -> a -> a
Classes
class (Num a, Ord a) => Real a where Source #
Real numbers.
The Haskell report defines no laws for Real, however Real instances
 are customarily expected to adhere to the following law:
- Coherence with fromRational
- if the type also implements Fractional, thenfromRationalis a left inverse fortoRational, i.e.fromRational (toRational i) = i
The law does not hold for Float, Double, CFloat,
 CDouble, etc., because these types contain non-finite values,
 which cannot be roundtripped through Rational.
Methods
toRational :: a -> Rational Source #
Rational equivalent of its real argument with full precision.
Instances
class (Real a, Enum a) => Integral a where Source #
Integral numbers, supporting integer division.
The Haskell Report defines no laws for Integral. However, Integral
 instances are customarily expected to define a Euclidean domain and have the
 following properties for the div/mod and quot/rem pairs, given
 suitable Euclidean functions f and g:
- x=- y * quot x y + rem x ywith- rem x y=- fromInteger 0or- g (rem x y)<- g y
- x=- y * div x y + mod x ywith- mod x y=- fromInteger 0or- f (mod x y)<- f y
An example of a suitable Euclidean function, for Integer's instance, is
 abs.
In addition, toInteger should be total, and fromInteger should be a left
 inverse for it, i.e. fromInteger (toInteger i) = i.
Methods
quot :: a -> a -> a infixl 7 Source #
Integer division truncated toward zero.
WARNING: This function is partial (because it throws when 0 is passed as
 the divisor) for all the integer types in base.
rem :: a -> a -> a infixl 7 Source #
Integer remainder, satisfying
(x `quot` y)*y + (x `rem` y) == x
WARNING: This function is partial (because it throws when 0 is passed as
 the divisor) for all the integer types in base.
div :: a -> a -> a infixl 7 Source #
Integer division truncated toward negative infinity.
WARNING: This function is partial (because it throws when 0 is passed as
 the divisor) for all the integer types in base.
mod :: a -> a -> a infixl 7 Source #
Integer modulus, satisfying
(x `div` y)*y + (x `mod` y) == x
WARNING: This function is partial (because it throws when 0 is passed as
 the divisor) for all the integer types in base.
quotRem :: a -> a -> (a, a) Source #
WARNING: This function is partial (because it throws when 0 is passed as
 the divisor) for all the integer types in base.
divMod :: a -> a -> (a, a) Source #
WARNING: This function is partial (because it throws when 0 is passed as
 the divisor) for all the integer types in base.
toInteger :: a -> Integer Source #
Conversion to Integer.
Instances
class Num a => Fractional a where Source #
Fractional numbers, supporting real division.
The Haskell Report defines no laws for Fractional. However, ( and
 +)( are customarily expected to define a division ring and have the
 following properties:*)
- recipgives the multiplicative inverse
- x * recip x=- recip x * x=- fromInteger 1
- Totality of toRational
- toRationalis total
- Coherence with toRational
- if the type also implements Real, thenfromRationalis a left inverse fortoRational, i.e.fromRational (toRational i) = i
Note that it isn't customarily expected that a type instance of
 Fractional implement a field. However, all instances in base do.
Minimal complete definition
fromRational, (recip | (/))
Methods
(/) :: a -> a -> a infixl 7 Source #
Fractional division.
Reciprocal fraction.
fromRational :: Rational -> a Source #
Conversion from a Rational (that is Ratio IntegerfromRational
 to a value of type Rational, so such literals have type
 (.Fractional a) => a
Instances
| Fractional CDouble | |
| Fractional CFloat | |
| RealFloat a => Fractional (Complex a) Source # | Since: base-2.1 | 
| Fractional a => Fractional (Identity a) | @since base-4.9.0.0 | 
| Fractional a => Fractional (Down a) | @since base-4.14.0.0 | 
| Integral a => Fractional (Ratio a) | @since base-2.0.1 | 
| HasResolution a => Fractional (Fixed a) Source # | Since: base-2.1 | 
| Fractional a => Fractional (Op a b) Source # | |
| Fractional a => Fractional (Const a b) | @since base-4.9.0.0 | 
| Fractional (f (g a)) => Fractional (Compose f g a) Source # | Since: base-4.20.0.0 | 
class (Real a, Fractional a) => RealFrac a where Source #
Extracting components of fractions.
Minimal complete definition
Methods
properFraction :: Integral b => a -> (b, a) Source #
The function properFraction takes a real fractional number x
 and returns a pair (n,f) such that x = n+f, and:
- nis an integral number with the same sign as- x; and
- fis a fraction with the same type and sign as- x, and with absolute value less than- 1.
The default definitions of the ceiling, floor, truncate
 and round functions are in terms of properFraction.
truncate :: Integral b => a -> b Source #
truncate xx between zero and x
round :: Integral b => a -> b Source #
round xx;
   the even integer if x is equidistant between two integers
ceiling :: Integral b => a -> b Source #
ceiling xx
floor :: Integral b => a -> b Source #
floor xx
Instances
| RealFrac CDouble | |
| RealFrac CFloat | |
| RealFrac a => RealFrac (Identity a) | @since base-4.9.0.0 | 
| Defined in GHC.Internal.Data.Functor.Identity | |
| RealFrac a => RealFrac (Down a) | @since base-4.14.0.0 | 
| Integral a => RealFrac (Ratio a) | @since base-2.0.1 | 
| HasResolution a => RealFrac (Fixed a) Source # | Since: base-2.1 | 
| RealFrac a => RealFrac (Const a b) | @since base-4.9.0.0 | 
| Defined in GHC.Internal.Data.Functor.Const | |
| RealFrac (f (g a)) => RealFrac (Compose f g a) Source # | Since: base-4.20.0.0 | 
| Defined in Data.Functor.Compose | |
Conversion
fromIntegral :: (Integral a, Num b) => a -> b Source #
General coercion from Integral types.
WARNING: This function performs silent truncation if the result type is not at least as big as the argument's type.
realToFrac :: (Real a, Fractional b) => a -> b Source #
General coercion to Fractional types.
WARNING: This function goes through the Rational type, which does not have values for NaN for example.
 This means it does not round-trip.
For Double it also behaves differently with or without -O0:
Prelude> realToFrac nan -- With -O0 -Infinity Prelude> realToFrac nan NaN
Formatting
Arguments
| :: Real a | |
| => (a -> ShowS) | a function that can show unsigned values | 
| -> Int | the precedence of the enclosing context | 
| -> a | the value to show | 
| -> ShowS | 
Converts a possibly-negative Real value to a string.
Predicates
Arithmetic
(^) :: (Num a, Integral b) => a -> b -> a infixr 8 Source #
raise a number to a non-negative integral power
(^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 Source #
raise a number to an integral power
gcd :: Integral a => a -> a -> a Source #
gcd x yx and y of which
 every common factor of x and y is also a factor; for example
 gcd 4 2 = 2gcd (-4) 6 = 2gcd 0 44. gcd 0 00.
 (That is, the common divisor that is "greatest" in the divisibility
 preordering.)
Note: Since for signed fixed-width integer types, abs minBound < 0minBound0 or minBound
lcm :: Integral a => a -> a -> a Source #
lcm x yx and y divide.
Ratio
Rational numbers, with numerator and denominator of some Integral type.
Note that Ratio's instances inherit the deficiencies from the type
 parameter's. For example, Ratio Natural's Num instance has similar
 problems to Natural's.
Constructors
| !a :% !a | 
Instances
| (Data a, Integral a) => Data (Ratio a) | @since base-4.0.0.0 | 
| Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ratio a -> c (Ratio a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ratio a) Source # toConstr :: Ratio a -> Constr Source # dataTypeOf :: Ratio a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ratio a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ratio a)) Source # gmapT :: (forall b. Data b => b -> b) -> Ratio a -> Ratio a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ratio a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ratio a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ratio a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ratio a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) Source # | |
| Integral a => Enum (Ratio a) | @since base-2.0.1 | 
| Defined in GHC.Internal.Real Methods succ :: Ratio a -> Ratio a Source # pred :: Ratio a -> Ratio a Source # toEnum :: Int -> Ratio a Source # fromEnum :: Ratio a -> Int Source # enumFrom :: Ratio a -> [Ratio a] Source # enumFromThen :: Ratio a -> Ratio a -> [Ratio a] Source # enumFromTo :: Ratio a -> Ratio a -> [Ratio a] Source # enumFromThenTo :: Ratio a -> Ratio a -> Ratio a -> [Ratio a] Source # | |
| (Storable a, Integral a) => Storable (Ratio a) | @since base-4.8.0.0 | 
| Defined in GHC.Internal.Foreign.Storable Methods sizeOf :: Ratio a -> Int Source # alignment :: Ratio a -> Int Source # peekElemOff :: Ptr (Ratio a) -> Int -> IO (Ratio a) Source # pokeElemOff :: Ptr (Ratio a) -> Int -> Ratio a -> IO () Source # peekByteOff :: Ptr b -> Int -> IO (Ratio a) Source # pokeByteOff :: Ptr b -> Int -> Ratio a -> IO () Source # | |
| Integral a => Num (Ratio a) | @since base-2.0.1 | 
| Defined in GHC.Internal.Real | |
| (Integral a, Read a) => Read (Ratio a) | @since base-2.01 | 
| Integral a => Fractional (Ratio a) | @since base-2.0.1 | 
| Integral a => Real (Ratio a) | @since base-2.0.1 | 
| Defined in GHC.Internal.Real Methods toRational :: Ratio a -> Rational Source # | |
| Integral a => RealFrac (Ratio a) | @since base-2.0.1 | 
| Show a => Show (Ratio a) | @since base-2.0.1 | 
| Eq a => Eq (Ratio a) | @since base-2.01 | 
| Integral a => Ord (Ratio a) | @since base-2.0.1 | 
| Defined in GHC.Internal.Real | |
Enum helpers
numericEnumFrom :: Fractional a => a -> [a] Source #
numericEnumFromThen :: Fractional a => a -> a -> [a] Source #
numericEnumFromTo :: (Ord a, Fractional a) => a -> a -> [a] Source #
numericEnumFromThenTo :: (Ord a, Fractional a) => a -> a -> a -> [a] Source #
integralEnumFrom :: (Integral a, Bounded a) => a -> [a] Source #
integralEnumFromThen :: (Integral a, Bounded a) => a -> a -> [a] Source #
integralEnumFromTo :: Integral a => a -> a -> [a] Source #
integralEnumFromThenTo :: Integral a => a -> a -> a -> [a] Source #
Construction
Projection
numerator :: Ratio a -> a Source #
Extract the numerator of the ratio in reduced form: the numerator and denominator have no common factor and the denominator is positive.
denominator :: Ratio a -> a Source #
Extract the denominator of the ratio in reduced form: the numerator and denominator have no common factor and the denominator is positive.
Operations
reduce :: Integral a => a -> a -> Ratio a Source #
reduce is a subsidiary function used only in this module.
 It normalises a ratio by dividing both numerator and denominator by
 their greatest common divisor.
Internal
ratioPrec1 :: Int Source #
divZeroError :: a Source #
overflowError :: a Source #
underflowError :: a Source #
data FractionalExponentBase Source #
Instances
| Show FractionalExponentBase | |
| Defined in GHC.Internal.Real | |
powImplAcc :: (Num a, Integral b) => a -> b -> a -> a Source #