Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | stable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Standard functions on rational numbers
Documentation
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
(Data a, Integral a) => Data (Ratio a) | @since base-4.0.0.0 |
Defined in GHC.Internal.Data.Data 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 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 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 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 |
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
, andabs
(numerator
y) <=abs
(numerator
y')
.denominator
y <=denominator
y'
Any real interval contains a unique simplest rational;
in particular, note that 0/1
is the simplest rational of all.