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

GHC.Real

Description

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

Synopsis

Documentation

data Ratio a #

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
Integral a => Enum (Ratio a) #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

succ :: Ratio a -> Ratio a #

pred :: Ratio a -> Ratio a #

toEnum :: Int -> Ratio a #

fromEnum :: Ratio a -> Int #

enumFrom :: Ratio a -> [Ratio a] #

enumFromThen :: Ratio a -> Ratio a -> [Ratio a] #

enumFromTo :: Ratio a -> Ratio a -> [Ratio a] #

enumFromThenTo :: Ratio a -> Ratio a -> Ratio a -> [Ratio a] #

Eq a => Eq (Ratio a) #

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

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

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

Integral a => Fractional (Ratio a) #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

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

recip :: Ratio a -> Ratio a #

fromRational :: Rational -> Ratio a #

(Data a, Integral a) => Data (Ratio a) #

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) -> Ratio a -> c (Ratio a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ratio a) #

toConstr :: Ratio a -> Constr #

dataTypeOf :: Ratio a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Ratio a -> Ratio a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ratio a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ratio a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ratio a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ratio a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) #

Integral a => Num (Ratio a) #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

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

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

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

negate :: Ratio a -> Ratio a #

abs :: Ratio a -> Ratio a #

signum :: Ratio a -> Ratio a #

fromInteger :: Integer -> Ratio a #

Integral a => Ord (Ratio a) #

Since: base-2.0.1

Instance details

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

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

Since: base-2.1

Instance details

Defined in GHC.Read

Integral a => Real (Ratio a) #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

toRational :: Ratio a -> Rational #

Integral a => RealFrac (Ratio a) #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

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

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

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

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

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

Show a => Show (Ratio a) #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

showsPrec :: Int -> Ratio a -> ShowS #

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

(Storable a, Integral a) => Storable (Ratio a) #

Since: base-4.8.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ratio a -> Int #

alignment :: Ratio a -> Int #

peekElemOff :: Ptr (Ratio a) -> Int -> IO (Ratio a) #

pokeElemOff :: Ptr (Ratio a) -> Int -> Ratio a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ratio a) #

pokeByteOff :: Ptr b -> Int -> Ratio a -> IO () #

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

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

type Rational = Ratio Integer #

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

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

Forms the ratio of two integral numbers.

numerator :: Ratio a -> a #

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 #

Extract the denominator of the ratio in reduced form: the numerator and denominator have no common factor and the denominator is positive.

reduce :: Integral a => a -> a -> Ratio a #

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.

class (Num a, Ord a) => Real a where #

Methods

toRational :: a -> Rational #

the rational equivalent of its real argument with full precision

Instances

Instances details
Real Double #

Since: base-2.1

Instance details

Defined in GHC.Float

Real Float #

Since: base-2.1

Instance details

Defined in GHC.Float

Methods

toRational :: Float -> Rational #

Real Int #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

toRational :: Int -> Rational #

Real Int8 #

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int8 -> Rational #

Real Int16 #

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int16 -> Rational #

Real Int32 #

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int32 -> Rational #

Real Int64 #

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int64 -> Rational #

Real Integer #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Real Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Real Word #

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

toRational :: Word -> Rational #

Real Word8 #

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

toRational :: Word8 -> Rational #

Real Word16 #

Since: base-2.1

Instance details

Defined in GHC.Word

Real Word32 #

Since: base-2.1

Instance details

Defined in GHC.Word

Real Word64 #

Since: base-2.1

Instance details

Defined in GHC.Word

Real IntPtr # 
Instance details

Defined in Foreign.Ptr

Real WordPtr # 
Instance details

Defined in Foreign.Ptr

Real CUIntMax # 
Instance details

Defined in Foreign.C.Types

Real CIntMax # 
Instance details

Defined in Foreign.C.Types

Real CUIntPtr # 
Instance details

Defined in Foreign.C.Types

Real CIntPtr # 
Instance details

Defined in Foreign.C.Types

Real CSUSeconds # 
Instance details

Defined in Foreign.C.Types

Real CUSeconds # 
Instance details

Defined in Foreign.C.Types

Real CTime # 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CTime -> Rational #

Real CClock # 
Instance details

Defined in Foreign.C.Types

Real CSigAtomic # 
Instance details

Defined in Foreign.C.Types

Real CWchar # 
Instance details

Defined in Foreign.C.Types

Real CSize # 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CSize -> Rational #

Real CPtrdiff # 
Instance details

Defined in Foreign.C.Types

Real CDouble # 
Instance details

Defined in Foreign.C.Types

Real CFloat # 
Instance details

Defined in Foreign.C.Types

Real CBool # 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CBool -> Rational #

Real CULLong # 
Instance details

Defined in Foreign.C.Types

Real CLLong # 
Instance details

Defined in Foreign.C.Types

