numhask-0.2.2.0: numeric classes

Safe HaskellNone
LanguageHaskell2010

NumHask.Algebra.Rational

Contents

Description

Integral classes

Synopsis

Documentation

data Ratio a Source #

Constructors

!a :% !a 

Instances

Eq a => Eq (Ratio a) Source # 

Methods

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

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

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

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 # 

Methods

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

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

(Ord a, Signed a, Integral a, AdditiveGroup a) => AdditiveGroup (Ratio a) Source # 

Methods

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

(Ord a, Signed a, Integral a, AdditiveInvertible a) => Additive (Ratio a) Source # 

Methods

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

(Ord a, Signed a, Integral a, AdditiveInvertible a) => AdditiveInvertible (Ratio a) Source # 

Methods

negate :: Ratio a -> Ratio a Source #

(Ord a, Signed a, Integral a, AdditiveInvertible a) => AdditiveCommutative (Ratio a) Source # 
(Ord a, Signed a, Integral a, AdditiveInvertible a) => AdditiveAssociative (Ratio a) Source # 
(Ord a, Integral a, Signed a, AdditiveInvertible a) => AdditiveUnital (Ratio a) Source # 

Methods

zero :: Ratio a Source #

(Ord a, Integral a, Signed a, AdditiveInvertible a) => AdditiveMagma (Ratio a) Source # 

Methods

plus :: Ratio a -> Ratio a -> Ratio a Source #

(Signed a, AdditiveInvertible a, AdditiveUnital a, Integral a, Ord a, Multiplicative a) => MultiplicativeGroup (Ratio a) Source # 

Methods

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

(Signed a, AdditiveInvertible a, AdditiveUnital a, Integral a, Ord a, Multiplicative a) => Multiplicative (Ratio a) Source # 

Methods

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

(Ord a, Signed a, Integral a, AdditiveInvertible a) => MultiplicativeInvertible (Ratio a) Source # 

Methods

recip :: Ratio a -> Ratio a Source #

(Ord a, Signed a, Integral a, AdditiveInvertible a) => MultiplicativeCommutative (Ratio a) Source # 
(Ord a, Signed a, Integral a, AdditiveInvertible a) => MultiplicativeAssociative (Ratio a) Source # 
(Ord a, Signed a, Integral a, AdditiveInvertible a) => MultiplicativeUnital (Ratio a) Source # 

Methods

one :: Ratio a Source #

(Ord a, Signed a, Integral a, AdditiveInvertible a) => MultiplicativeMagma (Ratio a) Source # 

Methods

times :: Ratio a -> Ratio a -> Ratio a Source #

(Ord a, Signed a, Integral a, AdditiveInvertible a) => Distribution (Ratio a) Source # 
(Ord a, Signed a, Integral a, Multiplicative a, Ring a) => InvolutiveRing (Ratio a) Source # 

Methods

adj :: Ratio a -> Ratio a Source #

(Ord a, Signed a, Integral a, Multiplicative a, Ring a) => CRing (Ratio a) Source # 
(Ord a, Signed a, Integral a, AdditiveGroup a) => Ring (Ratio a) Source # 
(Ord a, Signed a, Integral a, AdditiveInvertible a) => Semiring (Ratio a) Source # 
(FromInteger a, MultiplicativeUnital a) => FromInteger (Ratio a) Source # 
(Ord a, Signed a, Integral a, Multiplicative a, Ring a, AdditiveInvertible a) => LowerBoundedField (Ratio a) Source # 
(Ord a, Signed a, Integral a, AdditiveInvertible a, Multiplicative a, Ring a) => UpperBoundedField (Ratio a) Source # 
(Ord a, Signed a, Integral a, Multiplicative a, Ring a) => Field (Ratio a) Source # 
(Ord a, Signed a, Integral a, Multiplicative a, Ring a) => Semifield (Ratio a) Source # 
(Ord a, Signed a, Integral a, AdditiveGroup a) => Epsilon (Ratio a) Source # 
(Ord a, Signed a, Integral a, AdditiveInvertible a) => Signed (Ratio a) Source # 

Methods

sign :: Ratio a -> Ratio a Source #

abs :: Ratio a -> Ratio a Source #

FromInteger a => FromRatio (Ratio a) Source # 
ToInteger a => ToRatio (Ratio a) Source # 
(Ord a, Signed a, ToInteger a, Integral a, Multiplicative a, Ring a, Eq b, AdditiveGroup b, Integral b, FromInteger b) => QuotientField (Ratio a) b Source # 

Methods

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

round :: Ratio a -> b Source #

ceiling :: Ratio a -> b Source #

floor :: Ratio a -> b Source #

(Ord a, Integral a, Signed a, AdditiveGroup a) => Metric (Ratio a) (Ratio a) Source # 

Methods

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

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

distanceLp :: Ratio a -> Ratio a -> Ratio a -> Ratio a Source #

(Ord a, Integral a, Signed a, AdditiveInvertible a) => Normed (Ratio a) (Ratio a) Source # 

Methods

normL1 :: Ratio a -> Ratio a Source #

normL2 :: Ratio a -> Ratio a Source #

normLp :: Ratio a -> Ratio a -> Ratio a Source #

class FromRatio a where Source #

Fractional in base splits into fromRatio and MultiplicativeGroup

Minimal complete definition

fromRatio

Methods

fromRatio :: Ratio Integer -> a Source #

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

coercion of Rationals

fromRational a == a

$integral_functionality

reduce :: (Ord a, AdditiveInvertible 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 :: (Ord 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.