Safe Haskell | None |
---|---|
Language | Haskell2010 |
Posit (type III unum)
Synopsis
- newtype Posit (nbits :: Nat) (es :: Nat) = Posit (IntN nbits)
- data PositKind
- data PositK k nbits es where
- positKind :: forall n es. (Bits (IntN n), KnownNat n, Eq (IntN n)) => Posit n es -> SomePosit n es
- isZero :: forall n es. (Bits (IntN n), Eq (IntN n), KnownNat n) => Posit n es -> Bool
- isInfinity :: forall n es. (Bits (IntN n), Eq (IntN n), KnownNat n) => Posit n es -> Bool
- isPositive :: forall n es. (Bits (IntN n), Ord (IntN n), KnownNat n) => PositValue n es -> Bool
- isNegative :: forall n es. (Bits (IntN n), Ord (IntN n), KnownNat n) => PositValue n es -> Bool
- positAbs :: forall n es. (Num (IntN n), KnownNat n) => PositValue n es -> PositValue n es
- data PositEncoding
- data PositFields = PositFields {}
- positEncoding :: forall n es. (Bits (IntN n), Ord (IntN n), Num (IntN n), KnownNat n, KnownNat es, Integral (IntN n)) => Posit n es -> PositEncoding
- positFields :: forall n es. (Bits (IntN n), Ord (IntN n), Num (IntN n), KnownNat n, KnownNat es, Integral (IntN n)) => PositValue n es -> PositFields
- positToRational :: forall n es. (KnownNat n, KnownNat es, Eq (IntN n), Bits (IntN n), Integral (IntN n)) => Posit n es -> Rational
- positFromRational :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), KnownNat es, KnownNat n) => Rational -> Posit n es
- positApproxFactor :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), Integral (IntN n), KnownNat es, KnownNat n) => Rational -> Double
- positDecimalError :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), Integral (IntN n), KnownNat es, KnownNat n) => Rational -> Double
- positDecimalAccuracy :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), Integral (IntN n), KnownNat es, KnownNat n) => Rational -> Double
- positBinaryError :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), Integral (IntN n), KnownNat es, KnownNat n) => Rational -> Double
- positBinaryAccuracy :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), Integral (IntN n), KnownNat es, KnownNat n) => Rational -> Double
- floatBinaryAccuracy :: forall f. (Fractional f, Real f) => Rational -> Double
Documentation
data PositK k nbits es where Source #
Kinded Posit
GADT that can be used to ensure at the type level that we deal with non-infinite/non-zero Posit values
positKind :: forall n es. (Bits (IntN n), KnownNat n, Eq (IntN n)) => Posit n es -> SomePosit n es Source #
Get the kind of the posit at the type level
isZero :: forall n es. (Bits (IntN n), Eq (IntN n), KnownNat n) => Posit n es -> Bool Source #
Check if a posit is zero
isInfinity :: forall n es. (Bits (IntN n), Eq (IntN n), KnownNat n) => Posit n es -> Bool Source #
Check if a posit is infinity
isPositive :: forall n es. (Bits (IntN n), Ord (IntN n), KnownNat n) => PositValue n es -> Bool Source #
Check if a posit is positive
isNegative :: forall n es. (Bits (IntN n), Ord (IntN n), KnownNat n) => PositValue n es -> Bool Source #
Check if a posit is negative
positAbs :: forall n es. (Num (IntN n), KnownNat n) => PositValue n es -> PositValue n es Source #
Posit absolute value
data PositEncoding Source #
Instances
Show PositEncoding Source # | |
Defined in Haskus.Number.Posit showsPrec :: Int -> PositEncoding -> ShowS # show :: PositEncoding -> String # showList :: [PositEncoding] -> ShowS # |
data PositFields Source #
Instances
Show PositFields Source # | |
Defined in Haskus.Number.Posit showsPrec :: Int -> PositFields -> ShowS # show :: PositFields -> String # showList :: [PositFields] -> ShowS # |
positEncoding :: forall n es. (Bits (IntN n), Ord (IntN n), Num (IntN n), KnownNat n, KnownNat es, Integral (IntN n)) => Posit n es -> PositEncoding Source #
positFields :: forall n es. (Bits (IntN n), Ord (IntN n), Num (IntN n), KnownNat n, KnownNat es, Integral (IntN n)) => PositValue n es -> PositFields Source #
Decode posit fields
positToRational :: forall n es. (KnownNat n, KnownNat es, Eq (IntN n), Bits (IntN n), Integral (IntN n)) => Posit n es -> Rational Source #
Convert a Posit into a Rational
positFromRational :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), KnownNat es, KnownNat n) => Rational -> Posit n es Source #
Convert a rational into the approximate Posit
positApproxFactor :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), Integral (IntN n), KnownNat es, KnownNat n) => Rational -> Double Source #
Factor of approximation for a given Rational when encoded as a Posit. The closer to 1, the better.
Usage:
positApproxFactor @(Posit 8 2) (52 % 137)
positDecimalError :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), Integral (IntN n), KnownNat es, KnownNat n) => Rational -> Double Source #
Compute the decimal error if the given Rational is encoded as a Posit.
Usage:
positDecimalError @(Posit 8 2) (52 % 137)
positDecimalAccuracy :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), Integral (IntN n), KnownNat es, KnownNat n) => Rational -> Double Source #
Compute the number of decimals of accuracy if the given Rational is encoded as a Posit.
Usage:
positDecimalAccuracy @(Posit 8 2) (52 % 137)
positBinaryError :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), Integral (IntN n), KnownNat es, KnownNat n) => Rational -> Double Source #
Compute the binary error if the given Rational is encoded as a Posit.
Usage:
positBinaryError @(Posit 8 2) (52 % 137)
positBinaryAccuracy :: forall p n es. (Posit n es ~ p, Num (IntN n), Bits (IntN n), Integral (IntN n), KnownNat es, KnownNat n) => Rational -> Double Source #
Compute the number of bits of accuracy if the given Rational is encoded as a Posit.
Usage:
positBinaryAccuracy @(Posit 8 2) (52 % 137)
floatBinaryAccuracy :: forall f. (Fractional f, Real f) => Rational -> Double Source #
Compute the number of bits of accuracy if the given Rational is encoded as a Float/Double.
Usage:
floatBinaryAccuracy @Double (52 % 137)