Real CULong # 
Instance details

Defined in Foreign.C.Types

Real CLong # 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CLong -> Rational #

Real CUInt # 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CUInt -> Rational #

Real CInt # 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CInt -> Rational #

Real CUShort # 
Instance details

Defined in Foreign.C.Types

Real CShort # 
Instance details

Defined in Foreign.C.Types

Real CUChar # 
Instance details

Defined in Foreign.C.Types

Real CSChar # 
Instance details

Defined in Foreign.C.Types

Real CChar # 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CChar -> Rational #

Real Fd # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: Fd -> Rational #

Real CNfds # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CNfds -> Rational #

Real CSocklen # 
Instance details

Defined in System.Posix.Types

Real CKey # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CKey -> Rational #

Real CId # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CId -> Rational #

Real CFsFilCnt # 
Instance details

Defined in System.Posix.Types

Real CFsBlkCnt # 
Instance details

Defined in System.Posix.Types

Real CClockId # 
Instance details

Defined in System.Posix.Types

Real CBlkCnt # 
Instance details

Defined in System.Posix.Types

Real CBlkSize # 
Instance details

Defined in System.Posix.Types

Real CRLim # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CRLim -> Rational #

Real CTcflag # 
Instance details

Defined in System.Posix.Types

Real CSpeed # 
Instance details

Defined in System.Posix.Types

Real CCc # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CCc -> Rational #

Real CUid # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CUid -> Rational #

Real CNlink # 
Instance details

Defined in System.Posix.Types

Real CGid # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CGid -> Rational #

Real CSsize # 
Instance details

Defined in System.Posix.Types

Real CPid # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CPid -> Rational #

Real COff # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: COff -> Rational #

Real CMode # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CMode -> Rational #

Real CIno # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CIno -> Rational #

Real CDev # 
Instance details

Defined in System.Posix.Types

Methods

toRational :: CDev -> Rational #

Integral a => Real (Ratio a) #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

toRational :: Ratio a -> Rational #

Real a => Real (Down a) #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

toRational :: Down a -> Rational #

