haskus-binary-1.5: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Number.Posit

Description

Posit (type III unum)

Synopsis

Documentation

newtype Posit (nbits :: Nat) (es :: Nat) Source #

Constructors

Posit (IntN nbits) 
Instances
(Bits (IntN n), FiniteBits (IntN n), Ord (IntN n), Num (IntN n), KnownNat n, KnownNat es, Integral (IntN n)) => Show (Posit n es) Source #

Show posit

Instance details

Defined in Haskus.Number.Posit

Methods

showsPrec :: Int -> Posit n es -> ShowS #

show :: Posit n es -> String #

showList :: [Posit n es] -> ShowS #

data PositKind Source #

Constructors

ZeroK 
InfinityK 
NormalK 
Instances
Eq PositKind Source # 
Instance details

Defined in Haskus.Number.Posit

Show PositKind Source # 
Instance details

Defined in Haskus.Number.Posit

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

Constructors

Zero :: PositK ZeroK nbits es 
Infinity :: PositK InfinityK nbits es 
Value :: Posit nbits es -> PositK NormalK nbits es 

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

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)