| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Numeric.Rounded.Hardware.Internal
Synopsis
- binaryFloatToDecimalDigitsRn :: forall a. RealFloat a => RoundingMode -> Int -> a -> ([Int], Int)
- binaryFloatToFixedDecimalDigitsRn :: forall a. RealFloat a => RoundingMode -> Int -> a -> [Int]
- binaryFloatToDecimalDigits :: RealFloat a => a -> ([Int], Int)
- showEFloatRn :: RealFloat a => RoundingMode -> Maybe Int -> a -> ShowS
- showFFloatRn :: RealFloat a => RoundingMode -> Maybe Int -> a -> ShowS
- showGFloatRn :: RealFloat a => RoundingMode -> Maybe Int -> a -> ShowS
- data RoundingMode
- oppositeRoundingMode :: RoundingMode -> RoundingMode
- class Rounding (r :: RoundingMode)
- rounding :: Rounding r => proxy r -> RoundingMode
- reifyRounding :: RoundingMode -> (forall s. Rounding s => Proxy s -> a) -> a
- newtype Rounded (r :: RoundingMode) a = Rounded {- getRounded :: a
 
- data family MVector s a
- data family Vector a
- nextUp :: RealFloat a => a -> a
- nextDown :: RealFloat a => a -> a
- nextTowardZero :: RealFloat a => a -> a
- distanceUlp :: RealFloat a => a -> a -> Maybe Integer
- fusedMultiplyAdd :: RealFloat a => a -> a -> a -> a
- roundedFromInteger_default :: RealFloat a => RoundingMode -> Integer -> a
- roundedFromRational_default :: RealFloat a => RoundingMode -> Rational -> a
- intervalFromInteger_default :: RealFloat a => Integer -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- intervalFromIntegral :: (Integral i, RealFloat a) => i -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- intervalFromRational_default :: RealFloat a => Rational -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- class RealFloatConstants a where- positiveInfinity :: a
- negativeInfinity :: a
- maxFinite :: a
- minPositive :: a
- pi_down :: Rounded 'TowardNegInf a
- pi_up :: Rounded 'TowardInf a
- three_pi_down :: Rounded 'TowardNegInf a
- three_pi_up :: Rounded 'TowardInf a
- five_pi_down :: Rounded 'TowardNegInf a
- five_pi_up :: Rounded 'TowardInf a
- log2_down :: Rounded 'TowardNegInf a
- log2_up :: Rounded 'TowardInf a
- exp1_down :: Rounded 'TowardNegInf a
- exp1_up :: Rounded 'TowardInf a
- exp1_2_down :: Rounded 'TowardNegInf a
- exp1_2_up :: Rounded 'TowardInf a
- expm1_2_down :: Rounded 'TowardNegInf a
- expm1_2_up :: Rounded 'TowardInf a
- sqrt2_down :: Rounded 'TowardNegInf a
- sqrt2_up :: Rounded 'TowardInf a
- sqrt2m1_down :: Rounded 'TowardNegInf a
- sqrt2m1_up :: Rounded 'TowardInf a
- sqrt1_2_down :: Rounded 'TowardNegInf a
- sqrt1_2_up :: Rounded 'TowardInf a
- three_minus_2sqrt2_down :: Rounded 'TowardNegInf a
- three_minus_2sqrt2_up :: Rounded 'TowardInf a
- two_minus_sqrt2_down :: Rounded 'TowardNegInf a
- two_minus_sqrt2_up :: Rounded 'TowardInf a
 
- class (RoundedSqrt a, RoundedRing_Vector vector a) => RoundedSqrt_Vector vector a where- map_roundedSqrt :: RoundingMode -> vector a -> vector a
 
- class (RoundedFractional a, RoundedRing_Vector vector a) => RoundedFractional_Vector vector a where- zipWith_roundedDiv :: RoundingMode -> vector a -> vector a -> vector a
 
- class RoundedRing a => RoundedRing_Vector vector a where- roundedSum :: RoundingMode -> vector a -> a
- zipWith_roundedAdd :: RoundingMode -> vector a -> vector a -> vector a
- zipWith_roundedSub :: RoundingMode -> vector a -> vector a -> vector a
- zipWith_roundedMul :: RoundingMode -> vector a -> vector a -> vector a
- zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> vector a -> vector a -> vector a -> vector a
 
- class RoundedRing a => RoundedSqrt a where- roundedSqrt :: RoundingMode -> a -> a
- intervalSqrt :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
 
- class RoundedRing a => RoundedFractional a where- roundedDiv :: RoundingMode -> a -> a -> a
- roundedRecip :: RoundingMode -> a -> a
- roundedFromRational :: RoundingMode -> Rational -> a
- roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> a
- intervalDiv :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- intervalDivAdd :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- intervalRecip :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- intervalFromRational :: Rational -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
 
- class Ord a => RoundedRing a where- roundedAdd :: RoundingMode -> a -> a -> a
- roundedSub :: RoundingMode -> a -> a -> a
- roundedMul :: RoundingMode -> a -> a -> a
- roundedFusedMultiplyAdd :: RoundingMode -> a -> a -> a -> a
- roundedFromInteger :: RoundingMode -> Integer -> a
- intervalAdd :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- intervalSub :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- intervalMul :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- intervalMulAdd :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- intervalFromInteger :: Integer -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
- backendNameT :: Tagged a String
 
- backendName :: RoundedRing a => proxy a -> String
- data RoundingMode
- oppositeRoundingMode :: RoundingMode -> RoundingMode
- class Rounding (r :: RoundingMode)
- rounding :: Rounding r => proxy r -> RoundingMode
- reifyRounding :: RoundingMode -> (forall s. Rounding s => Proxy s -> a) -> a
- newtype Rounded (r :: RoundingMode) a = Rounded {- getRounded :: a
 
- data family MVector s a
- data family Vector a
Documentation
>>>import Data.Int
binaryFloatToDecimalDigitsRn Source #
Arguments
| :: forall a. RealFloat a | |
| => RoundingMode | rounding mode | 
| -> Int | prec | 
| -> a | a non-negative number (zero, normal or subnormal) | 
| -> ([Int], Int) | 
>>>binaryFloatToDecimalDigitsRn ToNearest 3 (0.125 :: Double)([1,2,5],0)>>>binaryFloatToDecimalDigitsRn ToNearest 3 (12.5 :: Double)([1,2,5],2)
binaryFloatToFixedDecimalDigitsRn Source #
Arguments
| :: forall a. RealFloat a | |
| => RoundingMode | rounding mode | 
| -> Int | prec | 
| -> a | a non-negative number (zero, normal or subnormal) | 
| -> [Int] | 
>>>binaryFloatToFixedDecimalDigitsRn ToNearest 3 (0.125 :: Double)[1,2,5]>>>binaryFloatToFixedDecimalDigitsRn ToNearest 3 (12.5 :: Double)[1,2,5,0,0]
binaryFloatToDecimalDigits Source #
>>>binaryFloatToDecimalDigits (0.125 :: Double)([1,2,5],0)>>>binaryFloatToDecimalDigits (12.5 :: Double)([1,2,5],2)
showEFloatRn :: RealFloat a => RoundingMode -> Maybe Int -> a -> ShowS Source #
>>>showEFloatRn ToNearest (Just 0) (0 :: Double) """0e0">>>showEFloatRn ToNearest Nothing (0 :: Double) """0.0e0">>>showEFloatRn ToNearest Nothing (0.5 :: Double) """5.0e-1"
showFFloatRn :: RealFloat a => RoundingMode -> Maybe Int -> a -> ShowS Source #
>>>showFFloatRn ToNearest (Just 0) (0 :: Double) """0">>>showFFloatRn ToNearest Nothing (0 :: Double) """0.0">>>showFFloatRn ToNearest Nothing (-0 :: Double) """-0.0">>>showFFloatRn ToNearest Nothing (-0.5 :: Double) """-0.5"
showGFloatRn :: RealFloat a => RoundingMode -> Maybe Int -> a -> ShowS Source #
data RoundingMode Source #
The type for IEEE754 rounding-direction attributes.
Constructors
| ToNearest | Round to the nearest value (IEEE754 roundTiesToEven) | 
| TowardNegInf | Round downward (IEEE754 roundTowardNegative) | 
| TowardInf | Round upward (IEEE754 roundTowardPositive) | 
| TowardZero | Round toward zero (IEEE754 roundTowardZero) | 
Instances
oppositeRoundingMode :: RoundingMode -> RoundingMode Source #
Returns the opposite rounding direction.
TowardNegInf and TowardInf are swapped.
class Rounding (r :: RoundingMode) Source #
This class allows you to recover the runtime value from a type-level rounding mode.
See rounding.
Minimal complete definition
roundingT
Instances
| Rounding 'ToNearest Source # | |
| Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
| Rounding 'TowardNegInf Source # | |
| Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
| Rounding 'TowardInf Source # | |
| Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
| Rounding 'TowardZero Source # | |
| Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
rounding :: Rounding r => proxy r -> RoundingMode Source #
Recovers the value from type-level rounding mode.
reifyRounding :: RoundingMode -> (forall s. Rounding s => Proxy s -> a) -> a Source #
Lifts a rounding mode to type-level.
newtype Rounded (r :: RoundingMode) a Source #
A type tagged with a rounding direction.
The rounding direction is effective for a single operation.
 You won't get the correctly-rounded result for a compound expression like (a - b * c) :: Rounded 'TowardInf Double.
In particular, a negative literal like -0.1 :: Rounded r Double doesn't yield the correctly-rounded value for -0.1.
 To get the correct value, call fromRational explicitly (i.e. fromRational (-0.1) :: Rounded r Double) or use NegativeLiterals extension.
Constructors
| Rounded | |
| Fields 
 | |
Instances
Instances
Instances
nextUp :: RealFloat a => a -> a #
Returns the smallest value that is larger than the argument.
IEEE 754 nextUp operation.
>>>nextUp 1 == (0x1.000002p0 :: Float)True>>>nextUp 1 == (0x1.0000_0000_0000_1p0 :: Double)True>>>nextUp (1/0) == (1/0 :: Double)True>>>nextUp (-1/0) == (- maxFinite :: Double)True>>>nextUp 0 == (0x1p-1074 :: Double)True>>>nextUp (-0) == (0x1p-1074 :: Double)True>>>nextUp (-0x1p-1074) :: Double -- returns negative zero-0.0
nextDown :: RealFloat a => a -> a #
Returns the largest value that is smaller than the argument.
IEEE 754 nextDown operation.
>>>nextDown 1 == (0x1.ffff_ffff_ffff_fp-1 :: Double)True>>>nextDown 1 == (0x1.fffffep-1 :: Float)True>>>nextDown (1/0) == (maxFinite :: Double)True>>>nextDown (-1/0) == (-1/0 :: Double)True>>>nextDown 0 == (-0x1p-1074 :: Double)True>>>nextDown (-0) == (-0x1p-1074 :: Double)True>>>nextDown 0x1p-1074 -- returns positive zero0.0>>>nextDown 0x1p-1022 == (0x0.ffff_ffff_ffff_fp-1022 :: Double)True
nextTowardZero :: RealFloat a => a -> a #
Returns the value whose magnitude is smaller than that of the argument, and is closest to the argument.
This operation is not in IEEE, but may be useful to some.
>>>nextTowardZero 1 == (0x1.ffff_ffff_ffff_fp-1 :: Double)True>>>nextTowardZero 1 == (0x1.fffffep-1 :: Float)True>>>nextTowardZero (1/0) == (maxFinite :: Double)True>>>nextTowardZero (-1/0) == (-maxFinite :: Double)True>>>nextTowardZero 0 :: Double -- returns positive zero0.0>>>nextTowardZero (-0 :: Double) -- returns negative zero-0.0>>>nextTowardZero 0x1p-1074 :: Double0.0
fusedMultiplyAdd :: RealFloat a => a -> a -> a -> a #
fusedMultiplyAdd a b ca * b + c as a single, ternary operation.
 Rounding is done only once.
May make use of hardware FMA instructions if the target architecture has it; set fma3 package flag on x86 systems.
IEEE 754 fusedMultiplyAdd operation.
\(a :: Double) (b :: Double) (c :: Double) -> fusedMultiplyAdd a b c == fromRational (toRational a * toRational b + toRational c)
roundedFromInteger_default :: RealFloat a => RoundingMode -> Integer -> a Source #
roundedFromRational_default :: RealFloat a => RoundingMode -> Rational -> a Source #
intervalFromInteger_default :: RealFloat a => Integer -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
intervalFromIntegral :: (Integral i, RealFloat a) => i -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
intervalFromRational_default :: RealFloat a => Rational -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
class RealFloatConstants a where Source #
Methods
positiveInfinity :: a Source #
\(+\infty\)
negativeInfinity :: a Source #
\(-\infty\)
minPositive :: a Source #
pi_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(\pi\)
pi_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(\pi\)
three_pi_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(3\pi\)
three_pi_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(3\pi\)
five_pi_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(5\pi\)
five_pi_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(5\pi\)
log2_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(\log_e 2\)
log2_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(\log_e 2\)
exp1_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(\exp(1)\)
exp1_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(\exp(1)\)
exp1_2_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(\exp(1/2)\)
exp1_2_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(\exp(1/2)\)
expm1_2_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(\exp(-1/2)\)
expm1_2_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(\exp(-1/2)\)
sqrt2_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(\sqrt{2}\)
sqrt2_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(\sqrt{2}\)
sqrt2m1_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(\sqrt{2}-1\)
sqrt2m1_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(\sqrt{2}-1\)
sqrt1_2_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(1/\sqrt{2}\)
sqrt1_2_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(1/\sqrt{2}\)
three_minus_2sqrt2_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(3-2\sqrt{2}\)
three_minus_2sqrt2_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(3-2\sqrt{2}\)
two_minus_sqrt2_down :: Rounded 'TowardNegInf a Source #
The correctly-rounded value of \(2-\sqrt{2}\)
two_minus_sqrt2_up :: Rounded 'TowardInf a Source #
The correctly-rounded value of \(2-\sqrt{2}\)
Instances
class (RoundedSqrt a, RoundedRing_Vector vector a) => RoundedSqrt_Vector vector a where Source #
Lifted version of RoundedSqrt
Minimal complete definition
Nothing
Methods
map_roundedSqrt :: RoundingMode -> vector a -> vector a Source #
Equivalent to map . roundedSqrt
default map_roundedSqrt :: Vector vector a => RoundingMode -> vector a -> vector a Source #
Instances
class (RoundedFractional a, RoundedRing_Vector vector a) => RoundedFractional_Vector vector a where Source #
Lifted version of RoundedFractional
Minimal complete definition
Nothing
Methods
zipWith_roundedDiv :: RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith . roundedDiv
default zipWith_roundedDiv :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #
Instances
class RoundedRing a => RoundedRing_Vector vector a where Source #
Lifted version of RoundedRing
Minimal complete definition
Nothing
Methods
roundedSum :: RoundingMode -> vector a -> a Source #
Equivalent to \r -> foldl (roundedAdd r) 0
default roundedSum :: (Vector vector a, Num a) => RoundingMode -> vector a -> a Source #
zipWith_roundedAdd :: RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith . roundedAdd
default zipWith_roundedAdd :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #
zipWith_roundedSub :: RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith . roundedSub
default zipWith_roundedSub :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #
zipWith_roundedMul :: RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith . roundedMul
default zipWith_roundedMul :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #
zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> vector a -> vector a -> vector a -> vector a Source #
Equivalent to zipWith3 . roundedFusedMultiplyAdd
default zipWith3_roundedFusedMultiplyAdd :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a -> vector a Source #
Instances
class RoundedRing a => RoundedSqrt a where Source #
Rounding-controlled version of sqrt.
Minimal complete definition
Methods
roundedSqrt :: RoundingMode -> a -> a Source #
intervalSqrt :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
Instances
class RoundedRing a => RoundedFractional a where Source #
Rounding-controlled version of Fractional.
Minimal complete definition
Methods
roundedDiv :: RoundingMode -> a -> a -> a Source #
roundedRecip :: RoundingMode -> a -> a Source #
default roundedRecip :: Num a => RoundingMode -> a -> a Source #
roundedFromRational :: RoundingMode -> Rational -> a Source #
default roundedFromRational :: RealFloat a => RoundingMode -> Rational -> a Source #
roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> a Source #
default roundedFromRealFloat :: (Fractional a, RealFloat b) => RoundingMode -> b -> a Source #
intervalDiv :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
intervalDivAdd :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
intervalRecip :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
intervalFromRational :: Rational -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
Instances
class Ord a => RoundedRing a where Source #
Rounding-controlled version of Num.
Minimal complete definition
roundedAdd, roundedSub, roundedMul, roundedFusedMultiplyAdd, backendNameT
Methods
roundedAdd :: RoundingMode -> a -> a -> a Source #
roundedSub :: RoundingMode -> a -> a -> a Source #
roundedMul :: RoundingMode -> a -> a -> a Source #
roundedFusedMultiplyAdd :: RoundingMode -> a -> a -> a -> a Source #
roundedFromInteger :: RoundingMode -> Integer -> a Source #
default roundedFromInteger :: RealFloat a => RoundingMode -> Integer -> a Source #
intervalAdd :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
\x_lo x_hi y_lo y_hi -> intervalAdd (Rounded x_lo) (Rounded x_hi) (Rounded y_lo) (Rounded y_hi) == (Rounded (roundedAdd TowardNegInf x_lo y_lo), Rounded (roundedAdd TowardInf x_hi y_hi))
intervalSub :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
\x_lo x_hi y_lo y_hi -> intervalSub (Rounded x_lo) (Rounded x_hi) (Rounded y_lo) (Rounded y_hi) == (Rounded (roundedSub TowardNegInf x_lo y_hi), Rounded (roundedSub TowardInf x_hi y_lo))
intervalMul :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
intervalMulAdd :: Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> Rounded 'TowardNegInf a -> Rounded 'TowardInf a -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
intervalFromInteger :: Integer -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a) Source #
backendNameT :: Tagged a String Source #
Instances
backendName :: RoundedRing a => proxy a -> String Source #
Returns the name of backend as a string.
Example:
>>> :m + Data.Proxy
>>> backendName (Proxy :: Proxy Double)
"FastFFI+SSE2"
data RoundingMode Source #
The type for IEEE754 rounding-direction attributes.
Constructors
| ToNearest | Round to the nearest value (IEEE754 roundTiesToEven) | 
| TowardNegInf | Round downward (IEEE754 roundTowardNegative) | 
| TowardInf | Round upward (IEEE754 roundTowardPositive) | 
| TowardZero | Round toward zero (IEEE754 roundTowardZero) | 
Instances
oppositeRoundingMode :: RoundingMode -> RoundingMode Source #
Returns the opposite rounding direction.
TowardNegInf and TowardInf are swapped.
class Rounding (r :: RoundingMode) Source #
This class allows you to recover the runtime value from a type-level rounding mode.
See rounding.
Minimal complete definition
roundingT
Instances
| Rounding 'ToNearest Source # | |
| Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
| Rounding 'TowardNegInf Source # | |
| Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
| Rounding 'TowardInf Source # | |
| Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
| Rounding 'TowardZero Source # | |
| Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
rounding :: Rounding r => proxy r -> RoundingMode Source #
Recovers the value from type-level rounding mode.
reifyRounding :: RoundingMode -> (forall s. Rounding s => Proxy s -> a) -> a Source #
Lifts a rounding mode to type-level.
newtype Rounded (r :: RoundingMode) a Source #
A type tagged with a rounding direction.
The rounding direction is effective for a single operation.
 You won't get the correctly-rounded result for a compound expression like (a - b * c) :: Rounded 'TowardInf Double.
In particular, a negative literal like -0.1 :: Rounded r Double doesn't yield the correctly-rounded value for -0.1.
 To get the correct value, call fromRational explicitly (i.e. fromRational (-0.1) :: Rounded r Double) or use NegativeLiterals extension.
Constructors
| Rounded | |
| Fields 
 | |