numhask-0.5.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, Additive 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

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

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

Defined in NumHask.Data.Rational

Methods

fromIntegral_ :: b -> Ratio a Source #

(GCDConstraints a, GCDConstraints b, ToInteger a, Field a, FromIntegral b a) => 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 #

FromRatio (Ratio Integer) Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio (Ratio Integer) Integer Source # 
Instance details

Defined in NumHask.Data.Rational

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 #

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.

class ToRatio a b where Source #

toRatio is equivalent to Real in base, but is polymorphic in the Integral type.

Minimal complete definition

Nothing

Methods

toRatio :: a -> Ratio b Source #

toRatio :: (Ratio c ~ a, ToIntegral c Integer, ToRatio (Ratio b) b, FromInteger b) => a -> Ratio b Source #

Instances
ToRatio Double Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Float Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int8 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int16 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int32 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Int64 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Integer Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Natural Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Rational Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word8 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word16 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word32 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio Word64 Integer Source # 
Instance details

Defined in NumHask.Data.Rational

ToRatio (Ratio Integer) Integer Source # 
Instance details

Defined in NumHask.Data.Rational

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

Defined in NumHask.Data.LogField

Methods

toRatio :: LogField a -> Ratio b Source #

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

Defined in NumHask.Data.Wrapped

Methods

toRatio :: Wrapped a -> Ratio b Source #

class FromRatio a b where Source #

Fractional in base splits into fromRatio and Field FIXME: work out why the default type isn't firing so that an explicit instance is needed for `FromRatio (Ratio Integer) Integer`

Minimal complete definition

Nothing

Methods

fromRatio :: Ratio b -> a Source #

fromRatio :: Ratio b ~ a => Ratio b -> a Source #

Instances
FromRatio Double Integer Source # 
Instance details

Defined in NumHask.Data.Rational

FromRatio Float Integer Source # 
Instance details

Defined in NumHask.Data.Rational

FromRatio Rational Integer Source # 
Instance details

Defined in NumHask.Data.Rational

FromRatio (Ratio Integer) Integer Source # 
Instance details

Defined in NumHask.Data.Rational

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

Defined in NumHask.Data.Pair

Methods

fromRatio :: Ratio b -> Pair a Source #

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

Defined in NumHask.Data.LogField

Methods

fromRatio :: Ratio b -> LogField a Source #

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

Defined in NumHask.Data.Wrapped

Methods

fromRatio :: Ratio b -> Wrapped a Source #

class FromRational a Source #

with RebindableSyntax the literal '1.0' mean exactly `fromRational (1.0::GHC.Real.Rational)`.

Instances
FromRational Double Source # 
Instance details

Defined in NumHask.Data.Rational

FromRational Float Source # 
Instance details

Defined in NumHask.Data.Rational

FromRational Rational Source # 
Instance details

Defined in NumHask.Data.Rational

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

Given that fromRational is reserved, fromRational' provides general conversion between numhask rationals.

$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.