Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- countTrailingZerosInteger :: Integer -> Int
- 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 :: Type
- data family Vector a :: Type
- class Functor f => Result f where
- newtype Exactness a = Exactness {
- getExactness :: Bool
- newtype DynamicRoundingMode a = DynamicRoundingMode {
- withRoundingMode :: RoundingMode -> a
- newtype OppositeRoundingMode f a = OppositeRoundingMode {
- withOppositeRoundingMode :: f a
- nextUp :: RealFloat a => a -> a
- nextDown :: RealFloat a => a -> a
- nextTowardZero :: RealFloat a => a -> a
- minPositive_ieee :: RealFloat a => a
- maxFinite_ieee :: RealFloat a => a
- distanceUlp :: RealFloat a => a -> a -> Maybe Integer
- fusedMultiplyAdd :: RealFloat a => a -> a -> a -> a
- fromInt :: RealFloat a => RoundingMode -> Integer -> a
- fromIntF :: forall a f. (RealFloat a, Result f) => Integer -> f a
- intervalFromInteger_default :: RealFloat a => Integer -> (Rounded TowardNegInf a, Rounded TowardInf a)
- fromRatio :: RealFloat a => RoundingMode -> Integer -> Integer -> a
- fromRatioF :: forall a f. (RealFloat a, Result f) => Integer -> Integer -> f 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 :: Type
- data family Vector a :: Type
Documentation
>>>
import Data.Int
countTrailingZerosInteger :: Integer -> Int Source #
\x -> x == 0 || countTrailingZerosInteger (fromIntegral x) == countTrailingZeros (x :: Int64)
>>>
countTrailingZerosInteger 7
0>>>
countTrailingZerosInteger 8
3
binaryFloatToDecimalDigitsRn Source #
:: 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 #
:: 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.
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
.
roundingT
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.
Rounded | |
|
Instances
data family MVector s a :: Type #
Instances
data family Vector a :: Type #
Instances
class Functor f => Result f where Source #
Instances
Result DynamicRoundingMode Source # | |
Defined in Numeric.Rounded.Hardware.Internal.RoundedResult exact :: a -> DynamicRoundingMode a Source # inexact :: a -> a -> a -> a -> DynamicRoundingMode a Source # | |
Result Exactness Source # | |
Rounding r => Result (Rounded r) Source # | |
Result f => Result (OppositeRoundingMode f) Source # | |
Defined in Numeric.Rounded.Hardware.Internal.RoundedResult exact :: a -> OppositeRoundingMode f a Source # inexact :: a -> a -> a -> a -> OppositeRoundingMode f a Source # | |
(Result f, Result g) => Result (Product f g) Source # | |
Instances
Functor Exactness Source # | |
Result Exactness Source # | |
Eq (Exactness a) Source # | |
Ord (Exactness a) Source # | |
Show (Exactness a) Source # | |
newtype DynamicRoundingMode a Source #
Instances
Functor DynamicRoundingMode Source # | |
Defined in Numeric.Rounded.Hardware.Internal.RoundedResult fmap :: (a -> b) -> DynamicRoundingMode a -> DynamicRoundingMode b # (<$) :: a -> DynamicRoundingMode b -> DynamicRoundingMode a # | |
Result DynamicRoundingMode Source # | |
Defined in Numeric.Rounded.Hardware.Internal.RoundedResult exact :: a -> DynamicRoundingMode a Source # inexact :: a -> a -> a -> a -> DynamicRoundingMode a Source # |
newtype OppositeRoundingMode f a Source #
Instances
nextUp :: RealFloat a => a -> a Source #
nextUp 1 == (0x1.0000_0000_0000_1p0 :: Double)
nextUp 1 == (0x1.000002p0 :: Float)
nextUp (1/0) == (1/0 :: Double)
nextUp (-1/0) == (- maxFinite_ieee :: Double)
nextUp 0 == (0x1p-1074 :: Double)
nextUp (-0) == (0x1p-1074 :: Double)
nextUp (-0x1p-1074) == (-0 :: Double)
isNegativeZero (nextUp (-0x1p-1074) :: Double)
nextDown :: RealFloat a => a -> a Source #
nextDown 1 == (0x1.ffff_ffff_ffff_fp-1 :: Double)
nextDown 1 == (0x1.fffffep-1 :: Float)
nextDown (1/0) == (maxFinite_ieee :: Double)
nextDown (-1/0) == (-1/0 :: Double)
nextDown 0 == (-0x1p-1074 :: Double)
nextDown (-0) == (-0x1p-1074 :: Double)
nextDown 0x1p-1074 == (0 :: Double)
nextTowardZero :: RealFloat a => a -> a Source #
nextTowardZero 1 == (0x1.ffff_ffff_ffff_fp-1 :: Double)
nextTowardZero 1 == (0x1.fffffep-1 :: Float)
nextTowardZero (1/0) == (maxFinite_ieee :: Double)
nextTowardZero (-1/0) == (-maxFinite_ieee :: Double)
nextTowardZero 0 == (0 :: Double)
isNegativeZero (nextTowardZero (-0 :: Double))
nextTowardZero 0x1p-1074 == (0 :: Double)
minPositive_ieee :: RealFloat a => a Source #
(minPositive_ieee :: Double) == 0x1p-1074
(minPositive_ieee :: Float) == 0x1p-149
maxFinite_ieee :: RealFloat a => a Source #
(maxFinite_ieee :: Double) == 0x1.ffff_ffff_ffff_fp+1023
(maxFinite_ieee :: Float) == 0x1.fffffep+127
fusedMultiplyAdd :: RealFloat a => a -> a -> a -> a Source #
intervalFromInteger_default :: RealFloat a => Integer -> (Rounded TowardNegInf a, Rounded TowardInf a) Source #
intervalFromRational_default :: RealFloat a => Rational -> (Rounded TowardNegInf a, Rounded TowardInf a) Source #
class RealFloatConstants a where Source #
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
Nothing
map_roundedSqrt :: RoundingMode -> vector a -> vector a Source #
Equivalent to map .
roundedSqrt
map_roundedSqrt :: Vector vector a => RoundingMode -> vector a -> vector a Source #
Equivalent to map .
roundedSqrt
Instances
class (RoundedFractional a, RoundedRing_Vector vector a) => RoundedFractional_Vector vector a where Source #
Lifted version of RoundedFractional
Nothing
zipWith_roundedDiv :: RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith .
roundedDiv
zipWith_roundedDiv :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith .
roundedDiv
Instances
class RoundedRing a => RoundedRing_Vector vector a where Source #
Lifted version of RoundedRing
Nothing
roundedSum :: RoundingMode -> vector a -> a Source #
Equivalent to \r -> foldl (
roundedAdd
r) 0
zipWith_roundedAdd :: RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith .
roundedAdd
zipWith_roundedSub :: RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith .
roundedSub
zipWith_roundedMul :: RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith .
roundedMul
zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> vector a -> vector a -> vector a -> vector a Source #
Equivalent to zipWith3 .
roundedFusedMultiplyAdd
roundedSum :: (Vector vector a, Num a) => RoundingMode -> vector a -> a Source #
Equivalent to \r -> foldl (
roundedAdd
r) 0
zipWith_roundedAdd :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith .
roundedAdd
zipWith_roundedSub :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith .
roundedSub
zipWith_roundedMul :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #
Equivalent to zipWith .
roundedMul
zipWith3_roundedFusedMultiplyAdd :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a -> vector a Source #
Equivalent to zipWith3 .
roundedFusedMultiplyAdd
Instances
class RoundedRing a => RoundedSqrt a where Source #
Rounding-controlled version of sqrt
.
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
.
roundedDiv :: RoundingMode -> a -> a -> a Source #
roundedRecip :: RoundingMode -> a -> a Source #
roundedRecip :: Num a => RoundingMode -> a -> a Source #
roundedFromRational :: RoundingMode -> Rational -> a Source #
roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> a Source #
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
.
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 #
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.
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
.
roundingT
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.
Rounded | |
|
Instances
data family MVector s a :: Type #
Instances
data family Vector a :: Type #