Real a => Real (Identity a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

toRational :: Identity a -> Rational #

HasResolution a => Real (Fixed a) #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

toRational :: Fixed a -> Rational #

Real a => Real (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

toRational :: Const a b -> Rational #

class (Real a, Enum a) => Integral a where #

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.

Minimal complete definition

quotRem, toInteger

Methods

quot :: a -> a -> a infixl 7 #

integer division truncated toward zero

rem :: a -> a -> a infixl 7 #

integer remainder, satisfying

(x `quot` y)*y + (x `rem` y) == x

div :: a -> a -> a infixl 7 #

integer division truncated toward negative infinity

mod :: a -> a -> a infixl 7 #

integer modulus, satisfying

(x `div` y)*y + (x `mod` y) == x

quotRem :: a -> a -> (a, a) #

simultaneous quot and rem

divMod :: a -> a -> (a, a) #

simultaneous div and mod

toInteger :: a -> Integer #

conversion to Integer

Instances

Instances details
Integral Int #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

quot :: Int -> Int -> Int #

rem :: Int -> Int -> Int #

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

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

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

toInteger :: Int -> Integer #

Integral Int8 #

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

quot :: Int8 -> Int8 -> Int8 #

rem :: Int8 -> Int8 -> Int8 #

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

quotRem :: Int8 -> Int8 -> (Int8, Int8) #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

toInteger :: Int8 -> Integer #

Integral Int16 #

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int32 #

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int64 #

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Integer #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Integral Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Integral Word #

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

Integral Word8 #

Since: base-2.1

Instance details

Defined in GHC.Word

Integral Word16 #

Since: base-2.1

Instance details

Defined in GHC.Word

Integral Word32 #

Since: base-2.1

Instance details

Defined in GHC.Word

Integral Word64 #

Since: base-2.1

Instance details

Defined in GHC.Word

Integral IntPtr # 
Instance details

Defined in Foreign.Ptr

Integral WordPtr # 
Instance details

Defined in Foreign.Ptr

Integral CUIntMax # 
Instance details

Defined in Foreign.C.Types

Integral CIntMax # 
Instance details

Defined in Foreign.C.Types

Integral CUIntPtr # 
Instance details

Defined in Foreign.C.Types

Integral CIntPtr # 
Instance details

Defined in Foreign.C.Types

Integral CSigAtomic # 
Instance details

Defined in Foreign.C.Types

Integral CWchar # 
Instance details

Defined in Foreign.C.Types

Integral CSize # 
Instance details

Defined in Foreign.C.Types

Integral CPtrdiff # 
Instance details

Defined in Foreign.C.Types

Integral CBool # 
Instance details

Defined in Foreign.C.Types

Integral CULLong # 
Instance details

Defined in Foreign.C.Types

Integral CLLong # 
Instance details

Defined in Foreign.C.Types

Integral CULong # 
Instance details

Defined in Foreign.C.Types

Integral CLong # 
Instance details

Defined in Foreign.C.Types

Integral CUInt # 
Instance details

Defined in Foreign.C.Types

Integral CInt # 
Instance details

Defined in Foreign.C.Types

Methods

quot :: CInt -> CInt -> CInt #

rem :: CInt -> CInt -> CInt #

div :: CInt -> CInt -> CInt #

mod :: CInt -> CInt -> CInt #

quotRem :: CInt -> CInt -> (CInt, CInt) #

divMod :: CInt -> CInt -> (CInt, CInt) #

toInteger :: CInt -> Integer #

Integral CUShort # 
Instance details

Defined in Foreign.C.Types

Integral CShort # 
Instance details

Defined in Foreign.C.Types

Integral CUChar # 
Instance details

Defined in Foreign.C.Types

Integral CSChar # 
Instance details

Defined in Foreign.C.Types

Integral CChar # 
Instance details

Defined in Foreign.C.Types

Integral Fd # 
Instance details

Defined in System.Posix.Types

Methods

quot :: Fd -> Fd -> Fd #

rem :: Fd -> Fd -> Fd #

div :: Fd -> Fd -> Fd #

mod :: Fd -> Fd -> Fd #

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

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

toInteger :: Fd -> Integer #

Integral CNfds # 
Instance details

Defined in System.Posix.Types

Integral CSocklen # 
Instance details

Defined in System.Posix.Types

Integral CKey # 
Instance details

Defined in System.Posix.Types

Methods

quot :: CKey -> CKey -> CKey #

rem :: CKey -> CKey -> CKey #

div :: CKey -> CKey -> CKey #

mod :: CKey -> CKey -> CKey #

quotRem :: CKey -> CKey -> (CKey, CKey) #

divMod :: CKey -> CKey -> (CKey, CKey) #

toInteger :: CKey -> Integer #

Integral CId # 
Instance details

Defined in System.Posix.Types

Methods

quot :: CId -> CId -> CId #

rem :: CId -> CId -> CId #

div :: CId -> CId -> CId #

mod :: CId -> CId -> CId #

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

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

toInteger :: CId -> Integer #

Integral CFsFilCnt # 
Instance details

Defined in System.Posix.Types

Integral CFsBlkCnt # 
Instance details

Defined in System.Posix.Types

Integral CClockId # 
Instance details

Defined in System.Posix.Types

Integral CBlkCnt # 
Instance details

Defined in System.Posix.Types

Integral CBlkSize # 
Instance details

Defined in System.Posix.Types

Integral CRLim # 
Instance details

Defined in System.Posix.Types

Integral CTcflag # 
Instance details

Defined in System.Posix.Types

Integral CUid # 
Instance details

Defined in System.Posix.Types

Methods

quot :: CUid -> CUid -> CUid #

rem :: CUid -> CUid -> CUid #

div :: CUid -> CUid -> CUid #

mod :: CUid -> CUid -> CUid #

quotRem :: CUid -> CUid -> (CUid, CUid) #

divMod :: CUid -> CUid -> (CUid, CUid) #

toInteger :: CUid -> Integer #

Integral CNlink # 
Instance details

Defined in System.Posix.Types

Integral CGid # 
Instance details

Defined in System.Posix.Types

Methods

quot :: CGid -> CGid -> CGid #

rem :: CGid -> CGid -> CGid #

div :: CGid -> CGid -> CGid #

mod :: CGid -> CGid -> CGid #

quotRem :: CGid -> CGid -> (CGid, CGid) #

divMod :: CGid -> CGid -> (CGid, CGid) #

toInteger :: CGid -> Integer #

Integral CSsize # 
Instance details

Defined in System.Posix.Types

Integral CPid # 
Instance details

Defined in System.Posix.Types

Methods

quot :: CPid -> CPid -> CPid #

rem :: CPid -> CPid -> CPid #

div :: CPid -> CPid -> CPid #

mod :: CPid -> CPid -> CPid #

quotRem :: CPid -> CPid -> (CPid, CPid) #

divMod :: CPid -> CPid -> (CPid, CPid) #

toInteger :: CPid -> Integer #

Integral COff # 
Instance details

Defined in System.Posix.Types

Methods

quot :: COff -> COff -> COff #

rem :: COff -> COff -> COff #

div :: COff -> COff -> COff #

mod :: COff -> COff -> COff #

quotRem :: COff -> COff -> (COff, COff) #

divMod :: COff -> COff -> (COff, COff) #

toInteger :: COff -> Integer #

Integral CMode # 
Instance details

Defined in System.Posix.Types

Integral CIno # 
Instance details

Defined in System.Posix.Types

Methods

quot :: CIno -> CIno -> CIno #

rem :: CIno -> CIno -> CIno #

div :: CIno -> CIno -> CIno #

mod :: CIno -> CIno -> CIno #

quotRem :: CIno -> CIno -> (CIno, CIno) #

divMod :: CIno -> CIno -> (CIno, CIno) #

toInteger :: CIno -> Integer #

Integral CDev # 
Instance details

Defined in System.Posix.Types

Methods

quot :: CDev -> CDev -> CDev #

rem :: CDev -> CDev -> CDev #

div :: CDev -> CDev -> CDev #

mod :: CDev -> CDev -> CDev #

quotRem :: CDev -> CDev -> (CDev, CDev) #

divMod :: CDev -> CDev -> (CDev, CDev) #

toInteger :: CDev -> Integer #

Integral a => Integral (Down a) #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

quot :: Down a -> Down a -> Down a #

rem :: Down a -> Down a -> Down a #

div :: Down a -> Down a -> Down a #

mod :: Down a -> Down a -> Down a #

quotRem :: Down a -> Down a -> (Down a, Down a) #

divMod :: Down a -> Down a -> (Down a, Down a) #

toInteger :: Down a -> Integer #

Integral a => Integral (Identity a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Integral a => Integral (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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

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

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

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

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

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

toInteger :: Const a b -> Integer #

class Num a => Fractional a where #

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

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 #

Fractional division.

recip :: a -> a #

Reciprocal fraction.

fromRational :: Rational -> a #

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

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

Fractional Float #

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

Fractional CDouble # 
Instance details

Defined in Foreign.C.Types

Fractional CFloat # 
Instance details

Defined in Foreign.C.Types

Integral a => Fractional (Ratio a) #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

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

recip :: Ratio a -> Ratio a #

fromRational :: Rational -> Ratio a #

Fractional a => Fractional (Down a) #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

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

recip :: Down a -> Down a #

fromRational :: Rational -> Down a #

Fractional a => Fractional (Identity a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

RealFloat a => Fractional (Complex a) #

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

(/) :: Complex a -> Complex a -> Complex a #

recip :: Complex a -> Complex a #

fromRational :: Rational -> Complex a #

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

Defined in Data.Functor.Contravariant

Methods

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

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

fromRational :: Rational -> Op a b #

HasResolution a => Fractional (Fixed a) #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

(/) :: Fixed a -> Fixed a -> Fixed a #

recip :: Fixed a -> Fixed a #

fromRational :: Rational -> Fixed a #

Fractional a => Fractional (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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

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

fromRational :: Rational -> Const a b #

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

Extracting components of fractions.

Minimal complete definition

properFraction

Methods

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

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 #

truncate x returns the integer nearest x between zero and x

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

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

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

ceiling x returns the least integer not less than x

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

floor x returns the greatest integer not greater than x

Instances

Instances details
RealFrac Double #

Since: base-2.1

Instance details

Defined in GHC.Float

Methods

properFraction :: Integral b => Double -> (b, Double) #

truncate :: Integral b => Double -> b #

round :: Integral b => Double -> b #

ceiling :: Integral b => Double -> b #

floor :: Integral b => Double -> b #

RealFrac Float #

Since: base-2.1

Instance details

Defined in GHC.Float

Methods

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

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

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

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

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

RealFrac CDouble # 
Instance details

Defined in Foreign.C.Types

Methods

properFraction :: Integral b => CDouble -> (b, CDouble) #

truncate :: Integral b => CDouble -> b #

round :: Integral b => CDouble -> b #

ceiling :: Integral b => CDouble -> b #

floor :: Integral b => CDouble -> b #

RealFrac CFloat # 
Instance details

Defined in Foreign.C.Types

Methods

properFraction :: Integral b => CFloat -> (b, CFloat) #

truncate :: Integral b => CFloat -> b #

round :: Integral b => CFloat -> b #

ceiling :: Integral b => CFloat -> b #

floor :: Integral b => CFloat -> b #

Integral a => RealFrac (Ratio a) #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

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

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

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

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

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

RealFrac a => RealFrac (Down a) #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

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

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

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

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

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

RealFrac a => RealFrac (Identity a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

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

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

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

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

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

HasResolution a => RealFrac (Fixed a) #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

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

truncate :: Integral b => Fixed a -> b #

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

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

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

RealFrac a => RealFrac (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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

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

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

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

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

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

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

general coercion from integral types

realToFrac :: (Real a, Fractional b) => a -> b #

general coercion to fractional types

showSigned #

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.

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

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

(^) :: (Num a, Integral b) => a -> b -> a infixr 8 #

raise a number to a non-negative integral power

(^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 #

raise a number to an integral power

(^%^) :: Integral a => Rational -> a -> Rational #

gcd :: Integral a => a -> a -> a #

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 #

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

gcdInt' :: Int -> Int -> Int #

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