base-4.14.1.0: Basic libraries
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Ratio

Description

Standard functions on rational numbers

Synopsis

Documentation

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.

Instances

Instances details
Integral a => Enum (Ratio a) Source #

Since: 2.0.1

Instance details

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

Eq a => Eq (Ratio a) Source #

Since: 2.1

Instance details

Defined in GHC.Real

Methods

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

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

Integral a => Fractional (Ratio a) Source #

Since: 2.0.1

Instance details

Defined in GHC.Real

Methods

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

recip :: Ratio a -> Ratio a Source #

fromRational :: Rational -> Ratio a Source #

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

Since: 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) 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 => Num (Ratio a) Source #

Since: 2.0.1

Instance details

Defined in GHC.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 => Ord (Ratio a) Source #

Since: 2.0.1

Instance details

Defined in GHC.Real

Methods

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

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

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

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

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

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

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

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

Since: 2.1

Instance details

Defined in GHC.Read

Integral a => Real (Ratio a) Source #

Since: 2.0.1

Instance details

Defined in GHC.Real

Integral a => RealFrac (Ratio a) Source #

Since: 2.0.1

Instance details

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

Since: 2.0.1

Instance details

Defined in GHC.Real

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

Since: 4.8.0.0

Instance details

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

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.

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

Forms the ratio of two integral numbers.

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.

approxRational :: RealFrac a => a -> a -> Rational Source #

approxRational, applied to two real fractional numbers x and epsilon, returns the simplest rational number within epsilon of x. A rational number y is said to be simpler than another y' if

Any real interval contains a unique simplest rational; in particular, note that 0/1 is the simplest rational of all.