| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Numeric.Rounded.Hardware.Internal
Synopsis
- 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
- nextUp :: RealFloat a => a -> a
- nextDown :: RealFloat a => a -> a
- nextTowardZero :: RealFloat a => a -> a
- fusedMultiplyAdd :: RealFloat a => a -> a -> a -> a
- backendName :: RoundedRing a => proxy a -> String
- newtype Rounded (r :: RoundingMode) a = Rounded {
- getRounded :: a
- data RoundingMode
- class Rounding (r :: RoundingMode)
- 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
- 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 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 => RoundedRing_Vector (vector :: Type -> Type) 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 (RoundedFractional a, RoundedRing_Vector vector a) => RoundedFractional_Vector (vector :: Type -> Type) a where
- zipWith_roundedDiv :: RoundingMode -> vector a -> vector a -> vector a
- class (RoundedSqrt a, RoundedRing_Vector vector a) => RoundedSqrt_Vector (vector :: Type -> Type) a where
- map_roundedSqrt :: RoundingMode -> vector a -> vector a
- oppositeRoundingMode :: RoundingMode -> RoundingMode
- rounding :: forall (r :: RoundingMode) proxy. Rounding r => proxy r -> RoundingMode
- reifyRounding :: RoundingMode -> (forall (s :: RoundingMode). Rounding s => Proxy s -> a) -> a
- data family MVector s a
- data family Vector 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)
- distanceUlp :: RealFloat a => a -> a -> Maybe Integer
- binaryFloatToDecimalDigitsRn :: RealFloat a => RoundingMode -> Int -> a -> ([Int], Int)
- binaryFloatToFixedDecimalDigitsRn :: 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
Documentation
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
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 #
computes 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)
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"
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
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
| Bounded RoundingMode Source # | |||||
Defined in Numeric.Rounded.Hardware.Internal.Rounding | |||||
| Enum RoundingMode Source # | |||||
Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods succ :: RoundingMode -> RoundingMode # pred :: RoundingMode -> RoundingMode # toEnum :: Int -> RoundingMode # fromEnum :: RoundingMode -> Int # enumFrom :: RoundingMode -> [RoundingMode] # enumFromThen :: RoundingMode -> RoundingMode -> [RoundingMode] # enumFromTo :: RoundingMode -> RoundingMode -> [RoundingMode] # enumFromThenTo :: RoundingMode -> RoundingMode -> RoundingMode -> [RoundingMode] # | |||||
| Generic RoundingMode Source # | |||||
Defined in Numeric.Rounded.Hardware.Internal.Rounding Associated Types
| |||||
| Read RoundingMode Source # | |||||
Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods readsPrec :: Int -> ReadS RoundingMode # readList :: ReadS [RoundingMode] # | |||||
| Show RoundingMode Source # | |||||
Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods showsPrec :: Int -> RoundingMode -> ShowS # show :: RoundingMode -> String # showList :: [RoundingMode] -> ShowS # | |||||
| NFData RoundingMode Source # | |||||
Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods rnf :: RoundingMode -> () # | |||||
| Eq RoundingMode Source # | |||||
Defined in Numeric.Rounded.Hardware.Internal.Rounding | |||||
| Ord RoundingMode Source # | |||||
Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods compare :: RoundingMode -> RoundingMode -> Ordering # (<) :: RoundingMode -> RoundingMode -> Bool # (<=) :: RoundingMode -> RoundingMode -> Bool # (>) :: RoundingMode -> RoundingMode -> Bool # (>=) :: RoundingMode -> RoundingMode -> Bool # max :: RoundingMode -> RoundingMode -> RoundingMode # min :: RoundingMode -> RoundingMode -> RoundingMode # | |||||
| type Rep RoundingMode Source # | |||||
Defined in Numeric.Rounded.Hardware.Internal.Rounding type Rep RoundingMode = D1 ('MetaData "RoundingMode" "Numeric.Rounded.Hardware.Internal.Rounding" "rounded-hw-0.4.0.2-8N1qAeGOePG57F1jKA4niW" 'False) ((C1 ('MetaCons "ToNearest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TowardNegInf" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TowardInf" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TowardZero" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
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 'TowardInf Source # | |
Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
| Rounding 'TowardNegInf Source # | |
Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
| Rounding 'TowardZero Source # | |
Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods | |
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
| RoundedRing CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedAdd :: RoundingMode -> CDouble -> CDouble -> CDouble Source # roundedSub :: RoundingMode -> CDouble -> CDouble -> CDouble Source # roundedMul :: RoundingMode -> CDouble -> CDouble -> CDouble Source # roundedFusedMultiplyAdd :: RoundingMode -> CDouble -> CDouble -> CDouble -> CDouble Source # roundedFromInteger :: RoundingMode -> Integer -> CDouble Source # intervalAdd :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalSub :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalMul :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalMulAdd :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalFromInteger :: Integer -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # | |
| RoundedRing CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedAdd :: RoundingMode -> CFloat -> CFloat -> CFloat Source # roundedSub :: RoundingMode -> CFloat -> CFloat -> CFloat Source # roundedMul :: RoundingMode -> CFloat -> CFloat -> CFloat Source # roundedFusedMultiplyAdd :: RoundingMode -> CFloat -> CFloat -> CFloat -> CFloat Source # roundedFromInteger :: RoundingMode -> Integer -> CFloat Source # intervalAdd :: Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat) Source # intervalSub :: Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat) Source # intervalMul :: Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat) Source # intervalMulAdd :: Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat) Source # intervalFromInteger :: Integer -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat) Source # | |
| RoundedRing CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods roundedAdd :: RoundingMode -> CDouble -> CDouble -> CDouble Source # roundedSub :: RoundingMode -> CDouble -> CDouble -> CDouble Source # roundedMul :: RoundingMode -> CDouble -> CDouble -> CDouble Source # roundedFusedMultiplyAdd :: RoundingMode -> CDouble -> CDouble -> CDouble -> CDouble Source # roundedFromInteger :: RoundingMode -> Integer -> CDouble Source # intervalAdd :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalSub :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalMul :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalMulAdd :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalFromInteger :: Integer -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # | |
| RoundedRing Integer Source # | |
Defined in Numeric.Rounded.Hardware.Internal.Class Methods roundedAdd :: RoundingMode -> Integer -> Integer -> Integer Source # roundedSub :: RoundingMode -> Integer -> Integer -> Integer Source # roundedMul :: RoundingMode -> Integer -> Integer -> Integer Source # roundedFusedMultiplyAdd :: RoundingMode -> Integer -> Integer -> Integer -> Integer Source # roundedFromInteger :: RoundingMode -> Integer -> Integer Source # intervalAdd :: Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> (Rounded 'TowardNegInf Integer, Rounded 'TowardInf Integer) Source # intervalSub :: Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> (Rounded 'TowardNegInf Integer, Rounded 'TowardInf Integer) Source # intervalMul :: Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> (Rounded 'TowardNegInf Integer, Rounded 'TowardInf Integer) Source # intervalMulAdd :: Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> (Rounded 'TowardNegInf Integer, Rounded 'TowardInf Integer) Source # intervalFromInteger :: Integer -> (Rounded 'TowardNegInf Integer, Rounded 'TowardInf Integer) Source # | |
| RoundedRing Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedAdd :: RoundingMode -> Double -> Double -> Double Source # roundedSub :: RoundingMode -> Double -> Double -> Double Source # roundedMul :: RoundingMode -> Double -> Double -> Double Source # roundedFusedMultiplyAdd :: RoundingMode -> Double -> Double -> Double -> Double Source # roundedFromInteger :: RoundingMode -> Integer -> Double Source # intervalAdd :: Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) Source # intervalSub :: Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) Source # intervalMul :: Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) Source # intervalMulAdd :: Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) Source # intervalFromInteger :: Integer -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) Source # | |
| RoundedRing Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedAdd :: RoundingMode -> Float -> Float -> Float Source # roundedSub :: RoundingMode -> Float -> Float -> Float Source # roundedMul :: RoundingMode -> Float -> Float -> Float Source # roundedFusedMultiplyAdd :: RoundingMode -> Float -> Float -> Float -> Float Source # roundedFromInteger :: RoundingMode -> Integer -> Float Source # intervalAdd :: Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) Source # intervalSub :: Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) Source # intervalMul :: Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) Source # intervalMulAdd :: Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) Source # intervalFromInteger :: Integer -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) Source # | |
| Integral a => RoundedRing (Ratio a) Source # | |
Defined in Numeric.Rounded.Hardware.Internal.Class Methods roundedAdd :: RoundingMode -> Ratio a -> Ratio a -> Ratio a Source # roundedSub :: RoundingMode -> Ratio a -> Ratio a -> Ratio a Source # roundedMul :: RoundingMode -> Ratio a -> Ratio a -> Ratio a Source # roundedFusedMultiplyAdd :: RoundingMode -> Ratio a -> Ratio a -> Ratio a -> Ratio a Source # roundedFromInteger :: RoundingMode -> Integer -> Ratio a Source # intervalAdd :: Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> (Rounded 'TowardNegInf (Ratio a), Rounded 'TowardInf (Ratio a)) Source # intervalSub :: Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> (Rounded 'TowardNegInf (Ratio a), Rounded 'TowardInf (Ratio a)) Source # intervalMul :: Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> (Rounded 'TowardNegInf (Ratio a), Rounded 'TowardInf (Ratio a)) Source # intervalMulAdd :: Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> (Rounded 'TowardNegInf (Ratio a), Rounded 'TowardInf (Ratio a)) Source # intervalFromInteger :: Integer -> (Rounded 'TowardNegInf (Ratio a), Rounded 'TowardInf (Ratio a)) Source # | |
| (RealFloat a, Num a, RealFloatConstants a) => RoundedRing (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods roundedAdd :: RoundingMode -> ViaRational a -> ViaRational a -> ViaRational a Source # roundedSub :: RoundingMode -> ViaRational a -> ViaRational a -> ViaRational a Source # roundedMul :: RoundingMode -> ViaRational a -> ViaRational a -> ViaRational a Source # roundedFusedMultiplyAdd :: RoundingMode -> ViaRational a -> ViaRational a -> ViaRational a -> ViaRational a Source # roundedFromInteger :: RoundingMode -> Integer -> ViaRational a Source # intervalAdd :: Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> (Rounded 'TowardNegInf (ViaRational a), Rounded 'TowardInf (ViaRational a)) Source # intervalSub :: Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> (Rounded 'TowardNegInf (ViaRational a), Rounded 'TowardInf (ViaRational a)) Source # intervalMul :: Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> (Rounded 'TowardNegInf (ViaRational a), Rounded 'TowardInf (ViaRational a)) Source # intervalMulAdd :: Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> (Rounded 'TowardNegInf (ViaRational a), Rounded 'TowardInf (ViaRational a)) Source # intervalFromInteger :: Integer -> (Rounded 'TowardNegInf (ViaRational a), Rounded 'TowardInf (ViaRational a)) Source # backendNameT :: Tagged (ViaRational a) String Source # | |
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
| RoundedFractional CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedDiv :: RoundingMode -> CDouble -> CDouble -> CDouble Source # roundedRecip :: RoundingMode -> CDouble -> CDouble Source # roundedFromRational :: RoundingMode -> Rational -> CDouble Source # roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> CDouble Source # intervalDiv :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalDivAdd :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalRecip :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalFromRational :: Rational -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # | |
| RoundedFractional CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedDiv :: RoundingMode -> CFloat -> CFloat -> CFloat Source # roundedRecip :: RoundingMode -> CFloat -> CFloat Source # roundedFromRational :: RoundingMode -> Rational -> CFloat Source # roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> CFloat Source # intervalDiv :: Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat) Source # intervalDivAdd :: Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat) Source # intervalRecip :: Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat) Source # intervalFromRational :: Rational -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat) Source # | |
| RoundedFractional CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods roundedDiv :: RoundingMode -> CDouble -> CDouble -> CDouble Source # roundedRecip :: RoundingMode -> CDouble -> CDouble Source # roundedFromRational :: RoundingMode -> Rational -> CDouble Source # roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> CDouble Source # intervalDiv :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalDivAdd :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalRecip :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # intervalFromRational :: Rational -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # | |
| RoundedFractional Integer Source # | |
Defined in Numeric.Rounded.Hardware.Internal.Class Methods roundedDiv :: RoundingMode -> Integer -> Integer -> Integer Source # roundedRecip :: RoundingMode -> Integer -> Integer Source # roundedFromRational :: RoundingMode -> Rational -> Integer Source # roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> Integer Source # intervalDiv :: Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> (Rounded 'TowardNegInf Integer, Rounded 'TowardInf Integer) Source # intervalDivAdd :: Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> (Rounded 'TowardNegInf Integer, Rounded 'TowardInf Integer) Source # intervalRecip :: Rounded 'TowardNegInf Integer -> Rounded 'TowardInf Integer -> (Rounded 'TowardNegInf Integer, Rounded 'TowardInf Integer) Source # intervalFromRational :: Rational -> (Rounded 'TowardNegInf Integer, Rounded 'TowardInf Integer) Source # | |
| RoundedFractional Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedDiv :: RoundingMode -> Double -> Double -> Double Source # roundedRecip :: RoundingMode -> Double -> Double Source # roundedFromRational :: RoundingMode -> Rational -> Double Source # roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> Double Source # intervalDiv :: Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) Source # intervalDivAdd :: Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) Source # intervalRecip :: Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) Source # intervalFromRational :: Rational -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) Source # | |
| RoundedFractional Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedDiv :: RoundingMode -> Float -> Float -> Float Source # roundedRecip :: RoundingMode -> Float -> Float Source # roundedFromRational :: RoundingMode -> Rational -> Float Source # roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> Float Source # intervalDiv :: Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) Source # intervalDivAdd :: Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) Source # intervalRecip :: Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) Source # intervalFromRational :: Rational -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) Source # | |
| Integral a => RoundedFractional (Ratio a) Source # | |
Defined in Numeric.Rounded.Hardware.Internal.Class Methods roundedDiv :: RoundingMode -> Ratio a -> Ratio a -> Ratio a Source # roundedRecip :: RoundingMode -> Ratio a -> Ratio a Source # roundedFromRational :: RoundingMode -> Rational -> Ratio a Source # roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> Ratio a Source # intervalDiv :: Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> (Rounded 'TowardNegInf (Ratio a), Rounded 'TowardInf (Ratio a)) Source # intervalDivAdd :: Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> (Rounded 'TowardNegInf (Ratio a), Rounded 'TowardInf (Ratio a)) Source # intervalRecip :: Rounded 'TowardNegInf (Ratio a) -> Rounded 'TowardInf (Ratio a) -> (Rounded 'TowardNegInf (Ratio a), Rounded 'TowardInf (Ratio a)) Source # intervalFromRational :: Rational -> (Rounded 'TowardNegInf (Ratio a), Rounded 'TowardInf (Ratio a)) Source # | |
| (RealFloat a, Num a, RealFloatConstants a) => RoundedFractional (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods roundedDiv :: RoundingMode -> ViaRational a -> ViaRational a -> ViaRational a Source # roundedRecip :: RoundingMode -> ViaRational a -> ViaRational a Source # roundedFromRational :: RoundingMode -> Rational -> ViaRational a Source # roundedFromRealFloat :: RealFloat b => RoundingMode -> b -> ViaRational a Source # intervalDiv :: Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> (Rounded 'TowardNegInf (ViaRational a), Rounded 'TowardInf (ViaRational a)) Source # intervalDivAdd :: Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> (Rounded 'TowardNegInf (ViaRational a), Rounded 'TowardInf (ViaRational a)) Source # intervalRecip :: Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> (Rounded 'TowardNegInf (ViaRational a), Rounded 'TowardInf (ViaRational a)) Source # intervalFromRational :: Rational -> (Rounded 'TowardNegInf (ViaRational a), Rounded 'TowardInf (ViaRational a)) Source # | |
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
| RoundedSqrt CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedSqrt :: RoundingMode -> CDouble -> CDouble Source # intervalSqrt :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # | |
| RoundedSqrt CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedSqrt :: RoundingMode -> CFloat -> CFloat Source # intervalSqrt :: Rounded 'TowardNegInf CFloat -> Rounded 'TowardInf CFloat -> (Rounded 'TowardNegInf CFloat, Rounded 'TowardInf CFloat) Source # | |
| RoundedSqrt CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods roundedSqrt :: RoundingMode -> CDouble -> CDouble Source # intervalSqrt :: Rounded 'TowardNegInf CDouble -> Rounded 'TowardInf CDouble -> (Rounded 'TowardNegInf CDouble, Rounded 'TowardInf CDouble) Source # | |
| RoundedSqrt Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedSqrt :: RoundingMode -> Double -> Double Source # intervalSqrt :: Rounded 'TowardNegInf Double -> Rounded 'TowardInf Double -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) Source # | |
| RoundedSqrt Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedSqrt :: RoundingMode -> Float -> Float Source # intervalSqrt :: Rounded 'TowardNegInf Float -> Rounded 'TowardInf Float -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) Source # | |
| (RealFloat a, RealFloatConstants a) => RoundedSqrt (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods roundedSqrt :: RoundingMode -> ViaRational a -> ViaRational a Source # intervalSqrt :: Rounded 'TowardNegInf (ViaRational a) -> Rounded 'TowardInf (ViaRational a) -> (Rounded 'TowardNegInf (ViaRational a), Rounded 'TowardInf (ViaRational a)) Source # | |
class RoundedRing a => RoundedRing_Vector (vector :: Type -> Type) 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
| RoundedRing_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedSum :: RoundingMode -> Vector CDouble -> CDouble Source # zipWith_roundedAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedSub :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedMul :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedRing_Vector Vector CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedSum :: RoundingMode -> Vector CFloat -> CFloat Source # zipWith_roundedAdd :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # zipWith_roundedSub :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # zipWith_roundedMul :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # | |
| RoundedRing_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods roundedSum :: RoundingMode -> Vector CDouble -> CDouble Source # zipWith_roundedAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedSub :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedMul :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedRing_Vector Vector Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedSum :: RoundingMode -> Vector Double -> Double Source # zipWith_roundedAdd :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # zipWith_roundedSub :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # zipWith_roundedMul :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector Double -> Vector Double -> Vector Double -> Vector Double Source # | |
| RoundedRing_Vector Vector Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedSum :: RoundingMode -> Vector Float -> Float Source # zipWith_roundedAdd :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # zipWith_roundedSub :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # zipWith_roundedMul :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector Float -> Vector Float -> Vector Float -> Vector Float Source # | |
| RoundedRing_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedSum :: RoundingMode -> Vector CDouble -> CDouble Source # zipWith_roundedAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedSub :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedMul :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedRing_Vector Vector CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedSum :: RoundingMode -> Vector CFloat -> CFloat Source # zipWith_roundedAdd :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # zipWith_roundedSub :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # zipWith_roundedMul :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # | |
| RoundedRing_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods roundedSum :: RoundingMode -> Vector CDouble -> CDouble Source # zipWith_roundedAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedSub :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedMul :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedRing_Vector Vector Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedSum :: RoundingMode -> Vector Double -> Double Source # zipWith_roundedAdd :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # zipWith_roundedSub :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # zipWith_roundedMul :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector Double -> Vector Double -> Vector Double -> Vector Double Source # | |
| RoundedRing_Vector Vector Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedSum :: RoundingMode -> Vector Float -> Float Source # zipWith_roundedAdd :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # zipWith_roundedSub :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # zipWith_roundedMul :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector Float -> Vector Float -> Vector Float -> Vector Float Source # | |
| (RealFloat a, RealFloatConstants a, Storable a) => RoundedRing_Vector Vector (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods roundedSum :: RoundingMode -> Vector (ViaRational a) -> ViaRational a Source # zipWith_roundedAdd :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # zipWith_roundedSub :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # zipWith_roundedMul :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # | |
| (RealFloat a, RealFloatConstants a, Unbox a) => RoundedRing_Vector Vector (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods roundedSum :: RoundingMode -> Vector (ViaRational a) -> ViaRational a Source # zipWith_roundedAdd :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # zipWith_roundedSub :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # zipWith_roundedMul :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # | |
class (RoundedFractional a, RoundedRing_Vector vector a) => RoundedFractional_Vector (vector :: Type -> Type) 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
| RoundedFractional_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods zipWith_roundedDiv :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedFractional_Vector Vector CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods zipWith_roundedDiv :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # | |
| RoundedFractional_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods zipWith_roundedDiv :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedFractional_Vector Vector Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods zipWith_roundedDiv :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # | |
| RoundedFractional_Vector Vector Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods zipWith_roundedDiv :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # | |
| RoundedFractional_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods zipWith_roundedDiv :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedFractional_Vector Vector CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods zipWith_roundedDiv :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # | |
| RoundedFractional_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods zipWith_roundedDiv :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedFractional_Vector Vector Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods zipWith_roundedDiv :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # | |
| RoundedFractional_Vector Vector Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods zipWith_roundedDiv :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # | |
| (RealFloat a, RealFloatConstants a, Storable a) => RoundedFractional_Vector Vector (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods zipWith_roundedDiv :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # | |
| (RealFloat a, RealFloatConstants a, Unbox a) => RoundedFractional_Vector Vector (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods zipWith_roundedDiv :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # | |
class (RoundedSqrt a, RoundedRing_Vector vector a) => RoundedSqrt_Vector (vector :: Type -> Type) 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
| RoundedSqrt_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods map_roundedSqrt :: RoundingMode -> Vector CDouble -> Vector CDouble Source # | |
| RoundedSqrt_Vector Vector CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods map_roundedSqrt :: RoundingMode -> Vector CFloat -> Vector CFloat Source # | |
| RoundedSqrt_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods map_roundedSqrt :: RoundingMode -> Vector CDouble -> Vector CDouble Source # | |
| RoundedSqrt_Vector Vector Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods map_roundedSqrt :: RoundingMode -> Vector Double -> Vector Double Source # | |
| RoundedSqrt_Vector Vector Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods map_roundedSqrt :: RoundingMode -> Vector Float -> Vector Float Source # | |
| RoundedSqrt_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods map_roundedSqrt :: RoundingMode -> Vector CDouble -> Vector CDouble Source # | |
| RoundedSqrt_Vector Vector CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods map_roundedSqrt :: RoundingMode -> Vector CFloat -> Vector CFloat Source # | |
| RoundedSqrt_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods map_roundedSqrt :: RoundingMode -> Vector CDouble -> Vector CDouble Source # | |
| RoundedSqrt_Vector Vector Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods map_roundedSqrt :: RoundingMode -> Vector Double -> Vector Double Source # | |
| RoundedSqrt_Vector Vector Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods map_roundedSqrt :: RoundingMode -> Vector Float -> Vector Float Source # | |
| (RealFloat a, RealFloatConstants a, Storable a) => RoundedSqrt_Vector Vector (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods map_roundedSqrt :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) Source # | |
| (RealFloat a, RealFloatConstants a, Unbox a) => RoundedSqrt_Vector Vector (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods map_roundedSqrt :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) Source # | |
oppositeRoundingMode :: RoundingMode -> RoundingMode Source #
Returns the opposite rounding direction.
TowardNegInf and TowardInf are swapped.
rounding :: forall (r :: RoundingMode) proxy. Rounding r => proxy r -> RoundingMode Source #
Recovers the value from type-level rounding mode.
reifyRounding :: RoundingMode -> (forall (s :: RoundingMode). Rounding s => Proxy s -> a) -> a Source #
Lifts a rounding mode to type-level.
Instances
| MVector MVector All | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s All -> Int basicUnsafeSlice :: Int -> Int -> MVector s All -> MVector s All basicOverlaps :: MVector s All -> MVector s All -> Bool basicUnsafeNew :: Int -> ST s (MVector s All) basicInitialize :: MVector s All -> ST s () basicUnsafeReplicate :: Int -> All -> ST s (MVector s All) basicUnsafeRead :: MVector s All -> Int -> ST s All basicUnsafeWrite :: MVector s All -> Int -> All -> ST s () basicClear :: MVector s All -> ST s () basicSet :: MVector s All -> All -> ST s () basicUnsafeCopy :: MVector s All -> MVector s All -> ST s () basicUnsafeMove :: MVector s All -> MVector s All -> ST s () basicUnsafeGrow :: MVector s All -> Int -> ST s (MVector s All) | |
| MVector MVector Any | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Any -> Int basicUnsafeSlice :: Int -> Int -> MVector s Any -> MVector s Any basicOverlaps :: MVector s Any -> MVector s Any -> Bool basicUnsafeNew :: Int -> ST s (MVector s Any) basicInitialize :: MVector s Any -> ST s () basicUnsafeReplicate :: Int -> Any -> ST s (MVector s Any) basicUnsafeRead :: MVector s Any -> Int -> ST s Any basicUnsafeWrite :: MVector s Any -> Int -> Any -> ST s () basicClear :: MVector s Any -> ST s () basicSet :: MVector s Any -> Any -> ST s () basicUnsafeCopy :: MVector s Any -> MVector s Any -> ST s () basicUnsafeMove :: MVector s Any -> MVector s Any -> ST s () basicUnsafeGrow :: MVector s Any -> Int -> ST s (MVector s Any) | |
| MVector MVector Int16 | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Int16 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Int16 -> MVector s Int16 basicOverlaps :: MVector s Int16 -> MVector s Int16 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Int16) basicInitialize :: MVector s Int16 -> ST s () basicUnsafeReplicate :: Int -> Int16 -> ST s (MVector s Int16) basicUnsafeRead :: MVector s Int16 -> Int -> ST s Int16 basicUnsafeWrite :: MVector s Int16 -> Int -> Int16 -> ST s () basicClear :: MVector s Int16 -> ST s () basicSet :: MVector s Int16 -> Int16 -> ST s () basicUnsafeCopy :: MVector s Int16 -> MVector s Int16 -> ST s () basicUnsafeMove :: MVector s Int16 -> MVector s Int16 -> ST s () basicUnsafeGrow :: MVector s Int16 -> Int -> ST s (MVector s Int16) | |
| MVector MVector Int32 | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Int32 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Int32 -> MVector s Int32 basicOverlaps :: MVector s Int32 -> MVector s Int32 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Int32) basicInitialize :: MVector s Int32 -> ST s () basicUnsafeReplicate :: Int -> Int32 -> ST s (MVector s Int32) basicUnsafeRead :: MVector s Int32 -> Int -> ST s Int32 basicUnsafeWrite :: MVector s Int32 -> Int -> Int32 -> ST s () basicClear :: MVector s Int32 -> ST s () basicSet :: MVector s Int32 -> Int32 -> ST s () basicUnsafeCopy :: MVector s Int32 -> MVector s Int32 -> ST s () basicUnsafeMove :: MVector s Int32 -> MVector s Int32 -> ST s () basicUnsafeGrow :: MVector s Int32 -> Int -> ST s (MVector s Int32) | |
| MVector MVector Int64 | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Int64 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Int64 -> MVector s Int64 basicOverlaps :: MVector s Int64 -> MVector s Int64 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Int64) basicInitialize :: MVector s Int64 -> ST s () basicUnsafeReplicate :: Int -> Int64 -> ST s (MVector s Int64) basicUnsafeRead :: MVector s Int64 -> Int -> ST s Int64 basicUnsafeWrite :: MVector s Int64 -> Int -> Int64 -> ST s () basicClear :: MVector s Int64 -> ST s () basicSet :: MVector s Int64 -> Int64 -> ST s () basicUnsafeCopy :: MVector s Int64 -> MVector s Int64 -> ST s () basicUnsafeMove :: MVector s Int64 -> MVector s Int64 -> ST s () basicUnsafeGrow :: MVector s Int64 -> Int -> ST s (MVector s Int64) | |
| MVector MVector Int8 | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Int8 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Int8 -> MVector s Int8 basicOverlaps :: MVector s Int8 -> MVector s Int8 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Int8) basicInitialize :: MVector s Int8 -> ST s () basicUnsafeReplicate :: Int -> Int8 -> ST s (MVector s Int8) basicUnsafeRead :: MVector s Int8 -> Int -> ST s Int8 basicUnsafeWrite :: MVector s Int8 -> Int -> Int8 -> ST s () basicClear :: MVector s Int8 -> ST s () basicSet :: MVector s Int8 -> Int8 -> ST s () basicUnsafeCopy :: MVector s Int8 -> MVector s Int8 -> ST s () basicUnsafeMove :: MVector s Int8 -> MVector s Int8 -> ST s () basicUnsafeGrow :: MVector s Int8 -> Int -> ST s (MVector s Int8) | |
| MVector MVector Word16 | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Word16 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Word16 -> MVector s Word16 basicOverlaps :: MVector s Word16 -> MVector s Word16 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Word16) basicInitialize :: MVector s Word16 -> ST s () basicUnsafeReplicate :: Int -> Word16 -> ST s (MVector s Word16) basicUnsafeRead :: MVector s Word16 -> Int -> ST s Word16 basicUnsafeWrite :: MVector s Word16 -> Int -> Word16 -> ST s () basicClear :: MVector s Word16 -> ST s () basicSet :: MVector s Word16 -> Word16 -> ST s () basicUnsafeCopy :: MVector s Word16 -> MVector s Word16 -> ST s () basicUnsafeMove :: MVector s Word16 -> MVector s Word16 -> ST s () basicUnsafeGrow :: MVector s Word16 -> Int -> ST s (MVector s Word16) | |
| MVector MVector Word32 | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Word32 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Word32 -> MVector s Word32 basicOverlaps :: MVector s Word32 -> MVector s Word32 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Word32) basicInitialize :: MVector s Word32 -> ST s () basicUnsafeReplicate :: Int -> Word32 -> ST s (MVector s Word32) basicUnsafeRead :: MVector s Word32 -> Int -> ST s Word32 basicUnsafeWrite :: MVector s Word32 -> Int -> Word32 -> ST s () basicClear :: MVector s Word32 -> ST s () basicSet :: MVector s Word32 -> Word32 -> ST s () basicUnsafeCopy :: MVector s Word32 -> MVector s Word32 -> ST s () basicUnsafeMove :: MVector s Word32 -> MVector s Word32 -> ST s () basicUnsafeGrow :: MVector s Word32 -> Int -> ST s (MVector s Word32) | |
| MVector MVector Word64 | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Word64 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Word64 -> MVector s Word64 basicOverlaps :: MVector s Word64 -> MVector s Word64 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Word64) basicInitialize :: MVector s Word64 -> ST s () basicUnsafeReplicate :: Int -> Word64 -> ST s (MVector s Word64) basicUnsafeRead :: MVector s Word64 -> Int -> ST s Word64 basicUnsafeWrite :: MVector s Word64 -> Int -> Word64 -> ST s () basicClear :: MVector s Word64 -> ST s () basicSet :: MVector s Word64 -> Word64 -> ST s () basicUnsafeCopy :: MVector s Word64 -> MVector s Word64 -> ST s () basicUnsafeMove :: MVector s Word64 -> MVector s Word64 -> ST s () basicUnsafeGrow :: MVector s Word64 -> Int -> ST s (MVector s Word64) | |
| MVector MVector Word8 | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Word8 -> Int basicUnsafeSlice :: Int -> Int -> MVector s Word8 -> MVector s Word8 basicOverlaps :: MVector s Word8 -> MVector s Word8 -> Bool basicUnsafeNew :: Int -> ST s (MVector s Word8) basicInitialize :: MVector s Word8 -> ST s () basicUnsafeReplicate :: Int -> Word8 -> ST s (MVector s Word8) basicUnsafeRead :: MVector s Word8 -> Int -> ST s Word8 basicUnsafeWrite :: MVector s Word8 -> Int -> Word8 -> ST s () basicClear :: MVector s Word8 -> ST s () basicSet :: MVector s Word8 -> Word8 -> ST s () basicUnsafeCopy :: MVector s Word8 -> MVector s Word8 -> ST s () basicUnsafeMove :: MVector s Word8 -> MVector s Word8 -> ST s () basicUnsafeGrow :: MVector s Word8 -> Int -> ST s (MVector s Word8) | |
| MVector MVector CDouble | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods basicLength :: MVector s CDouble -> Int basicUnsafeSlice :: Int -> Int -> MVector s CDouble -> MVector s CDouble basicOverlaps :: MVector s CDouble -> MVector s CDouble -> Bool basicUnsafeNew :: Int -> ST s (MVector s CDouble) basicInitialize :: MVector s CDouble -> ST s () basicUnsafeReplicate :: Int -> CDouble -> ST s (MVector s CDouble) basicUnsafeRead :: MVector s CDouble -> Int -> ST s CDouble basicUnsafeWrite :: MVector s CDouble -> Int -> CDouble -> ST s () basicClear :: MVector s CDouble -> ST s () basicSet :: MVector s CDouble -> CDouble -> ST s () basicUnsafeCopy :: MVector s CDouble -> MVector s CDouble -> ST s () basicUnsafeMove :: MVector s CDouble -> MVector s CDouble -> ST s () basicUnsafeGrow :: MVector s CDouble -> Int -> ST s (MVector s CDouble) | |
| MVector MVector CFloat | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods basicLength :: MVector s CFloat -> Int basicUnsafeSlice :: Int -> Int -> MVector s CFloat -> MVector s CFloat basicOverlaps :: MVector s CFloat -> MVector s CFloat -> Bool basicUnsafeNew :: Int -> ST s (MVector s CFloat) basicInitialize :: MVector s CFloat -> ST s () basicUnsafeReplicate :: Int -> CFloat -> ST s (MVector s CFloat) basicUnsafeRead :: MVector s CFloat -> Int -> ST s CFloat basicUnsafeWrite :: MVector s CFloat -> Int -> CFloat -> ST s () basicClear :: MVector s CFloat -> ST s () basicSet :: MVector s CFloat -> CFloat -> ST s () basicUnsafeCopy :: MVector s CFloat -> MVector s CFloat -> ST s () basicUnsafeMove :: MVector s CFloat -> MVector s CFloat -> ST s () basicUnsafeGrow :: MVector s CFloat -> Int -> ST s (MVector s CFloat) | |
| MVector MVector CDouble | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods basicLength :: MVector s CDouble -> Int basicUnsafeSlice :: Int -> Int -> MVector s CDouble -> MVector s CDouble basicOverlaps :: MVector s CDouble -> MVector s CDouble -> Bool basicUnsafeNew :: Int -> ST s (MVector s CDouble) basicInitialize :: MVector s CDouble -> ST s () basicUnsafeReplicate :: Int -> CDouble -> ST s (MVector s CDouble) basicUnsafeRead :: MVector s CDouble -> Int -> ST s CDouble basicUnsafeWrite :: MVector s CDouble -> Int -> CDouble -> ST s () basicClear :: MVector s CDouble -> ST s () basicSet :: MVector s CDouble -> CDouble -> ST s () basicUnsafeCopy :: MVector s CDouble -> MVector s CDouble -> ST s () basicUnsafeMove :: MVector s CDouble -> MVector s CDouble -> ST s () basicUnsafeGrow :: MVector s CDouble -> Int -> ST s (MVector s CDouble) | |
| MVector MVector () | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s () -> Int basicUnsafeSlice :: Int -> Int -> MVector s () -> MVector s () basicOverlaps :: MVector s () -> MVector s () -> Bool basicUnsafeNew :: Int -> ST s (MVector s ()) basicInitialize :: MVector s () -> ST s () basicUnsafeReplicate :: Int -> () -> ST s (MVector s ()) basicUnsafeRead :: MVector s () -> Int -> ST s () basicUnsafeWrite :: MVector s () -> Int -> () -> ST s () basicClear :: MVector s () -> ST s () basicSet :: MVector s () -> () -> ST s () basicUnsafeCopy :: MVector s () -> MVector s () -> ST s () basicUnsafeMove :: MVector s () -> MVector s () -> ST s () basicUnsafeGrow :: MVector s () -> Int -> ST s (MVector s ()) | |
| MVector MVector Bool | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Bool -> Int basicUnsafeSlice :: Int -> Int -> MVector s Bool -> MVector s Bool basicOverlaps :: MVector s Bool -> MVector s Bool -> Bool basicUnsafeNew :: Int -> ST s (MVector s Bool) basicInitialize :: MVector s Bool -> ST s () basicUnsafeReplicate :: Int -> Bool -> ST s (MVector s Bool) basicUnsafeRead :: MVector s Bool -> Int -> ST s Bool basicUnsafeWrite :: MVector s Bool -> Int -> Bool -> ST s () basicClear :: MVector s Bool -> ST s () basicSet :: MVector s Bool -> Bool -> ST s () basicUnsafeCopy :: MVector s Bool -> MVector s Bool -> ST s () basicUnsafeMove :: MVector s Bool -> MVector s Bool -> ST s () basicUnsafeGrow :: MVector s Bool -> Int -> ST s (MVector s Bool) | |
| MVector MVector Char | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Char -> Int basicUnsafeSlice :: Int -> Int -> MVector s Char -> MVector s Char basicOverlaps :: MVector s Char -> MVector s Char -> Bool basicUnsafeNew :: Int -> ST s (MVector s Char) basicInitialize :: MVector s Char -> ST s () basicUnsafeReplicate :: Int -> Char -> ST s (MVector s Char) basicUnsafeRead :: MVector s Char -> Int -> ST s Char basicUnsafeWrite :: MVector s Char -> Int -> Char -> ST s () basicClear :: MVector s Char -> ST s () basicSet :: MVector s Char -> Char -> ST s () basicUnsafeCopy :: MVector s Char -> MVector s Char -> ST s () basicUnsafeMove :: MVector s Char -> MVector s Char -> ST s () basicUnsafeGrow :: MVector s Char -> Int -> ST s (MVector s Char) | |
| MVector MVector Double | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Double -> Int basicUnsafeSlice :: Int -> Int -> MVector s Double -> MVector s Double basicOverlaps :: MVector s Double -> MVector s Double -> Bool basicUnsafeNew :: Int -> ST s (MVector s Double) basicInitialize :: MVector s Double -> ST s () basicUnsafeReplicate :: Int -> Double -> ST s (MVector s Double) basicUnsafeRead :: MVector s Double -> Int -> ST s Double basicUnsafeWrite :: MVector s Double -> Int -> Double -> ST s () basicClear :: MVector s Double -> ST s () basicSet :: MVector s Double -> Double -> ST s () basicUnsafeCopy :: MVector s Double -> MVector s Double -> ST s () basicUnsafeMove :: MVector s Double -> MVector s Double -> ST s () basicUnsafeGrow :: MVector s Double -> Int -> ST s (MVector s Double) | |
| MVector MVector Float | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Float -> Int basicUnsafeSlice :: Int -> Int -> MVector s Float -> MVector s Float basicOverlaps :: MVector s Float -> MVector s Float -> Bool basicUnsafeNew :: Int -> ST s (MVector s Float) basicInitialize :: MVector s Float -> ST s () basicUnsafeReplicate :: Int -> Float -> ST s (MVector s Float) basicUnsafeRead :: MVector s Float -> Int -> ST s Float basicUnsafeWrite :: MVector s Float -> Int -> Float -> ST s () basicClear :: MVector s Float -> ST s () basicSet :: MVector s Float -> Float -> ST s () basicUnsafeCopy :: MVector s Float -> MVector s Float -> ST s () basicUnsafeMove :: MVector s Float -> MVector s Float -> ST s () basicUnsafeGrow :: MVector s Float -> Int -> ST s (MVector s Float) | |
| MVector MVector Int | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Int -> Int basicUnsafeSlice :: Int -> Int -> MVector s Int -> MVector s Int basicOverlaps :: MVector s Int -> MVector s Int -> Bool basicUnsafeNew :: Int -> ST s (MVector s Int) basicInitialize :: MVector s Int -> ST s () basicUnsafeReplicate :: Int -> Int -> ST s (MVector s Int) basicUnsafeRead :: MVector s Int -> Int -> ST s Int basicUnsafeWrite :: MVector s Int -> Int -> Int -> ST s () basicClear :: MVector s Int -> ST s () basicSet :: MVector s Int -> Int -> ST s () basicUnsafeCopy :: MVector s Int -> MVector s Int -> ST s () basicUnsafeMove :: MVector s Int -> MVector s Int -> ST s () basicUnsafeGrow :: MVector s Int -> Int -> ST s (MVector s Int) | |
| MVector MVector Word | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Word -> Int basicUnsafeSlice :: Int -> Int -> MVector s Word -> MVector s Word basicOverlaps :: MVector s Word -> MVector s Word -> Bool basicUnsafeNew :: Int -> ST s (MVector s Word) basicInitialize :: MVector s Word -> ST s () basicUnsafeReplicate :: Int -> Word -> ST s (MVector s Word) basicUnsafeRead :: MVector s Word -> Int -> ST s Word basicUnsafeWrite :: MVector s Word -> Int -> Word -> ST s () basicClear :: MVector s Word -> ST s () basicSet :: MVector s Word -> Word -> ST s () basicUnsafeCopy :: MVector s Word -> MVector s Word -> ST s () basicUnsafeMove :: MVector s Word -> MVector s Word -> ST s () basicUnsafeGrow :: MVector s Word -> Int -> ST s (MVector s Word) | |
| Unbox a => MVector MVector (Complex a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Complex a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Complex a) -> MVector s (Complex a) basicOverlaps :: MVector s (Complex a) -> MVector s (Complex a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Complex a)) basicInitialize :: MVector s (Complex a) -> ST s () basicUnsafeReplicate :: Int -> Complex a -> ST s (MVector s (Complex a)) basicUnsafeRead :: MVector s (Complex a) -> Int -> ST s (Complex a) basicUnsafeWrite :: MVector s (Complex a) -> Int -> Complex a -> ST s () basicClear :: MVector s (Complex a) -> ST s () basicSet :: MVector s (Complex a) -> Complex a -> ST s () basicUnsafeCopy :: MVector s (Complex a) -> MVector s (Complex a) -> ST s () basicUnsafeMove :: MVector s (Complex a) -> MVector s (Complex a) -> ST s () basicUnsafeGrow :: MVector s (Complex a) -> Int -> ST s (MVector s (Complex a)) | |
| Unbox a => MVector MVector (Identity a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Identity a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Identity a) -> MVector s (Identity a) basicOverlaps :: MVector s (Identity a) -> MVector s (Identity a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Identity a)) basicInitialize :: MVector s (Identity a) -> ST s () basicUnsafeReplicate :: Int -> Identity a -> ST s (MVector s (Identity a)) basicUnsafeRead :: MVector s (Identity a) -> Int -> ST s (Identity a) basicUnsafeWrite :: MVector s (Identity a) -> Int -> Identity a -> ST s () basicClear :: MVector s (Identity a) -> ST s () basicSet :: MVector s (Identity a) -> Identity a -> ST s () basicUnsafeCopy :: MVector s (Identity a) -> MVector s (Identity a) -> ST s () basicUnsafeMove :: MVector s (Identity a) -> MVector s (Identity a) -> ST s () basicUnsafeGrow :: MVector s (Identity a) -> Int -> ST s (MVector s (Identity a)) | |
| Unbox a => MVector MVector (Down a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Down a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Down a) -> MVector s (Down a) basicOverlaps :: MVector s (Down a) -> MVector s (Down a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Down a)) basicInitialize :: MVector s (Down a) -> ST s () basicUnsafeReplicate :: Int -> Down a -> ST s (MVector s (Down a)) basicUnsafeRead :: MVector s (Down a) -> Int -> ST s (Down a) basicUnsafeWrite :: MVector s (Down a) -> Int -> Down a -> ST s () basicClear :: MVector s (Down a) -> ST s () basicSet :: MVector s (Down a) -> Down a -> ST s () basicUnsafeCopy :: MVector s (Down a) -> MVector s (Down a) -> ST s () basicUnsafeMove :: MVector s (Down a) -> MVector s (Down a) -> ST s () basicUnsafeGrow :: MVector s (Down a) -> Int -> ST s (MVector s (Down a)) | |
| Unbox a => MVector MVector (First a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (First a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (First a) -> MVector s (First a) basicOverlaps :: MVector s (First a) -> MVector s (First a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (First a)) basicInitialize :: MVector s (First a) -> ST s () basicUnsafeReplicate :: Int -> First a -> ST s (MVector s (First a)) basicUnsafeRead :: MVector s (First a) -> Int -> ST s (First a) basicUnsafeWrite :: MVector s (First a) -> Int -> First a -> ST s () basicClear :: MVector s (First a) -> ST s () basicSet :: MVector s (First a) -> First a -> ST s () basicUnsafeCopy :: MVector s (First a) -> MVector s (First a) -> ST s () basicUnsafeMove :: MVector s (First a) -> MVector s (First a) -> ST s () basicUnsafeGrow :: MVector s (First a) -> Int -> ST s (MVector s (First a)) | |
| Unbox a => MVector MVector (Last a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Last a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Last a) -> MVector s (Last a) basicOverlaps :: MVector s (Last a) -> MVector s (Last a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Last a)) basicInitialize :: MVector s (Last a) -> ST s () basicUnsafeReplicate :: Int -> Last a -> ST s (MVector s (Last a)) basicUnsafeRead :: MVector s (Last a) -> Int -> ST s (Last a) basicUnsafeWrite :: MVector s (Last a) -> Int -> Last a -> ST s () basicClear :: MVector s (Last a) -> ST s () basicSet :: MVector s (Last a) -> Last a -> ST s () basicUnsafeCopy :: MVector s (Last a) -> MVector s (Last a) -> ST s () basicUnsafeMove :: MVector s (Last a) -> MVector s (Last a) -> ST s () basicUnsafeGrow :: MVector s (Last a) -> Int -> ST s (MVector s (Last a)) | |
| Unbox a => MVector MVector (Max a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Max a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Max a) -> MVector s (Max a) basicOverlaps :: MVector s (Max a) -> MVector s (Max a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Max a)) basicInitialize :: MVector s (Max a) -> ST s () basicUnsafeReplicate :: Int -> Max a -> ST s (MVector s (Max a)) basicUnsafeRead :: MVector s (Max a) -> Int -> ST s (Max a) basicUnsafeWrite :: MVector s (Max a) -> Int -> Max a -> ST s () basicClear :: MVector s (Max a) -> ST s () basicSet :: MVector s (Max a) -> Max a -> ST s () basicUnsafeCopy :: MVector s (Max a) -> MVector s (Max a) -> ST s () basicUnsafeMove :: MVector s (Max a) -> MVector s (Max a) -> ST s () basicUnsafeGrow :: MVector s (Max a) -> Int -> ST s (MVector s (Max a)) | |
| Unbox a => MVector MVector (Min a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Min a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Min a) -> MVector s (Min a) basicOverlaps :: MVector s (Min a) -> MVector s (Min a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Min a)) basicInitialize :: MVector s (Min a) -> ST s () basicUnsafeReplicate :: Int -> Min a -> ST s (MVector s (Min a)) basicUnsafeRead :: MVector s (Min a) -> Int -> ST s (Min a) basicUnsafeWrite :: MVector s (Min a) -> Int -> Min a -> ST s () basicClear :: MVector s (Min a) -> ST s () basicSet :: MVector s (Min a) -> Min a -> ST s () basicUnsafeCopy :: MVector s (Min a) -> MVector s (Min a) -> ST s () basicUnsafeMove :: MVector s (Min a) -> MVector s (Min a) -> ST s () basicUnsafeGrow :: MVector s (Min a) -> Int -> ST s (MVector s (Min a)) | |
| Unbox a => MVector MVector (WrappedMonoid a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (WrappedMonoid a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (WrappedMonoid a) -> MVector s (WrappedMonoid a) basicOverlaps :: MVector s (WrappedMonoid a) -> MVector s (WrappedMonoid a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (WrappedMonoid a)) basicInitialize :: MVector s (WrappedMonoid a) -> ST s () basicUnsafeReplicate :: Int -> WrappedMonoid a -> ST s (MVector s (WrappedMonoid a)) basicUnsafeRead :: MVector s (WrappedMonoid a) -> Int -> ST s (WrappedMonoid a) basicUnsafeWrite :: MVector s (WrappedMonoid a) -> Int -> WrappedMonoid a -> ST s () basicClear :: MVector s (WrappedMonoid a) -> ST s () basicSet :: MVector s (WrappedMonoid a) -> WrappedMonoid a -> ST s () basicUnsafeCopy :: MVector s (WrappedMonoid a) -> MVector s (WrappedMonoid a) -> ST s () basicUnsafeMove :: MVector s (WrappedMonoid a) -> MVector s (WrappedMonoid a) -> ST s () basicUnsafeGrow :: MVector s (WrappedMonoid a) -> Int -> ST s (MVector s (WrappedMonoid a)) | |
| Unbox a => MVector MVector (Dual a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Dual a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Dual a) -> MVector s (Dual a) basicOverlaps :: MVector s (Dual a) -> MVector s (Dual a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Dual a)) basicInitialize :: MVector s (Dual a) -> ST s () basicUnsafeReplicate :: Int -> Dual a -> ST s (MVector s (Dual a)) basicUnsafeRead :: MVector s (Dual a) -> Int -> ST s (Dual a) basicUnsafeWrite :: MVector s (Dual a) -> Int -> Dual a -> ST s () basicClear :: MVector s (Dual a) -> ST s () basicSet :: MVector s (Dual a) -> Dual a -> ST s () basicUnsafeCopy :: MVector s (Dual a) -> MVector s (Dual a) -> ST s () basicUnsafeMove :: MVector s (Dual a) -> MVector s (Dual a) -> ST s () basicUnsafeGrow :: MVector s (Dual a) -> Int -> ST s (MVector s (Dual a)) | |
| Unbox a => MVector MVector (Product a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Product a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Product a) -> MVector s (Product a) basicOverlaps :: MVector s (Product a) -> MVector s (Product a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Product a)) basicInitialize :: MVector s (Product a) -> ST s () basicUnsafeReplicate :: Int -> Product a -> ST s (MVector s (Product a)) basicUnsafeRead :: MVector s (Product a) -> Int -> ST s (Product a) basicUnsafeWrite :: MVector s (Product a) -> Int -> Product a -> ST s () basicClear :: MVector s (Product a) -> ST s () basicSet :: MVector s (Product a) -> Product a -> ST s () basicUnsafeCopy :: MVector s (Product a) -> MVector s (Product a) -> ST s () basicUnsafeMove :: MVector s (Product a) -> MVector s (Product a) -> ST s () basicUnsafeGrow :: MVector s (Product a) -> Int -> ST s (MVector s (Product a)) | |
| Unbox a => MVector MVector (Sum a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Sum a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Sum a) -> MVector s (Sum a) basicOverlaps :: MVector s (Sum a) -> MVector s (Sum a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Sum a)) basicInitialize :: MVector s (Sum a) -> ST s () basicUnsafeReplicate :: Int -> Sum a -> ST s (MVector s (Sum a)) basicUnsafeRead :: MVector s (Sum a) -> Int -> ST s (Sum a) basicUnsafeWrite :: MVector s (Sum a) -> Int -> Sum a -> ST s () basicClear :: MVector s (Sum a) -> ST s () basicSet :: MVector s (Sum a) -> Sum a -> ST s () basicUnsafeCopy :: MVector s (Sum a) -> MVector s (Sum a) -> ST s () basicUnsafeMove :: MVector s (Sum a) -> MVector s (Sum a) -> ST s () basicUnsafeGrow :: MVector s (Sum a) -> Int -> ST s (MVector s (Sum a)) | |
| Unbox a => MVector MVector (ViaRational a) | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods basicLength :: MVector s (ViaRational a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (ViaRational a) -> MVector s (ViaRational a) basicOverlaps :: MVector s (ViaRational a) -> MVector s (ViaRational a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (ViaRational a)) basicInitialize :: MVector s (ViaRational a) -> ST s () basicUnsafeReplicate :: Int -> ViaRational a -> ST s (MVector s (ViaRational a)) basicUnsafeRead :: MVector s (ViaRational a) -> Int -> ST s (ViaRational a) basicUnsafeWrite :: MVector s (ViaRational a) -> Int -> ViaRational a -> ST s () basicClear :: MVector s (ViaRational a) -> ST s () basicSet :: MVector s (ViaRational a) -> ViaRational a -> ST s () basicUnsafeCopy :: MVector s (ViaRational a) -> MVector s (ViaRational a) -> ST s () basicUnsafeMove :: MVector s (ViaRational a) -> MVector s (ViaRational a) -> ST s () basicUnsafeGrow :: MVector s (ViaRational a) -> Int -> ST s (MVector s (ViaRational a)) | |
| (Unbox a, Ord a, Fractional a) => MVector MVector (Interval a) | |
Defined in Numeric.Rounded.Hardware.Interval Methods basicLength :: MVector s (Interval a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Interval a) -> MVector s (Interval a) basicOverlaps :: MVector s (Interval a) -> MVector s (Interval a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Interval a)) basicInitialize :: MVector s (Interval a) -> ST s () basicUnsafeReplicate :: Int -> Interval a -> ST s (MVector s (Interval a)) basicUnsafeRead :: MVector s (Interval a) -> Int -> ST s (Interval a) basicUnsafeWrite :: MVector s (Interval a) -> Int -> Interval a -> ST s () basicClear :: MVector s (Interval a) -> ST s () basicSet :: MVector s (Interval a) -> Interval a -> ST s () basicUnsafeCopy :: MVector s (Interval a) -> MVector s (Interval a) -> ST s () basicUnsafeMove :: MVector s (Interval a) -> MVector s (Interval a) -> ST s () basicUnsafeGrow :: MVector s (Interval a) -> Int -> ST s (MVector s (Interval a)) | |
| (Unbox a, Ord a, Fractional a) => MVector MVector (Interval a) | |
Defined in Numeric.Rounded.Hardware.Interval.NonEmpty Methods basicLength :: MVector s (Interval a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Interval a) -> MVector s (Interval a) basicOverlaps :: MVector s (Interval a) -> MVector s (Interval a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Interval a)) basicInitialize :: MVector s (Interval a) -> ST s () basicUnsafeReplicate :: Int -> Interval a -> ST s (MVector s (Interval a)) basicUnsafeRead :: MVector s (Interval a) -> Int -> ST s (Interval a) basicUnsafeWrite :: MVector s (Interval a) -> Int -> Interval a -> ST s () basicClear :: MVector s (Interval a) -> ST s () basicSet :: MVector s (Interval a) -> Interval a -> ST s () basicUnsafeCopy :: MVector s (Interval a) -> MVector s (Interval a) -> ST s () basicUnsafeMove :: MVector s (Interval a) -> MVector s (Interval a) -> ST s () basicUnsafeGrow :: MVector s (Interval a) -> Int -> ST s (MVector s (Interval a)) | |
| MVector MVector (DoNotUnboxLazy a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (DoNotUnboxLazy a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (DoNotUnboxLazy a) -> MVector s (DoNotUnboxLazy a) basicOverlaps :: MVector s (DoNotUnboxLazy a) -> MVector s (DoNotUnboxLazy a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (DoNotUnboxLazy a)) basicInitialize :: MVector s (DoNotUnboxLazy a) -> ST s () basicUnsafeReplicate :: Int -> DoNotUnboxLazy a -> ST s (MVector s (DoNotUnboxLazy a)) basicUnsafeRead :: MVector s (DoNotUnboxLazy a) -> Int -> ST s (DoNotUnboxLazy a) basicUnsafeWrite :: MVector s (DoNotUnboxLazy a) -> Int -> DoNotUnboxLazy a -> ST s () basicClear :: MVector s (DoNotUnboxLazy a) -> ST s () basicSet :: MVector s (DoNotUnboxLazy a) -> DoNotUnboxLazy a -> ST s () basicUnsafeCopy :: MVector s (DoNotUnboxLazy a) -> MVector s (DoNotUnboxLazy a) -> ST s () basicUnsafeMove :: MVector s (DoNotUnboxLazy a) -> MVector s (DoNotUnboxLazy a) -> ST s () basicUnsafeGrow :: MVector s (DoNotUnboxLazy a) -> Int -> ST s (MVector s (DoNotUnboxLazy a)) | |
| NFData a => MVector MVector (DoNotUnboxNormalForm a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (DoNotUnboxNormalForm a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (DoNotUnboxNormalForm a) -> MVector s (DoNotUnboxNormalForm a) basicOverlaps :: MVector s (DoNotUnboxNormalForm a) -> MVector s (DoNotUnboxNormalForm a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (DoNotUnboxNormalForm a)) basicInitialize :: MVector s (DoNotUnboxNormalForm a) -> ST s () basicUnsafeReplicate :: Int -> DoNotUnboxNormalForm a -> ST s (MVector s (DoNotUnboxNormalForm a)) basicUnsafeRead :: MVector s (DoNotUnboxNormalForm a) -> Int -> ST s (DoNotUnboxNormalForm a) basicUnsafeWrite :: MVector s (DoNotUnboxNormalForm a) -> Int -> DoNotUnboxNormalForm a -> ST s () basicClear :: MVector s (DoNotUnboxNormalForm a) -> ST s () basicSet :: MVector s (DoNotUnboxNormalForm a) -> DoNotUnboxNormalForm a -> ST s () basicUnsafeCopy :: MVector s (DoNotUnboxNormalForm a) -> MVector s (DoNotUnboxNormalForm a) -> ST s () basicUnsafeMove :: MVector s (DoNotUnboxNormalForm a) -> MVector s (DoNotUnboxNormalForm a) -> ST s () basicUnsafeGrow :: MVector s (DoNotUnboxNormalForm a) -> Int -> ST s (MVector s (DoNotUnboxNormalForm a)) | |
| MVector MVector (DoNotUnboxStrict a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (DoNotUnboxStrict a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (DoNotUnboxStrict a) -> MVector s (DoNotUnboxStrict a) basicOverlaps :: MVector s (DoNotUnboxStrict a) -> MVector s (DoNotUnboxStrict a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (DoNotUnboxStrict a)) basicInitialize :: MVector s (DoNotUnboxStrict a) -> ST s () basicUnsafeReplicate :: Int -> DoNotUnboxStrict a -> ST s (MVector s (DoNotUnboxStrict a)) basicUnsafeRead :: MVector s (DoNotUnboxStrict a) -> Int -> ST s (DoNotUnboxStrict a) basicUnsafeWrite :: MVector s (DoNotUnboxStrict a) -> Int -> DoNotUnboxStrict a -> ST s () basicClear :: MVector s (DoNotUnboxStrict a) -> ST s () basicSet :: MVector s (DoNotUnboxStrict a) -> DoNotUnboxStrict a -> ST s () basicUnsafeCopy :: MVector s (DoNotUnboxStrict a) -> MVector s (DoNotUnboxStrict a) -> ST s () basicUnsafeMove :: MVector s (DoNotUnboxStrict a) -> MVector s (DoNotUnboxStrict a) -> ST s () basicUnsafeGrow :: MVector s (DoNotUnboxStrict a) -> Int -> ST s (MVector s (DoNotUnboxStrict a)) | |
| Prim a => MVector MVector (UnboxViaPrim a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (UnboxViaPrim a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (UnboxViaPrim a) -> MVector s (UnboxViaPrim a) basicOverlaps :: MVector s (UnboxViaPrim a) -> MVector s (UnboxViaPrim a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (UnboxViaPrim a)) basicInitialize :: MVector s (UnboxViaPrim a) -> ST s () basicUnsafeReplicate :: Int -> UnboxViaPrim a -> ST s (MVector s (UnboxViaPrim a)) basicUnsafeRead :: MVector s (UnboxViaPrim a) -> Int -> ST s (UnboxViaPrim a) basicUnsafeWrite :: MVector s (UnboxViaPrim a) -> Int -> UnboxViaPrim a -> ST s () basicClear :: MVector s (UnboxViaPrim a) -> ST s () basicSet :: MVector s (UnboxViaPrim a) -> UnboxViaPrim a -> ST s () basicUnsafeCopy :: MVector s (UnboxViaPrim a) -> MVector s (UnboxViaPrim a) -> ST s () basicUnsafeMove :: MVector s (UnboxViaPrim a) -> MVector s (UnboxViaPrim a) -> ST s () basicUnsafeGrow :: MVector s (UnboxViaPrim a) -> Int -> ST s (MVector s (UnboxViaPrim a)) | |
| (Unbox a, Unbox b) => MVector MVector (Arg a b) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Arg a b) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Arg a b) -> MVector s (Arg a b) basicOverlaps :: MVector s (Arg a b) -> MVector s (Arg a b) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Arg a b)) basicInitialize :: MVector s (Arg a b) -> ST s () basicUnsafeReplicate :: Int -> Arg a b -> ST s (MVector s (Arg a b)) basicUnsafeRead :: MVector s (Arg a b) -> Int -> ST s (Arg a b) basicUnsafeWrite :: MVector s (Arg a b) -> Int -> Arg a b -> ST s () basicClear :: MVector s (Arg a b) -> ST s () basicSet :: MVector s (Arg a b) -> Arg a b -> ST s () basicUnsafeCopy :: MVector s (Arg a b) -> MVector s (Arg a b) -> ST s () basicUnsafeMove :: MVector s (Arg a b) -> MVector s (Arg a b) -> ST s () basicUnsafeGrow :: MVector s (Arg a b) -> Int -> ST s (MVector s (Arg a b)) | |
| Unbox a => MVector MVector (Rounded r a) | |
Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods basicLength :: MVector s (Rounded r a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Rounded r a) -> MVector s (Rounded r a) basicOverlaps :: MVector s (Rounded r a) -> MVector s (Rounded r a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Rounded r a)) basicInitialize :: MVector s (Rounded r a) -> ST s () basicUnsafeReplicate :: Int -> Rounded r a -> ST s (MVector s (Rounded r a)) basicUnsafeRead :: MVector s (Rounded r a) -> Int -> ST s (Rounded r a) basicUnsafeWrite :: MVector s (Rounded r a) -> Int -> Rounded r a -> ST s () basicClear :: MVector s (Rounded r a) -> ST s () basicSet :: MVector s (Rounded r a) -> Rounded r a -> ST s () basicUnsafeCopy :: MVector s (Rounded r a) -> MVector s (Rounded r a) -> ST s () basicUnsafeMove :: MVector s (Rounded r a) -> MVector s (Rounded r a) -> ST s () basicUnsafeGrow :: MVector s (Rounded r a) -> Int -> ST s (MVector s (Rounded r a)) | |
| (IsoUnbox a b, Unbox b) => MVector MVector (As a b) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (As a b) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (As a b) -> MVector s (As a b) basicOverlaps :: MVector s (As a b) -> MVector s (As a b) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (As a b)) basicInitialize :: MVector s (As a b) -> ST s () basicUnsafeReplicate :: Int -> As a b -> ST s (MVector s (As a b)) basicUnsafeRead :: MVector s (As a b) -> Int -> ST s (As a b) basicUnsafeWrite :: MVector s (As a b) -> Int -> As a b -> ST s () basicClear :: MVector s (As a b) -> ST s () basicSet :: MVector s (As a b) -> As a b -> ST s () basicUnsafeCopy :: MVector s (As a b) -> MVector s (As a b) -> ST s () basicUnsafeMove :: MVector s (As a b) -> MVector s (As a b) -> ST s () basicUnsafeGrow :: MVector s (As a b) -> Int -> ST s (MVector s (As a b)) | |
| (Unbox a, Unbox b) => MVector MVector (a, b) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (a, b) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (a, b) -> MVector s (a, b) basicOverlaps :: MVector s (a, b) -> MVector s (a, b) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (a, b)) basicInitialize :: MVector s (a, b) -> ST s () basicUnsafeReplicate :: Int -> (a, b) -> ST s (MVector s (a, b)) basicUnsafeRead :: MVector s (a, b) -> Int -> ST s (a, b) basicUnsafeWrite :: MVector s (a, b) -> Int -> (a, b) -> ST s () basicClear :: MVector s (a, b) -> ST s () basicSet :: MVector s (a, b) -> (a, b) -> ST s () basicUnsafeCopy :: MVector s (a, b) -> MVector s (a, b) -> ST s () basicUnsafeMove :: MVector s (a, b) -> MVector s (a, b) -> ST s () basicUnsafeGrow :: MVector s (a, b) -> Int -> ST s (MVector s (a, b)) | |
| Unbox a => MVector MVector (Const a b) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Const a b) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Const a b) -> MVector s (Const a b) basicOverlaps :: MVector s (Const a b) -> MVector s (Const a b) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Const a b)) basicInitialize :: MVector s (Const a b) -> ST s () basicUnsafeReplicate :: Int -> Const a b -> ST s (MVector s (Const a b)) basicUnsafeRead :: MVector s (Const a b) -> Int -> ST s (Const a b) basicUnsafeWrite :: MVector s (Const a b) -> Int -> Const a b -> ST s () basicClear :: MVector s (Const a b) -> ST s () basicSet :: MVector s (Const a b) -> Const a b -> ST s () basicUnsafeCopy :: MVector s (Const a b) -> MVector s (Const a b) -> ST s () basicUnsafeMove :: MVector s (Const a b) -> MVector s (Const a b) -> ST s () basicUnsafeGrow :: MVector s (Const a b) -> Int -> ST s (MVector s (Const a b)) | |
| Unbox (f a) => MVector MVector (Alt f a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Alt f a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Alt f a) -> MVector s (Alt f a) basicOverlaps :: MVector s (Alt f a) -> MVector s (Alt f a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Alt f a)) basicInitialize :: MVector s (Alt f a) -> ST s () basicUnsafeReplicate :: Int -> Alt f a -> ST s (MVector s (Alt f a)) basicUnsafeRead :: MVector s (Alt f a) -> Int -> ST s (Alt f a) basicUnsafeWrite :: MVector s (Alt f a) -> Int -> Alt f a -> ST s () basicClear :: MVector s (Alt f a) -> ST s () basicSet :: MVector s (Alt f a) -> Alt f a -> ST s () basicUnsafeCopy :: MVector s (Alt f a) -> MVector s (Alt f a) -> ST s () basicUnsafeMove :: MVector s (Alt f a) -> MVector s (Alt f a) -> ST s () basicUnsafeGrow :: MVector s (Alt f a) -> Int -> ST s (MVector s (Alt f a)) | |
| (Unbox a, Unbox b, Unbox c) => MVector MVector (a, b, c) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (a, b, c) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (a, b, c) -> MVector s (a, b, c) basicOverlaps :: MVector s (a, b, c) -> MVector s (a, b, c) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (a, b, c)) basicInitialize :: MVector s (a, b, c) -> ST s () basicUnsafeReplicate :: Int -> (a, b, c) -> ST s (MVector s (a, b, c)) basicUnsafeRead :: MVector s (a, b, c) -> Int -> ST s (a, b, c) basicUnsafeWrite :: MVector s (a, b, c) -> Int -> (a, b, c) -> ST s () basicClear :: MVector s (a, b, c) -> ST s () basicSet :: MVector s (a, b, c) -> (a, b, c) -> ST s () basicUnsafeCopy :: MVector s (a, b, c) -> MVector s (a, b, c) -> ST s () basicUnsafeMove :: MVector s (a, b, c) -> MVector s (a, b, c) -> ST s () basicUnsafeGrow :: MVector s (a, b, c) -> Int -> ST s (MVector s (a, b, c)) | |
| (Unbox a, Unbox b, Unbox c, Unbox d) => MVector MVector (a, b, c, d) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (a, b, c, d) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (a, b, c, d) -> MVector s (a, b, c, d) basicOverlaps :: MVector s (a, b, c, d) -> MVector s (a, b, c, d) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (a, b, c, d)) basicInitialize :: MVector s (a, b, c, d) -> ST s () basicUnsafeReplicate :: Int -> (a, b, c, d) -> ST s (MVector s (a, b, c, d)) basicUnsafeRead :: MVector s (a, b, c, d) -> Int -> ST s (a, b, c, d) basicUnsafeWrite :: MVector s (a, b, c, d) -> Int -> (a, b, c, d) -> ST s () basicClear :: MVector s (a, b, c, d) -> ST s () basicSet :: MVector s (a, b, c, d) -> (a, b, c, d) -> ST s () basicUnsafeCopy :: MVector s (a, b, c, d) -> MVector s (a, b, c, d) -> ST s () basicUnsafeMove :: MVector s (a, b, c, d) -> MVector s (a, b, c, d) -> ST s () basicUnsafeGrow :: MVector s (a, b, c, d) -> Int -> ST s (MVector s (a, b, c, d)) | |
| Unbox (f (g a)) => MVector MVector (Compose f g a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Compose f g a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Compose f g a) -> MVector s (Compose f g a) basicOverlaps :: MVector s (Compose f g a) -> MVector s (Compose f g a) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (Compose f g a)) basicInitialize :: MVector s (Compose f g a) -> ST s () basicUnsafeReplicate :: Int -> Compose f g a -> ST s (MVector s (Compose f g a)) basicUnsafeRead :: MVector s (Compose f g a) -> Int -> ST s (Compose f g a) basicUnsafeWrite :: MVector s (Compose f g a) -> Int -> Compose f g a -> ST s () basicClear :: MVector s (Compose f g a) -> ST s () basicSet :: MVector s (Compose f g a) -> Compose f g a -> ST s () basicUnsafeCopy :: MVector s (Compose f g a) -> MVector s (Compose f g a) -> ST s () basicUnsafeMove :: MVector s (Compose f g a) -> MVector s (Compose f g a) -> ST s () basicUnsafeGrow :: MVector s (Compose f g a) -> Int -> ST s (MVector s (Compose f g a)) | |
| (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => MVector MVector (a, b, c, d, e) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (a, b, c, d, e) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (a, b, c, d, e) -> MVector s (a, b, c, d, e) basicOverlaps :: MVector s (a, b, c, d, e) -> MVector s (a, b, c, d, e) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (a, b, c, d, e)) basicInitialize :: MVector s (a, b, c, d, e) -> ST s () basicUnsafeReplicate :: Int -> (a, b, c, d, e) -> ST s (MVector s (a, b, c, d, e)) basicUnsafeRead :: MVector s (a, b, c, d, e) -> Int -> ST s (a, b, c, d, e) basicUnsafeWrite :: MVector s (a, b, c, d, e) -> Int -> (a, b, c, d, e) -> ST s () basicClear :: MVector s (a, b, c, d, e) -> ST s () basicSet :: MVector s (a, b, c, d, e) -> (a, b, c, d, e) -> ST s () basicUnsafeCopy :: MVector s (a, b, c, d, e) -> MVector s (a, b, c, d, e) -> ST s () basicUnsafeMove :: MVector s (a, b, c, d, e) -> MVector s (a, b, c, d, e) -> ST s () basicUnsafeGrow :: MVector s (a, b, c, d, e) -> Int -> ST s (MVector s (a, b, c, d, e)) | |
| (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => MVector MVector (a, b, c, d, e, f) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (a, b, c, d, e, f) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (a, b, c, d, e, f) -> MVector s (a, b, c, d, e, f) basicOverlaps :: MVector s (a, b, c, d, e, f) -> MVector s (a, b, c, d, e, f) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (a, b, c, d, e, f)) basicInitialize :: MVector s (a, b, c, d, e, f) -> ST s () basicUnsafeReplicate :: Int -> (a, b, c, d, e, f) -> ST s (MVector s (a, b, c, d, e, f)) basicUnsafeRead :: MVector s (a, b, c, d, e, f) -> Int -> ST s (a, b, c, d, e, f) basicUnsafeWrite :: MVector s (a, b, c, d, e, f) -> Int -> (a, b, c, d, e, f) -> ST s () basicClear :: MVector s (a, b, c, d, e, f) -> ST s () basicSet :: MVector s (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> ST s () basicUnsafeCopy :: MVector s (a, b, c, d, e, f) -> MVector s (a, b, c, d, e, f) -> ST s () basicUnsafeMove :: MVector s (a, b, c, d, e, f) -> MVector s (a, b, c, d, e, f) -> ST s () basicUnsafeGrow :: MVector s (a, b, c, d, e, f) -> Int -> ST s (MVector s (a, b, c, d, e, f)) | |
| NFData1 (MVector s) | |
Defined in Data.Vector.Unboxed.Base | |
| NFData (MVector s a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s All | |
| newtype MVector s Any | |
| newtype MVector s Int16 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Int32 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Int64 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Int8 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Word16 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Word32 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Word64 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Word8 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C | |
| newtype MVector s CFloat Source # | |
| newtype MVector s CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI | |
| newtype MVector s () | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Bool | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Char | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Double | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Float | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Int | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s Word | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Complex a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Identity a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Down a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (First a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Last a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Max a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Min a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (WrappedMonoid a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Dual a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Product a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Sum a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational | |
| newtype MVector s (Interval a) Source # | |
Defined in Numeric.Rounded.Hardware.Interval | |
| newtype MVector s (Interval a) Source # | |
Defined in Numeric.Rounded.Hardware.Interval.NonEmpty | |
| newtype MVector s (DoNotUnboxLazy a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (DoNotUnboxNormalForm a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (DoNotUnboxStrict a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (UnboxViaPrim a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Arg a b) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Rounded r a) Source # | |
Defined in Numeric.Rounded.Hardware.Internal.Rounding | |
| newtype MVector s (As a b) | |
Defined in Data.Vector.Unboxed.Base | |
| data MVector s (a, b) | |
| newtype MVector s (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype MVector s (Alt f a) | |
Defined in Data.Vector.Unboxed.Base | |
| data MVector s (a, b, c) | |
| data MVector s (a, b, c, d) | |
| newtype MVector s (Compose f g a) | |
Defined in Data.Vector.Unboxed.Base | |
| data MVector s (a, b, c, d, e) | |
| data MVector s (a, b, c, d, e, f) | |
Instances
| NFData1 Vector | |
Defined in Data.Vector.Unboxed.Base | |
| RoundedFractional_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods zipWith_roundedDiv :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedFractional_Vector Vector CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods zipWith_roundedDiv :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # | |
| RoundedFractional_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods zipWith_roundedDiv :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedFractional_Vector Vector Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods zipWith_roundedDiv :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # | |
| RoundedFractional_Vector Vector Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods zipWith_roundedDiv :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # | |
| RoundedRing_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedSum :: RoundingMode -> Vector CDouble -> CDouble Source # zipWith_roundedAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedSub :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedMul :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedRing_Vector Vector CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods roundedSum :: RoundingMode -> Vector CFloat -> CFloat Source # zipWith_roundedAdd :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # zipWith_roundedSub :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # zipWith_roundedMul :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector CFloat -> Vector CFloat -> Vector CFloat -> Vector CFloat Source # | |
| RoundedRing_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods roundedSum :: RoundingMode -> Vector CDouble -> CDouble Source # zipWith_roundedAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedSub :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith_roundedMul :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector CDouble -> Vector CDouble -> Vector CDouble -> Vector CDouble Source # | |
| RoundedRing_Vector Vector Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedSum :: RoundingMode -> Vector Double -> Double Source # zipWith_roundedAdd :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # zipWith_roundedSub :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # zipWith_roundedMul :: RoundingMode -> Vector Double -> Vector Double -> Vector Double Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector Double -> Vector Double -> Vector Double -> Vector Double Source # | |
| RoundedRing_Vector Vector Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods roundedSum :: RoundingMode -> Vector Float -> Float Source # zipWith_roundedAdd :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # zipWith_roundedSub :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # zipWith_roundedMul :: RoundingMode -> Vector Float -> Vector Float -> Vector Float Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector Float -> Vector Float -> Vector Float -> Vector Float Source # | |
| RoundedSqrt_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods map_roundedSqrt :: RoundingMode -> Vector CDouble -> Vector CDouble Source # | |
| RoundedSqrt_Vector Vector CFloat Source # | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods map_roundedSqrt :: RoundingMode -> Vector CFloat -> Vector CFloat Source # | |
| RoundedSqrt_Vector Vector CDouble Source # | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods map_roundedSqrt :: RoundingMode -> Vector CDouble -> Vector CDouble Source # | |
| RoundedSqrt_Vector Vector Double Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods map_roundedSqrt :: RoundingMode -> Vector Double -> Vector Double Source # | |
| RoundedSqrt_Vector Vector Float Source # | |
Defined in Numeric.Rounded.Hardware.Backend.Default Methods map_roundedSqrt :: RoundingMode -> Vector Float -> Vector Float Source # | |
| Vector Vector All | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s All -> ST s (Vector All) basicUnsafeThaw :: Vector All -> ST s (Mutable Vector s All) basicLength :: Vector All -> Int basicUnsafeSlice :: Int -> Int -> Vector All -> Vector All basicUnsafeIndexM :: Vector All -> Int -> Box All basicUnsafeCopy :: Mutable Vector s All -> Vector All -> ST s () | |
| Vector Vector Any | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Any -> ST s (Vector Any) basicUnsafeThaw :: Vector Any -> ST s (Mutable Vector s Any) basicLength :: Vector Any -> Int basicUnsafeSlice :: Int -> Int -> Vector Any -> Vector Any basicUnsafeIndexM :: Vector Any -> Int -> Box Any basicUnsafeCopy :: Mutable Vector s Any -> Vector Any -> ST s () | |
| Vector Vector Int16 | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Int16 -> ST s (Vector Int16) basicUnsafeThaw :: Vector Int16 -> ST s (Mutable Vector s Int16) basicLength :: Vector Int16 -> Int basicUnsafeSlice :: Int -> Int -> Vector Int16 -> Vector Int16 basicUnsafeIndexM :: Vector Int16 -> Int -> Box Int16 basicUnsafeCopy :: Mutable Vector s Int16 -> Vector Int16 -> ST s () | |
| Vector Vector Int32 | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Int32 -> ST s (Vector Int32) basicUnsafeThaw :: Vector Int32 -> ST s (Mutable Vector s Int32) basicLength :: Vector Int32 -> Int basicUnsafeSlice :: Int -> Int -> Vector Int32 -> Vector Int32 basicUnsafeIndexM :: Vector Int32 -> Int -> Box Int32 basicUnsafeCopy :: Mutable Vector s Int32 -> Vector Int32 -> ST s () | |
| Vector Vector Int64 | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Int64 -> ST s (Vector Int64) basicUnsafeThaw :: Vector Int64 -> ST s (Mutable Vector s Int64) basicLength :: Vector Int64 -> Int basicUnsafeSlice :: Int -> Int -> Vector Int64 -> Vector Int64 basicUnsafeIndexM :: Vector Int64 -> Int -> Box Int64 basicUnsafeCopy :: Mutable Vector s Int64 -> Vector Int64 -> ST s () | |
| Vector Vector Int8 | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Int8 -> ST s (Vector Int8) basicUnsafeThaw :: Vector Int8 -> ST s (Mutable Vector s Int8) basicLength :: Vector Int8 -> Int basicUnsafeSlice :: Int -> Int -> Vector Int8 -> Vector Int8 basicUnsafeIndexM :: Vector Int8 -> Int -> Box Int8 basicUnsafeCopy :: Mutable Vector s Int8 -> Vector Int8 -> ST s () | |
| Vector Vector Word16 | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Word16 -> ST s (Vector Word16) basicUnsafeThaw :: Vector Word16 -> ST s (Mutable Vector s Word16) basicLength :: Vector Word16 -> Int basicUnsafeSlice :: Int -> Int -> Vector Word16 -> Vector Word16 basicUnsafeIndexM :: Vector Word16 -> Int -> Box Word16 basicUnsafeCopy :: Mutable Vector s Word16 -> Vector Word16 -> ST s () | |
| Vector Vector Word32 | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Word32 -> ST s (Vector Word32) basicUnsafeThaw :: Vector Word32 -> ST s (Mutable Vector s Word32) basicLength :: Vector Word32 -> Int basicUnsafeSlice :: Int -> Int -> Vector Word32 -> Vector Word32 basicUnsafeIndexM :: Vector Word32 -> Int -> Box Word32 basicUnsafeCopy :: Mutable Vector s Word32 -> Vector Word32 -> ST s () | |
| Vector Vector Word64 | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Word64 -> ST s (Vector Word64) basicUnsafeThaw :: Vector Word64 -> ST s (Mutable Vector s Word64) basicLength :: Vector Word64 -> Int basicUnsafeSlice :: Int -> Int -> Vector Word64 -> Vector Word64 basicUnsafeIndexM :: Vector Word64 -> Int -> Box Word64 basicUnsafeCopy :: Mutable Vector s Word64 -> Vector Word64 -> ST s () | |
| Vector Vector Word8 | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Word8 -> ST s (Vector Word8) basicUnsafeThaw :: Vector Word8 -> ST s (Mutable Vector s Word8) basicLength :: Vector Word8 -> Int basicUnsafeSlice :: Int -> Int -> Vector Word8 -> Vector Word8 basicUnsafeIndexM :: Vector Word8 -> Int -> Box Word8 basicUnsafeCopy :: Mutable Vector s Word8 -> Vector Word8 -> ST s () | |
| Vector Vector CDouble | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods basicUnsafeFreeze :: Mutable Vector s CDouble -> ST s (Vector CDouble) basicUnsafeThaw :: Vector CDouble -> ST s (Mutable Vector s CDouble) basicLength :: Vector CDouble -> Int basicUnsafeSlice :: Int -> Int -> Vector CDouble -> Vector CDouble basicUnsafeIndexM :: Vector CDouble -> Int -> Box CDouble basicUnsafeCopy :: Mutable Vector s CDouble -> Vector CDouble -> ST s () | |
| Vector Vector CFloat | |
Defined in Numeric.Rounded.Hardware.Backend.C Methods basicUnsafeFreeze :: Mutable Vector s CFloat -> ST s (Vector CFloat) basicUnsafeThaw :: Vector CFloat -> ST s (Mutable Vector s CFloat) basicLength :: Vector CFloat -> Int basicUnsafeSlice :: Int -> Int -> Vector CFloat -> Vector CFloat basicUnsafeIndexM :: Vector CFloat -> Int -> Box CFloat basicUnsafeCopy :: Mutable Vector s CFloat -> Vector CFloat -> ST s () | |
| Vector Vector CDouble | |
Defined in Numeric.Rounded.Hardware.Backend.FastFFI Methods basicUnsafeFreeze :: Mutable Vector s CDouble -> ST s (Vector CDouble) basicUnsafeThaw :: Vector CDouble -> ST s (Mutable Vector s CDouble) basicLength :: Vector CDouble -> Int basicUnsafeSlice :: Int -> Int -> Vector CDouble -> Vector CDouble basicUnsafeIndexM :: Vector CDouble -> Int -> Box CDouble basicUnsafeCopy :: Mutable Vector s CDouble -> Vector CDouble -> ST s () | |
| Vector Vector () | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s () -> ST s (Vector ()) basicUnsafeThaw :: Vector () -> ST s (Mutable Vector s ()) basicLength :: Vector () -> Int basicUnsafeSlice :: Int -> Int -> Vector () -> Vector () basicUnsafeIndexM :: Vector () -> Int -> Box () basicUnsafeCopy :: Mutable Vector s () -> Vector () -> ST s () | |
| Vector Vector Bool | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Bool -> ST s (Vector Bool) basicUnsafeThaw :: Vector Bool -> ST s (Mutable Vector s Bool) basicLength :: Vector Bool -> Int basicUnsafeSlice :: Int -> Int -> Vector Bool -> Vector Bool basicUnsafeIndexM :: Vector Bool -> Int -> Box Bool basicUnsafeCopy :: Mutable Vector s Bool -> Vector Bool -> ST s () | |
| Vector Vector Char | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Char -> ST s (Vector Char) basicUnsafeThaw :: Vector Char -> ST s (Mutable Vector s Char) basicLength :: Vector Char -> Int basicUnsafeSlice :: Int -> Int -> Vector Char -> Vector Char basicUnsafeIndexM :: Vector Char -> Int -> Box Char basicUnsafeCopy :: Mutable Vector s Char -> Vector Char -> ST s () | |
| Vector Vector Double | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Double -> ST s (Vector Double) basicUnsafeThaw :: Vector Double -> ST s (Mutable Vector s Double) basicLength :: Vector Double -> Int basicUnsafeSlice :: Int -> Int -> Vector Double -> Vector Double basicUnsafeIndexM :: Vector Double -> Int -> Box Double basicUnsafeCopy :: Mutable Vector s Double -> Vector Double -> ST s () | |
| Vector Vector Float | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Float -> ST s (Vector Float) basicUnsafeThaw :: Vector Float -> ST s (Mutable Vector s Float) basicLength :: Vector Float -> Int basicUnsafeSlice :: Int -> Int -> Vector Float -> Vector Float basicUnsafeIndexM :: Vector Float -> Int -> Box Float basicUnsafeCopy :: Mutable Vector s Float -> Vector Float -> ST s () | |
| Vector Vector Int | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Int -> ST s (Vector Int) basicUnsafeThaw :: Vector Int -> ST s (Mutable Vector s Int) basicLength :: Vector Int -> Int basicUnsafeSlice :: Int -> Int -> Vector Int -> Vector Int basicUnsafeIndexM :: Vector Int -> Int -> Box Int basicUnsafeCopy :: Mutable Vector s Int -> Vector Int -> ST s () | |
| Vector Vector Word | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Word -> ST s (Vector Word) basicUnsafeThaw :: Vector Word -> ST s (Mutable Vector s Word) basicLength :: Vector Word -> Int basicUnsafeSlice :: Int -> Int -> Vector Word -> Vector Word basicUnsafeIndexM :: Vector Word -> Int -> Box Word basicUnsafeCopy :: Mutable Vector s Word -> Vector Word -> ST s () | |
| (RealFloat a, RealFloatConstants a, Unbox a) => RoundedFractional_Vector Vector (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods zipWith_roundedDiv :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # | |
| (RealFloat a, RealFloatConstants a, Unbox a) => RoundedRing_Vector Vector (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods roundedSum :: RoundingMode -> Vector (ViaRational a) -> ViaRational a Source # zipWith_roundedAdd :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # zipWith_roundedSub :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # zipWith_roundedMul :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) -> Vector (ViaRational a) Source # | |
| (RealFloat a, RealFloatConstants a, Unbox a) => RoundedSqrt_Vector Vector (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods map_roundedSqrt :: RoundingMode -> Vector (ViaRational a) -> Vector (ViaRational a) Source # | |
| Unbox a => Vector Vector (Complex a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Complex a) -> ST s (Vector (Complex a)) basicUnsafeThaw :: Vector (Complex a) -> ST s (Mutable Vector s (Complex a)) basicLength :: Vector (Complex a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Complex a) -> Vector (Complex a) basicUnsafeIndexM :: Vector (Complex a) -> Int -> Box (Complex a) basicUnsafeCopy :: Mutable Vector s (Complex a) -> Vector (Complex a) -> ST s () | |
| Unbox a => Vector Vector (Identity a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Identity a) -> ST s (Vector (Identity a)) basicUnsafeThaw :: Vector (Identity a) -> ST s (Mutable Vector s (Identity a)) basicLength :: Vector (Identity a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Identity a) -> Vector (Identity a) basicUnsafeIndexM :: Vector (Identity a) -> Int -> Box (Identity a) basicUnsafeCopy :: Mutable Vector s (Identity a) -> Vector (Identity a) -> ST s () | |
| Unbox a => Vector Vector (Down a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Down a) -> ST s (Vector (Down a)) basicUnsafeThaw :: Vector (Down a) -> ST s (Mutable Vector s (Down a)) basicLength :: Vector (Down a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Down a) -> Vector (Down a) basicUnsafeIndexM :: Vector (Down a) -> Int -> Box (Down a) basicUnsafeCopy :: Mutable Vector s (Down a) -> Vector (Down a) -> ST s () | |
| Unbox a => Vector Vector (First a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (First a) -> ST s (Vector (First a)) basicUnsafeThaw :: Vector (First a) -> ST s (Mutable Vector s (First a)) basicLength :: Vector (First a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (First a) -> Vector (First a) basicUnsafeIndexM :: Vector (First a) -> Int -> Box (First a) basicUnsafeCopy :: Mutable Vector s (First a) -> Vector (First a) -> ST s () | |
| Unbox a => Vector Vector (Last a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Last a) -> ST s (Vector (Last a)) basicUnsafeThaw :: Vector (Last a) -> ST s (Mutable Vector s (Last a)) basicLength :: Vector (Last a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Last a) -> Vector (Last a) basicUnsafeIndexM :: Vector (Last a) -> Int -> Box (Last a) basicUnsafeCopy :: Mutable Vector s (Last a) -> Vector (Last a) -> ST s () | |
| Unbox a => Vector Vector (Max a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Max a) -> ST s (Vector (Max a)) basicUnsafeThaw :: Vector (Max a) -> ST s (Mutable Vector s (Max a)) basicLength :: Vector (Max a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Max a) -> Vector (Max a) basicUnsafeIndexM :: Vector (Max a) -> Int -> Box (Max a) basicUnsafeCopy :: Mutable Vector s (Max a) -> Vector (Max a) -> ST s () | |
| Unbox a => Vector Vector (Min a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Min a) -> ST s (Vector (Min a)) basicUnsafeThaw :: Vector (Min a) -> ST s (Mutable Vector s (Min a)) basicLength :: Vector (Min a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Min a) -> Vector (Min a) basicUnsafeIndexM :: Vector (Min a) -> Int -> Box (Min a) basicUnsafeCopy :: Mutable Vector s (Min a) -> Vector (Min a) -> ST s () | |
| Unbox a => Vector Vector (WrappedMonoid a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (WrappedMonoid a) -> ST s (Vector (WrappedMonoid a)) basicUnsafeThaw :: Vector (WrappedMonoid a) -> ST s (Mutable Vector s (WrappedMonoid a)) basicLength :: Vector (WrappedMonoid a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (WrappedMonoid a) -> Vector (WrappedMonoid a) basicUnsafeIndexM :: Vector (WrappedMonoid a) -> Int -> Box (WrappedMonoid a) basicUnsafeCopy :: Mutable Vector s (WrappedMonoid a) -> Vector (WrappedMonoid a) -> ST s () elemseq :: Vector (WrappedMonoid a) -> WrappedMonoid a -> b -> b | |
| Unbox a => Vector Vector (Dual a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Dual a) -> ST s (Vector (Dual a)) basicUnsafeThaw :: Vector (Dual a) -> ST s (Mutable Vector s (Dual a)) basicLength :: Vector (Dual a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Dual a) -> Vector (Dual a) basicUnsafeIndexM :: Vector (Dual a) -> Int -> Box (Dual a) basicUnsafeCopy :: Mutable Vector s (Dual a) -> Vector (Dual a) -> ST s () | |
| Unbox a => Vector Vector (Product a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Product a) -> ST s (Vector (Product a)) basicUnsafeThaw :: Vector (Product a) -> ST s (Mutable Vector s (Product a)) basicLength :: Vector (Product a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Product a) -> Vector (Product a) basicUnsafeIndexM :: Vector (Product a) -> Int -> Box (Product a) basicUnsafeCopy :: Mutable Vector s (Product a) -> Vector (Product a) -> ST s () | |
| Unbox a => Vector Vector (Sum a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Sum a) -> ST s (Vector (Sum a)) basicUnsafeThaw :: Vector (Sum a) -> ST s (Mutable Vector s (Sum a)) basicLength :: Vector (Sum a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Sum a) -> Vector (Sum a) basicUnsafeIndexM :: Vector (Sum a) -> Int -> Box (Sum a) basicUnsafeCopy :: Mutable Vector s (Sum a) -> Vector (Sum a) -> ST s () | |
| Unbox a => Vector Vector (ViaRational a) | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational Methods basicUnsafeFreeze :: Mutable Vector s (ViaRational a) -> ST s (Vector (ViaRational a)) basicUnsafeThaw :: Vector (ViaRational a) -> ST s (Mutable Vector s (ViaRational a)) basicLength :: Vector (ViaRational a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (ViaRational a) -> Vector (ViaRational a) basicUnsafeIndexM :: Vector (ViaRational a) -> Int -> Box (ViaRational a) basicUnsafeCopy :: Mutable Vector s (ViaRational a) -> Vector (ViaRational a) -> ST s () elemseq :: Vector (ViaRational a) -> ViaRational a -> b -> b | |
| (Unbox a, Ord a, Fractional a) => Vector Vector (Interval a) | |
Defined in Numeric.Rounded.Hardware.Interval Methods basicUnsafeFreeze :: Mutable Vector s (Interval a) -> ST s (Vector (Interval a)) basicUnsafeThaw :: Vector (Interval a) -> ST s (Mutable Vector s (Interval a)) basicLength :: Vector (Interval a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Interval a) -> Vector (Interval a) basicUnsafeIndexM :: Vector (Interval a) -> Int -> Box (Interval a) basicUnsafeCopy :: Mutable Vector s (Interval a) -> Vector (Interval a) -> ST s () | |
| (Unbox a, Ord a, Fractional a) => Vector Vector (Interval a) | |
Defined in Numeric.Rounded.Hardware.Interval.NonEmpty Methods basicUnsafeFreeze :: Mutable Vector s (Interval a) -> ST s (Vector (Interval a)) basicUnsafeThaw :: Vector (Interval a) -> ST s (Mutable Vector s (Interval a)) basicLength :: Vector (Interval a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Interval a) -> Vector (Interval a) basicUnsafeIndexM :: Vector (Interval a) -> Int -> Box (Interval a) basicUnsafeCopy :: Mutable Vector s (Interval a) -> Vector (Interval a) -> ST s () | |
| Vector Vector (DoNotUnboxLazy a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (DoNotUnboxLazy a) -> ST s (Vector (DoNotUnboxLazy a)) basicUnsafeThaw :: Vector (DoNotUnboxLazy a) -> ST s (Mutable Vector s (DoNotUnboxLazy a)) basicLength :: Vector (DoNotUnboxLazy a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (DoNotUnboxLazy a) -> Vector (DoNotUnboxLazy a) basicUnsafeIndexM :: Vector (DoNotUnboxLazy a) -> Int -> Box (DoNotUnboxLazy a) basicUnsafeCopy :: Mutable Vector s (DoNotUnboxLazy a) -> Vector (DoNotUnboxLazy a) -> ST s () elemseq :: Vector (DoNotUnboxLazy a) -> DoNotUnboxLazy a -> b -> b | |
| NFData a => Vector Vector (DoNotUnboxNormalForm a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (DoNotUnboxNormalForm a) -> ST s (Vector (DoNotUnboxNormalForm a)) basicUnsafeThaw :: Vector (DoNotUnboxNormalForm a) -> ST s (Mutable Vector s (DoNotUnboxNormalForm a)) basicLength :: Vector (DoNotUnboxNormalForm a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (DoNotUnboxNormalForm a) -> Vector (DoNotUnboxNormalForm a) basicUnsafeIndexM :: Vector (DoNotUnboxNormalForm a) -> Int -> Box (DoNotUnboxNormalForm a) basicUnsafeCopy :: Mutable Vector s (DoNotUnboxNormalForm a) -> Vector (DoNotUnboxNormalForm a) -> ST s () elemseq :: Vector (DoNotUnboxNormalForm a) -> DoNotUnboxNormalForm a -> b -> b | |
| Vector Vector (DoNotUnboxStrict a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (DoNotUnboxStrict a) -> ST s (Vector (DoNotUnboxStrict a)) basicUnsafeThaw :: Vector (DoNotUnboxStrict a) -> ST s (Mutable Vector s (DoNotUnboxStrict a)) basicLength :: Vector (DoNotUnboxStrict a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (DoNotUnboxStrict a) -> Vector (DoNotUnboxStrict a) basicUnsafeIndexM :: Vector (DoNotUnboxStrict a) -> Int -> Box (DoNotUnboxStrict a) basicUnsafeCopy :: Mutable Vector s (DoNotUnboxStrict a) -> Vector (DoNotUnboxStrict a) -> ST s () elemseq :: Vector (DoNotUnboxStrict a) -> DoNotUnboxStrict a -> b -> b | |
| Prim a => Vector Vector (UnboxViaPrim a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (UnboxViaPrim a) -> ST s (Vector (UnboxViaPrim a)) basicUnsafeThaw :: Vector (UnboxViaPrim a) -> ST s (Mutable Vector s (UnboxViaPrim a)) basicLength :: Vector (UnboxViaPrim a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (UnboxViaPrim a) -> Vector (UnboxViaPrim a) basicUnsafeIndexM :: Vector (UnboxViaPrim a) -> Int -> Box (UnboxViaPrim a) basicUnsafeCopy :: Mutable Vector s (UnboxViaPrim a) -> Vector (UnboxViaPrim a) -> ST s () elemseq :: Vector (UnboxViaPrim a) -> UnboxViaPrim a -> b -> b | |
| (Unbox a, Unbox b) => Vector Vector (Arg a b) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Arg a b) -> ST s (Vector (Arg a b)) basicUnsafeThaw :: Vector (Arg a b) -> ST s (Mutable Vector s (Arg a b)) basicLength :: Vector (Arg a b) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Arg a b) -> Vector (Arg a b) basicUnsafeIndexM :: Vector (Arg a b) -> Int -> Box (Arg a b) basicUnsafeCopy :: Mutable Vector s (Arg a b) -> Vector (Arg a b) -> ST s () | |
| Unbox a => Vector Vector (Rounded r a) | |
Defined in Numeric.Rounded.Hardware.Internal.Rounding Methods basicUnsafeFreeze :: Mutable Vector s (Rounded r a) -> ST s (Vector (Rounded r a)) basicUnsafeThaw :: Vector (Rounded r a) -> ST s (Mutable Vector s (Rounded r a)) basicLength :: Vector (Rounded r a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Rounded r a) -> Vector (Rounded r a) basicUnsafeIndexM :: Vector (Rounded r a) -> Int -> Box (Rounded r a) basicUnsafeCopy :: Mutable Vector s (Rounded r a) -> Vector (Rounded r a) -> ST s () | |
| (IsoUnbox a b, Unbox b) => Vector Vector (As a b) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (As a b) -> ST s (Vector (As a b)) basicUnsafeThaw :: Vector (As a b) -> ST s (Mutable Vector s (As a b)) basicLength :: Vector (As a b) -> Int basicUnsafeSlice :: Int -> Int -> Vector (As a b) -> Vector (As a b) basicUnsafeIndexM :: Vector (As a b) -> Int -> Box (As a b) basicUnsafeCopy :: Mutable Vector s (As a b) -> Vector (As a b) -> ST s () | |
| (Unbox a, Unbox b) => Vector Vector (a, b) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (a, b) -> ST s (Vector (a, b)) basicUnsafeThaw :: Vector (a, b) -> ST s (Mutable Vector s (a, b)) basicLength :: Vector (a, b) -> Int basicUnsafeSlice :: Int -> Int -> Vector (a, b) -> Vector (a, b) basicUnsafeIndexM :: Vector (a, b) -> Int -> Box (a, b) basicUnsafeCopy :: Mutable Vector s (a, b) -> Vector (a, b) -> ST s () | |
| Unbox a => Vector Vector (Const a b) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Const a b) -> ST s (Vector (Const a b)) basicUnsafeThaw :: Vector (Const a b) -> ST s (Mutable Vector s (Const a b)) basicLength :: Vector (Const a b) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Const a b) -> Vector (Const a b) basicUnsafeIndexM :: Vector (Const a b) -> Int -> Box (Const a b) basicUnsafeCopy :: Mutable Vector s (Const a b) -> Vector (Const a b) -> ST s () | |
| Unbox (f a) => Vector Vector (Alt f a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Alt f a) -> ST s (Vector (Alt f a)) basicUnsafeThaw :: Vector (Alt f a) -> ST s (Mutable Vector s (Alt f a)) basicLength :: Vector (Alt f a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Alt f a) -> Vector (Alt f a) basicUnsafeIndexM :: Vector (Alt f a) -> Int -> Box (Alt f a) basicUnsafeCopy :: Mutable Vector s (Alt f a) -> Vector (Alt f a) -> ST s () | |
| (Unbox a, Unbox b, Unbox c) => Vector Vector (a, b, c) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (a, b, c) -> ST s (Vector (a, b, c)) basicUnsafeThaw :: Vector (a, b, c) -> ST s (Mutable Vector s (a, b, c)) basicLength :: Vector (a, b, c) -> Int basicUnsafeSlice :: Int -> Int -> Vector (a, b, c) -> Vector (a, b, c) basicUnsafeIndexM :: Vector (a, b, c) -> Int -> Box (a, b, c) basicUnsafeCopy :: Mutable Vector s (a, b, c) -> Vector (a, b, c) -> ST s () | |
| (Unbox a, Unbox b, Unbox c, Unbox d) => Vector Vector (a, b, c, d) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (a, b, c, d) -> ST s (Vector (a, b, c, d)) basicUnsafeThaw :: Vector (a, b, c, d) -> ST s (Mutable Vector s (a, b, c, d)) basicLength :: Vector (a, b, c, d) -> Int basicUnsafeSlice :: Int -> Int -> Vector (a, b, c, d) -> Vector (a, b, c, d) basicUnsafeIndexM :: Vector (a, b, c, d) -> Int -> Box (a, b, c, d) basicUnsafeCopy :: Mutable Vector s (a, b, c, d) -> Vector (a, b, c, d) -> ST s () | |
| Unbox (f (g a)) => Vector Vector (Compose f g a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Compose f g a) -> ST s (Vector (Compose f g a)) basicUnsafeThaw :: Vector (Compose f g a) -> ST s (Mutable Vector s (Compose f g a)) basicLength :: Vector (Compose f g a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Compose f g a) -> Vector (Compose f g a) basicUnsafeIndexM :: Vector (Compose f g a) -> Int -> Box (Compose f g a) basicUnsafeCopy :: Mutable Vector s (Compose f g a) -> Vector (Compose f g a) -> ST s () elemseq :: Vector (Compose f g a) -> Compose f g a -> b -> b | |
| (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Vector Vector (a, b, c, d, e) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (a, b, c, d, e) -> ST s (Vector (a, b, c, d, e)) basicUnsafeThaw :: Vector (a, b, c, d, e) -> ST s (Mutable Vector s (a, b, c, d, e)) basicLength :: Vector (a, b, c, d, e) -> Int basicUnsafeSlice :: Int -> Int -> Vector (a, b, c, d, e) -> Vector (a, b, c, d, e) basicUnsafeIndexM :: Vector (a, b, c, d, e) -> Int -> Box (a, b, c, d, e) basicUnsafeCopy :: Mutable Vector s (a, b, c, d, e) -> Vector (a, b, c, d, e) -> ST s () elemseq :: Vector (a, b, c, d, e) -> (a, b, c, d, e) -> b0 -> b0 | |
| (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Vector Vector (a, b, c, d, e, f) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (a, b, c, d, e, f) -> ST s (Vector (a, b, c, d, e, f)) basicUnsafeThaw :: Vector (a, b, c, d, e, f) -> ST s (Mutable Vector s (a, b, c, d, e, f)) basicLength :: Vector (a, b, c, d, e, f) -> Int basicUnsafeSlice :: Int -> Int -> Vector (a, b, c, d, e, f) -> Vector (a, b, c, d, e, f) basicUnsafeIndexM :: Vector (a, b, c, d, e, f) -> Int -> Box (a, b, c, d, e, f) basicUnsafeCopy :: Mutable Vector s (a, b, c, d, e, f) -> Vector (a, b, c, d, e, f) -> ST s () elemseq :: Vector (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> b0 -> b0 | |
| (Data a, Unbox a) => Data (Vector a) | |
Defined in Data.Vector.Unboxed.Base Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) # toConstr :: Vector a -> Constr # dataTypeOf :: Vector a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) # gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # | |
| NFData (Vector a) | |
Defined in Data.Vector.Unboxed.Base | |
| type Mutable Vector | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector All | |
| newtype Vector Any | |
| newtype Vector Int16 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Int32 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Int64 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Int8 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Word16 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Word32 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Word64 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Word8 | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector CDouble Source # | |
| newtype Vector CFloat Source # | |
| newtype Vector CDouble Source # | |
| newtype Vector () | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Bool | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Char | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Double | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Float | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Int | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector Word | |
Defined in Data.Vector.Unboxed.Base | |
| type Item (Vector e) | |
Defined in Data.Vector.Unboxed | |
| newtype Vector (Complex a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Identity a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Down a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (First a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Last a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Max a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Min a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (WrappedMonoid a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Dual a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Product a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Sum a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (ViaRational a) Source # | |
Defined in Numeric.Rounded.Hardware.Backend.ViaRational | |
| newtype Vector (Interval a) Source # | |
Defined in Numeric.Rounded.Hardware.Interval | |
| newtype Vector (Interval a) Source # | |
Defined in Numeric.Rounded.Hardware.Interval.NonEmpty | |
| newtype Vector (DoNotUnboxLazy a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (DoNotUnboxNormalForm a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (DoNotUnboxStrict a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (UnboxViaPrim a) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Arg a b) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Rounded r a) Source # | |
Defined in Numeric.Rounded.Hardware.Internal.Rounding | |
| newtype Vector (As a b) | |
Defined in Data.Vector.Unboxed.Base | |
| data Vector (a, b) | |
| newtype Vector (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
| newtype Vector (Alt f a) | |
Defined in Data.Vector.Unboxed.Base | |
| data Vector (a, b, c) | |
| data Vector (a, b, c, d) | |
| newtype Vector (Compose f g a) | |
Defined in Data.Vector.Unboxed.Base | |
| data Vector (a, b, c, d, e) | |
| data Vector (a, b, c, d, e, f) | |
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 #
binaryFloatToDecimalDigitsRn Source #
Arguments
| :: 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
| :: 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 #