Safe Haskell | None |
---|---|
Language | Haskell2010 |
Integral classes
Synopsis
- data Ratio a = !a :% !a
- type Rational = Ratio Integer
- class ToRatio a b where
- type ToRational a = ToRatio a Integer
- toRational :: ToRatio a Integer => a -> Ratio Integer
- class FromRatio a b where
- class FromRational a
- fromRational :: FromRational a => Rational -> a
- fromRational' :: (FromRatio b Integer, ToRatio a Integer) => a -> b
- fromBaseRational :: Rational -> Ratio Integer
- reduce :: (Eq a, Subtractive a, Signed a, Integral a) => a -> a -> Ratio a
- gcd :: (Eq a, Signed a, Integral a) => a -> a -> a
Documentation
!a :% !a |
Instances
class ToRatio a b where Source #
toRatio is equivalent to Real
in base, but is polymorphic in the Integral type.
Nothing
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 # | |
ToRatio Float Integer Source # | |
ToRatio Int Integer Source # | |
ToRatio Int8 Integer Source # | |
ToRatio Int16 Integer Source # | |
ToRatio Int32 Integer Source # | |
ToRatio Int64 Integer Source # | |
ToRatio Integer Integer Source # | |
ToRatio Natural Integer Source # | |
ToRatio Rational Integer Source # | |
ToRatio Word Integer Source # | |
ToRatio Word8 Integer Source # | |
ToRatio Word16 Integer Source # | |
ToRatio Word32 Integer Source # | |
ToRatio Word64 Integer Source # | |
ToRatio (Ratio Integer) Integer Source # | |
(ToRatio a b, ExpField a) => ToRatio (LogField a) b Source # | |
ToRatio a b => ToRatio (Wrapped a) b Source # | |
type ToRational a = ToRatio a Integer 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`
Nothing
Instances
FromRatio Double Integer Source # | |
FromRatio Float Integer Source # | |
FromRatio Rational Integer Source # | |
FromRatio (Ratio Integer) Integer Source # | |
FromRatio a b => FromRatio (Pair a) b Source # | |
(FromRatio a b, ExpField a) => FromRatio (LogField a) b Source # | |
FromRatio a b => FromRatio (Wrapped a) b Source # | |
class FromRational a Source #
with RebindableSyntax the literal '1.0' mean exactly `fromRational (1.0::GHC.Real.Rational)`.
Instances
FromRational Double Source # | |
Defined in NumHask.Data.Rational fromRational :: Rational -> Double Source # | |
FromRational Float Source # | |
Defined in NumHask.Data.Rational fromRational :: Rational -> Float Source # | |
FromRational Rational Source # | |
Defined in NumHask.Data.Rational fromRational :: Rational -> Rational Source # |
fromRational :: FromRational a => Rational -> a Source #
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 #
is the non-negative factor of both gcd
x yx
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 44
.
= gcd
0 00
.
(That is, the common divisor that is "greatest" in the divisibility
preordering.)
Note: Since for signed fixed-width integer types,
,
the result may be negative if one of the arguments is abs
minBound
< 0
(and
necessarily is if the other is minBound
0
or
) for such types.minBound