base-4.20.0.0: Core data structures and operations
Copyright(c) The University of Glasgow 1994-2002
Licensesee libraries/base/LICENSE
Maintainerghc-devs@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC Extensions)
Safe HaskellSafe
LanguageHaskell2010

GHC.Real

Description

The types Ratio and Rational, and the classes Real, Fractional, Integral, and RealFrac.

Synopsis

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, then fromRational is a left inverse for toRational, 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

Instances details
Real CBool 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CClock 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CDouble 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CFloat 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CInt 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CIntMax 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CIntPtr 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CLLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CPtrdiff 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CSChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CSUSeconds 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CShort 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CSigAtomic 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CSize 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CTime 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CUChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CUInt 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CUIntMax 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CUIntPtr 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CULLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CULong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CUSeconds 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CUShort 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real CWchar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Real IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Real WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Real Int16

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Real Int32

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Real Int64

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Real Int8

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Real CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CNlink 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real Word16

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Real Word32

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Real Word64

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Real Word8

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Real Integer

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Real Natural

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Real

Real Int

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Real Word

@since base-2.01

Instance details

Defined in GHC.Internal.Real

Real a => Real (Identity a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Real a => Real (Down a)

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Integral a => Real (Ratio a)

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

HasResolution a => Real (Fixed a) Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Real a => Real (Const a b)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

toRational :: Const a b -> Rational Source #

Real (f (g a)) => Real (Compose f g a) Source #

Since: base-4.19.0.0

Instance details

Defined in Data.Functor.Compose

Methods

toRational :: Compose f g a -> Rational Source #

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 y with rem x y = fromInteger 0 or g (rem x y) < g y
  • x = y * div x y + mod x y with mod x y = fromInteger 0 or 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.

Minimal complete definition

quotRem, toInteger

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 #

Simultaneous quot and rem.

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 #

simultaneous div and mod.

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

Instances details
Integral CBool 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CInt 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CIntMax 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CIntPtr 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CLLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CPtrdiff 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CSChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CShort 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CSigAtomic 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CSize 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CUChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CUInt 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CUIntMax 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CUIntPtr 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CULLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CULong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CUShort 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral CWchar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Integral IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Integral WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Integral Int16

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Integral Int32

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Integral Int64

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Integral Int8

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Integral CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CId -> CId -> CId Source #

rem :: CId -> CId -> CId Source #

div :: CId -> CId -> CId Source #

mod :: CId -> CId -> CId Source #

quotRem :: CId -> CId -> (CId, CId) Source #

divMod :: CId -> CId -> (CId, CId) Source #

toInteger :: CId -> Integer Source #

Integral CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CNlink 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Integral Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: Fd -> Fd -> Fd Source #

rem :: Fd -> Fd -> Fd Source #

div :: Fd -> Fd -> Fd Source #

mod :: Fd -> Fd -> Fd Source #

quotRem :: Fd -> Fd -> (Fd, Fd) Source #

divMod :: Fd -> Fd -> (Fd, Fd) Source #

toInteger :: Fd -> Integer Source #

Integral Word16

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Integral Word32

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Integral Word64

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Integral Word8

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Integral Integer

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Integral Natural

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Real

Integral Int

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

quot :: Int -> Int -> Int Source #

rem :: Int -> Int -> Int Source #

div :: Int -> Int -> Int Source #

mod :: Int -> Int -> Int Source #

quotRem :: Int -> Int -> (Int, Int) Source #

divMod :: Int -> Int -> (Int, Int) Source #

toInteger :: Int -> Integer Source #

Integral Word

@since base-2.01

Instance details

Defined in GHC.Internal.Real

Integral a => Integral (Identity a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Integral a => Integral (Const a b)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

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

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

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

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

quotRem :: Const a b -> Const a b -> (Const a b, Const a b) Source #

divMod :: Const a b -> Const a b -> (Const a b, Const a b) Source #

toInteger :: Const a b -> Integer Source #

Integral (f (g a)) => Integral (Compose f g a) Source #

Since: base-4.19.0.0

Instance details

Defined in Data.Functor.Compose

Methods

quot :: Compose f g a -> Compose f g a -> Compose f g a Source #

rem :: Compose f g a -> Compose f g a -> Compose f g a Source #

div :: Compose f g a -> Compose f g a -> Compose f g a Source #

mod :: Compose f g a -> Compose f g a -> Compose f g a Source #

quotRem :: Compose f g a -> Compose f g a -> (Compose f g a, Compose f g a) Source #

divMod :: Compose f g a -> Compose f g a -> (Compose f g a, Compose f g a) Source #

toInteger :: Compose f g a -> Integer Source #

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:

recip gives the multiplicative inverse
x * recip x = recip x * x = fromInteger 1
Totality of toRational
toRational is total
Coherence with toRational
if the type also implements Real, then fromRational is a left inverse for toRational, 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.

recip :: a -> a Source #

Reciprocal fraction.

fromRational :: Rational -> a Source #

Conversion from a Rational (that is Ratio Integer). A floating literal stands for an application of fromRational to a value of type Rational, so such literals have type (Fractional a) => a.

Instances

Instances details
Fractional CDouble 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Fractional CFloat 
Instance details

Defined in GHC.Internal.Foreign.C.Types

RealFloat a => Fractional (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Fractional a => Fractional (Identity a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Fractional a => Fractional (Down a)

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

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

recip :: Down a -> Down a Source #

fromRational :: Rational -> Down a Source #

Integral a => Fractional (Ratio a)

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

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

recip :: Ratio a -> Ratio a Source #

fromRational :: Rational -> Ratio a Source #

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 #

Fractional a => Fractional (Op a b) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

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

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

fromRational :: Rational -> Op a b Source #

Fractional a => Fractional (Const a b)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

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

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

fromRational :: Rational -> Const a b Source #

Fractional (f (g a)) => Fractional (Compose f g a) Source #

Since: base-4.20.0.0

Instance details

Defined in Data.Functor.Compose

Methods

(/) :: Compose f g a -> Compose f g a -> Compose f g a Source #

recip :: Compose f g a -> Compose f g a Source #

fromRational :: Rational -> Compose f g a Source #

class (Real a, Fractional a) => RealFrac a where Source #

Extracting components of fractions.

Minimal complete definition

properFraction

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:

  • n is an integral number with the same sign as x; and
  • f is 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 x returns the integer nearest x between zero and x

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

round x returns the nearest integer to x; the even integer if x is equidistant between two integers

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

ceiling x returns the least integer not less than x

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

floor x returns the greatest integer not greater than x

Instances

Instances details
RealFrac CDouble 
Instance details

Defined in GHC.Internal.Foreign.C.Types

RealFrac CFloat 
Instance details

Defined in GHC.Internal.Foreign.C.Types

RealFrac a => RealFrac (Identity a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Methods

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

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

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

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

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

RealFrac a => RealFrac (Down a)

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

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

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

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

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

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

Integral a => RealFrac (Ratio a)

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

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

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

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

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

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

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 #

RealFrac a => RealFrac (Const a b)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

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

truncate :: Integral b0 => Const a b -> b0 Source #

round :: Integral b0 => Const a b -> b0 Source #

ceiling :: Integral b0 => Const a b -> b0 Source #

floor :: Integral b0 => Const a b -> b0 Source #

RealFrac (f (g a)) => RealFrac (Compose f g a) Source #

Since: base-4.20.0.0

Instance details

Defined in Data.Functor.Compose

Methods

properFraction :: Integral b => Compose f g a -> (b, Compose f g a) Source #

truncate :: Integral b => Compose f g a -> b Source #

round :: Integral b => Compose f g a -> b Source #

ceiling :: Integral b => Compose f g a -> b Source #

floor :: Integral b => Compose f g a -> b Source #

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

showSigned Source #

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

even :: Integral a => a -> Bool Source #

odd :: Integral a => a -> Bool Source #

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 y is the non-negative factor of both x and y of which every common factor of x and y is also a factor; for example gcd 4 2 = 2, gcd (-4) 6 = 2, gcd 0 4 = 4. gcd 0 0 = 0. (That is, the common divisor that is "greatest" in the divisibility preordering.)

Note: Since for signed fixed-width integer types, abs minBound < 0, the result may be negative if one of the arguments is minBound (and necessarily is if the other is 0 or minBound) for such types.

lcm :: Integral a => a -> a -> a Source #

lcm x y is the smallest positive integer that both x and y divide.

Ratio

data Ratio a Source #

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

Instances details
(Data a, Integral a) => Data (Ratio a)

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

Instance details

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

Instance details

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 #

peek :: Ptr (Ratio a) -> IO (Ratio a) Source #

poke :: Ptr (Ratio a) -> Ratio a -> IO () Source #

Integral a => Num (Ratio a)

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

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

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

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

negate :: Ratio a -> Ratio a Source #

abs :: Ratio a -> Ratio a Source #

signum :: Ratio a -> Ratio a Source #

fromInteger :: Integer -> Ratio a Source #

(Integral a, Read a) => Read (Ratio a)

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Integral a => Fractional (Ratio a)

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

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

recip :: Ratio a -> Ratio a Source #

fromRational :: Rational -> Ratio a Source #

Integral a => Real (Ratio a)

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Integral a => RealFrac (Ratio a)

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

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

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

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

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

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

Show a => Show (Ratio a)

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Eq a => Eq (Ratio a)

@since base-2.01

Instance details

Defined in GHC.Internal.Real

Methods

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

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

Integral a => Ord (Ratio a)

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

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

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

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

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

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

max :: Ratio a -> Ratio a -> Ratio a Source #

min :: Ratio a -> Ratio a -> Ratio a Source #

type Rational = Ratio Integer Source #

Arbitrary-precision rational numbers, represented as a ratio of two Integer values. A rational number may be constructed using the % operator.

Enum helpers

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

(%) :: Integral a => a -> a -> Ratio a infixl 7 Source #

Forms the ratio of two integral numbers.

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

powImpl :: (Num a, Integral b) => a -> b -> a Source #

powImplAcc :: (Num a, Integral b) => a -> b -> a -> a Source #