numhask-0.3.0.0: numeric classes

Safe HaskellNone
LanguageHaskell2010

NumHask.Data.Rational

Contents

Description

Integral classes

Synopsis

Documentation

data Ratio a Source #

Constructors

!a :% !a 
Instances
(Eq a, Additive a) => Eq (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

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

(Ord a, Multiplicative a, Integral a) => Ord (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

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 #

Show a => Show (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

GCDConstraints a => Subtractive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

negate :: Ratio a -> Ratio a Source #

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

GCDConstraints a => Additive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

zero :: Ratio a Source #

GCDConstraints a => Divisive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

recip :: Ratio a -> Ratio a Source #

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

GCDConstraints a => Multiplicative (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

one :: Ratio a Source #

GCDConstraints a => IntegralDomain (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

GCDConstraints a => Distributive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

(FromInteger a, Multiplicative a) => FromInteger (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

(GCDConstraints a, Field a) => LowerBoundedField (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

(GCDConstraints a, Distributive a, IntegralDomain a) => UpperBoundedField (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

GCDConstraints a => Field (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

GCDConstraints a => MeetSemiLattice (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

GCDConstraints a => JoinSemiLattice (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

(GCDConstraints a, MeetSemiLattice a) => Epsilon (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

GCDConstraints a => Signed (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

sign :: Ratio a -> Ratio a Source #

abs :: Ratio a -> Ratio a Source #

FromInteger a => FromRatio (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

ToInteger a => ToRatio (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

(GCDConstraints a, GCDConstraints b, ToInteger a, Field a, FromInteger b) => QuotientField (Ratio a) b Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

round :: Ratio a -> b Source #

ceiling :: Ratio a -> b Source #

floor :: Ratio a -> b Source #

truncate :: Ratio a -> b Source #

GCDConstraints a => Metric (Ratio a) (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

distanceL1 :: Ratio a -> Ratio a -> Ratio a Source #

distanceL2 :: Ratio a -> Ratio a -> Ratio a Source #

GCDConstraints a => Normed (Ratio a) (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

normL1 :: Ratio a -> Ratio a Source #

normL2 :: Ratio a -> Ratio a Source #

class ToRatio a where Source #

toRatio is equivalent to Real in base.

Methods

toRatio :: a -> Ratio Integer Source #

Instances
ToRatio Double Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Float Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int8 Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int16 Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int32 Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int64 Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Natural Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Rational Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word8 Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word16 Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word32 Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word64 Source # 
Instance details

Defined in NumHask.Data.Rational

ToInteger a => ToRatio (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

(ToRatio a, ExpField a) => ToRatio (LogField a) Source # 
Instance details

Defined in NumHask.Data.LogField

ToRatio a => ToRatio (Wrapped a) Source # 
Instance details

Defined in NumHask.Data.Wrapped

class FromRatio a where Source #

Fractional in base splits into fromRatio and Field

Methods

fromRatio :: Ratio Integer -> a Source #

Instances
FromRatio Double Source # 
Instance details

Defined in NumHask.Data.Rational

FromRatio Float Source # 
Instance details

Defined in NumHask.Data.Rational

FromInteger a => FromRatio (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

FromRatio a => FromRatio (Pair a) Source # 
Instance details

Defined in NumHask.Data.Pair

(FromRatio a, ExpField a) => FromRatio (LogField a) Source # 
Instance details

Defined in NumHask.Data.LogField

FromRatio a => FromRatio (Wrapped a) Source # 
Instance details

Defined in NumHask.Data.Wrapped

fromRational :: (ToRatio a, FromRatio b) => a -> b Source #

coercion of Rationals

fromRational a == a

$integral_functionality

reduce :: (Eq a, Subtractive a, Signed a, 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.

gcd :: (Eq a, Signed a, 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.