numhask-0.12.0.2: A numeric class hierarchy.
Safe HaskellSafe-Inferred
LanguageGHC2021

NumHask.Data.Rational

Description

Rational classes

Synopsis

Documentation

data Ratio a Source #

A rational number, represented as the ratio of two Integral numbers.

Constructors

!a :% !a 

Instances

Instances details
FromRatio Rational Integer Source # 
Instance details

Defined in NumHask.Data.Rational

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 #

(Eq a, Subtractive a, EndoBased a, Absolute a, Integral 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, Integral a, EndoBased a, Subtractive 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 #

(Ord a, EndoBased a, Integral a, Ring a) => Additive (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

zero :: Ratio a Source #

(Ord a, EndoBased a, Integral a, Ring 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 #

(Ord a, EndoBased a, Absolute a, ToInt a, Integral a, Ring a) => QuotientField (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Associated Types

type Whole (Ratio a) Source #

(Ord a, Integral a, EndoBased a, Subtractive a) => JoinSemiLattice (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

(Ord a, Integral a, EndoBased a, Subtractive a) => MeetSemiLattice (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

(Ord a, EndoBased a, Integral a, Ring a) => Basis (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Associated Types

type Mag (Ratio a) Source #

type Base (Ratio a) Source #

Methods

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

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

(Ord a, EndoBased a, Integral a, Ring a, MeetSemiLattice a) => Epsilon (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

epsilon :: Ratio a Source #

(Ord a, EndoBased a, Integral a, Ring 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 #

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

Defined in NumHask.Data.Rational

Methods

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

one :: Ratio a Source #

FromRational (Ratio Integer) Source # 
Instance details

Defined in NumHask.Data.Rational

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

Defined in NumHask.Data.Rational

Methods

fromIntegral :: b -> Ratio a Source #

ToRatio (Ratio Integer) Integer Source # 
Instance details

Defined in NumHask.Data.Rational

type Whole (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

type Whole (Ratio a) = Int
type Base (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

type Base (Ratio a) = Ratio a
type Mag (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

type Mag (Ratio a) = Ratio a

type Rational = Ratio Integer Source #

Ratio of two integers

class ToRatio a b where Source #

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

>>> toRatio (3.1415927 :: Float) :: Ratio Integer
13176795 :% 4194304

Methods

toRatio :: a -> Ratio b Source #

Instances

Instances details
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 Int8 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 Word8 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 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 Word Integer Source # 
Instance details

Defined in NumHask.Data.Rational

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

Defined in NumHask.Data.Positive

Methods

toRatio :: Positive a -> Ratio b Source #

ToRatio (Ratio Integer) Integer Source # 
Instance details

Defined in NumHask.Data.Rational

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

>>> fromRatio (5 :% 2 :: Ratio Integer) :: Double
2.5

Methods

fromRatio :: Ratio b -> a Source #

Instances

Instances details
FromRatio Rational Integer Source # 
Instance details

Defined in NumHask.Data.Rational

FromRatio Double Integer Source # 
Instance details

Defined in NumHask.Data.Rational

FromRatio Float Integer Source # 
Instance details

Defined in NumHask.Data.Rational

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

Defined in NumHask.Data.Positive

Methods

fromRatio :: Ratio b -> Positive 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 where Source #

fromRational is special in two ways:

  • numeric decimal literals (like "53.66") are interpreted as exactly "fromRational (53.66 :: GHC.Real.Ratio Integer)". The prelude version, GHC.Real.fromRational is used as default (or whatever is in scope if RebindableSyntax is set).
  • The default rules in haskell2010 specify that contraints on fromRational need to be in a form C v, where v is a Num or a subclass of Num.

So a type synonym of `type FromRational a = FromRatio a Integer` doesn't work well with type defaulting; hence the need for a separate class.

Methods

fromRational :: Rational -> a Source #

Instances

Instances details
FromRational Double Source # 
Instance details

Defined in NumHask.Data.Rational

FromRational Float Source # 
Instance details

Defined in NumHask.Data.Rational

FromRational a => FromRational (Positive a) Source # 
Instance details

Defined in NumHask.Data.Positive

FromRational (Ratio Integer) Source # 
Instance details

Defined in NumHask.Data.Rational

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

Defined in NumHask.Data.Wrapped

reduce :: (Eq a, Subtractive a, EndoBased a, Integral a) => a -> a -> Ratio a Source #

reduce normalises a ratio by dividing both numerator and denominator by their greatest common divisor.

>>> reduce 72 60
6 :% 5
\a b -> reduce a b == a :% b || b == zero

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

>>> gcd 72 60
12