rounded-hw-0.2.0: Directed rounding for built-in floating types
Safe HaskellNone
LanguageHaskell2010

Numeric.Rounded.Hardware.Internal

Synopsis

Documentation

>>> import Data.Int

binaryFloatToDecimalDigitsRn Source #

Arguments

:: forall a. RealFloat a 
=> RoundingMode

rounding mode

-> Int

prec

-> a

a non-negative number (zero, normal or subnormal)

-> ([Int], Int) 
>>> binaryFloatToDecimalDigitsRn ToNearest 3 (0.125 :: Double)
([1,2,5],0)
>>> binaryFloatToDecimalDigitsRn ToNearest 3 (12.5 :: Double)
([1,2,5],2)

binaryFloatToFixedDecimalDigitsRn Source #

Arguments

:: forall a. RealFloat a 
=> RoundingMode

rounding mode

-> Int

prec

-> a

a non-negative number (zero, normal or subnormal)

-> [Int] 
>>> binaryFloatToFixedDecimalDigitsRn ToNearest 3 (0.125 :: Double)
[1,2,5]
>>> binaryFloatToFixedDecimalDigitsRn ToNearest 3 (12.5 :: Double)
[1,2,5,0,0]

binaryFloatToDecimalDigits Source #

Arguments

:: RealFloat a 
=> a

a non-negative number (zero, normal or subnormal)

-> ([Int], Int) 
>>> 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"

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

Instances details
Bounded RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Enum RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Eq RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Ord RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Read RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Show RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Generic RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Associated Types

type Rep RoundingMode :: Type -> Type #

NFData RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

rnf :: RoundingMode -> () #

type Rep RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

type Rep RoundingMode = D1 ('MetaData "RoundingMode" "Numeric.Rounded.Hardware.Internal.Rounding" "rounded-hw-0.2.0-G2mMTdTBXOG87Ub6xfZ4rG" '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)))

oppositeRoundingMode :: RoundingMode -> RoundingMode Source #

Returns the opposite rounding direction.

TowardNegInf and TowardInf are swapped.

class Rounding (r :: RoundingMode) Source #

This class allows you to recover the runtime value from a type-level rounding mode.

See rounding.

Minimal complete definition

roundingT

rounding :: Rounding r => proxy r -> RoundingMode Source #

Recovers the value from type-level rounding mode.

reifyRounding :: RoundingMode -> (forall s. Rounding s => Proxy s -> a) -> a Source #

Lifts a rounding mode to type-level.

newtype Rounded (r :: RoundingMode) a Source #

A type tagged with a rounding direction.

The rounding direction is effective for a single operation. You won't get the correctly-rounded result for a compound expression like (a - b * c) :: Rounded 'TowardInf Double.

In particular, a negative literal like -0.1 :: Rounded r Double doesn't yield the correctly-rounded value for -0.1. To get the correct value, call fromRational explicitly (i.e. fromRational (-0.1) :: Rounded r Double) or use NegativeLiterals extension.

Constructors

Rounded 

Fields

Instances

Instances details
Unbox a => Vector Vector (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Rounded r a) -> m (Vector (Rounded r a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Rounded r a) -> m (Mutable Vector (PrimState m) (Rounded r a)) #

basicLength :: Vector (Rounded r a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Rounded r a) -> Vector (Rounded r a) #

basicUnsafeIndexM :: Monad m => Vector (Rounded r a) -> Int -> m (Rounded r a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Rounded r a) -> Vector (Rounded r a) -> m () #

elemseq :: Vector (Rounded r a) -> Rounded r a -> b -> b #

Unbox a => MVector MVector (Rounded r a) Source # 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Rounded r a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Rounded r a -> m (MVector (PrimState m) (Rounded r a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> m (Rounded r a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> Rounded r a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Rounded r a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> m (MVector (PrimState m) (Rounded r a)) #

Functor (Rounded r) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

fmap :: (a -> b) -> Rounded r a -> Rounded r b #

(<$) :: a -> Rounded r b -> Rounded r a #

Eq a => Eq (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

(==) :: Rounded r a -> Rounded r a -> Bool #

(/=) :: Rounded r a -> Rounded r a -> Bool #

(Rounding r, Num a, RoundedFractional a) => Fractional (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

Methods

(/) :: Rounded r a -> Rounded r a -> Rounded r a #

recip :: Rounded r a -> Rounded r a #

fromRational :: Rational -> Rounded r a #

(Rounding r, Num a, RoundedRing a) => Num (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

Methods

(+) :: Rounded r a -> Rounded r a -> Rounded r a #

(-) :: Rounded r a -> Rounded r a -> Rounded r a #

(*) :: Rounded r a -> Rounded r a -> Rounded r a #

negate :: Rounded r a -> Rounded r a #

abs :: Rounded r a -> Rounded r a #

signum :: Rounded r a -> Rounded r a #

fromInteger :: Integer -> Rounded r a #

Ord a => Ord (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

compare :: Rounded r a -> Rounded r a -> Ordering #

(<) :: Rounded r a -> Rounded r a -> Bool #

(<=) :: Rounded r a -> Rounded r a -> Bool #

(>) :: Rounded r a -> Rounded r a -> Bool #

(>=) :: Rounded r a -> Rounded r a -> Bool #

max :: Rounded r a -> Rounded r a -> Rounded r a #

min :: Rounded r a -> Rounded r a -> Rounded r a #

(Rounding r, Real a, RoundedFractional a) => Real (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

Methods

toRational :: Rounded r a -> Rational #

(Rounding r, RealFrac a, RoundedFractional a) => RealFrac (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

Methods

properFraction :: Integral b => Rounded r a -> (b, Rounded r a) #

truncate :: Integral b => Rounded r a -> b #

round :: Integral b => Rounded r a -> b #

ceiling :: Integral b => Rounded r a -> b #

floor :: Integral b => Rounded r a -> b #

Show a => Show (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

showsPrec :: Int -> Rounded r a -> ShowS #

show :: Rounded r a -> String #

showList :: [Rounded r a] -> ShowS #

Generic (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Associated Types

type Rep (Rounded r a) :: Type -> Type #

Methods

from :: Rounded r a -> Rep (Rounded r a) x #

to :: Rep (Rounded r a) x -> Rounded r a #

Storable a => Storable (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

sizeOf :: Rounded r a -> Int #

alignment :: Rounded r a -> Int #

peekElemOff :: Ptr (Rounded r a) -> Int -> IO (Rounded r a) #

pokeElemOff :: Ptr (Rounded r a) -> Int -> Rounded r a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rounded r a) #

pokeByteOff :: Ptr b -> Int -> Rounded r a -> IO () #

peek :: Ptr (Rounded r a) -> IO (Rounded r a) #

poke :: Ptr (Rounded r a) -> Rounded r a -> IO () #

NFData a => NFData (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

rnf :: Rounded r a -> () #

Unbox a => Unbox (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

newtype MVector s (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

newtype MVector s (Rounded r a) = MV_Rounded (MVector s a)
type Rep (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

type Rep (Rounded r a) = D1 ('MetaData "Rounded" "Numeric.Rounded.Hardware.Internal.Rounding" "rounded-hw-0.2.0-G2mMTdTBXOG87Ub6xfZ4rG" 'True) (C1 ('MetaCons "Rounded" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRounded") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
newtype Vector (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

newtype Vector (Rounded r a) = V_Rounded (Vector a)

data family MVector s a #

Instances

Instances details
MVector MVector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector () 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) ()) #

basicInitialize :: PrimMonad m => MVector (PrimState m) () -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> () -> m (MVector (PrimState m) ()) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) () -> Int -> m () #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) () -> Int -> () -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) () -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) () -> () -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) () -> MVector (PrimState m) () -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) () -> MVector (PrimState m) () -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) () -> Int -> m (MVector (PrimState m) ()) #

MVector MVector All 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Any 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

MVector MVector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

MVector MVector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

Unbox a => MVector MVector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Min a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Min a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Min a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Min a -> m (MVector (PrimState m) (Min a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Min a) -> Int -> m (Min a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Min a) -> Int -> Min a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Min a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Min a) -> Min a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Min a) -> MVector (PrimState m) (Min a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Min a) -> MVector (PrimState m) (Min a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Min a) -> Int -> m (MVector (PrimState m) (Min a)) #

Unbox a => MVector MVector (Max a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Max a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Max a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Max a -> m (MVector (PrimState m) (Max a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Max a) -> Int -> m (Max a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Max a) -> Int -> Max a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Max a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Max a) -> Max a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Max a) -> MVector (PrimState m) (Max a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Max a) -> MVector (PrimState m) (Max a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Max a) -> Int -> m (MVector (PrimState m) (Max a)) #

Unbox a => MVector MVector (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Last a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Last a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Last a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Last a -> m (MVector (PrimState m) (Last a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Last a) -> Int -> m (Last a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Last a) -> Int -> Last a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Last a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Last a) -> Last a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Last a) -> MVector (PrimState m) (Last a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Last a) -> MVector (PrimState m) (Last a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Last a) -> Int -> m (MVector (PrimState m) (Last a)) #

Unbox a => MVector MVector (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Dual a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Dual a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Dual a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Dual a -> m (MVector (PrimState m) (Dual a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Dual a) -> Int -> m (Dual a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Dual a) -> Int -> Dual a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Dual a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Dual a) -> Dual a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Dual a) -> MVector (PrimState m) (Dual a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Dual a) -> MVector (PrimState m) (Dual a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Dual a) -> Int -> m (MVector (PrimState m) (Dual a)) #

Unbox a => MVector MVector (Sum a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Sum a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Sum a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Sum a -> m (MVector (PrimState m) (Sum a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Sum a) -> Int -> m (Sum a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Sum a) -> Int -> Sum a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Sum a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Sum a) -> Sum a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Sum a) -> MVector (PrimState m) (Sum a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Sum a) -> MVector (PrimState m) (Sum a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Sum a) -> Int -> m (MVector (PrimState m) (Sum a)) #

Unbox a => MVector MVector (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Down a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Down a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Down a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Down a -> m (MVector (PrimState m) (Down a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Down a) -> Int -> m (Down a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Down a) -> Int -> Down a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Down a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Down a) -> Down a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Down a) -> MVector (PrimState m) (Down a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Down a) -> MVector (PrimState m) (Down a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Down a) -> Int -> m (MVector (PrimState m) (Down a)) #

Unbox a => MVector MVector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(Unbox a, Ord a, Fractional a) => MVector MVector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval.NonEmpty

(Unbox a, Ord a, Fractional a) => MVector MVector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval

(Unbox a, Unbox b) => MVector MVector (a, b) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (a, b)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a, b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b) -> m (MVector (PrimState m) (a, b)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a, b) -> Int -> m (a, b) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a, b) -> Int -> (a, b) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a, b) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a, b) -> (a, b) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a, b) -> MVector (PrimState m) (a, b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a, b) -> MVector (PrimState m) (a, b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a, b) -> Int -> m (MVector (PrimState m) (a, b)) #

(Unbox a, Unbox b) => MVector MVector (Arg a b) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Arg a b)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Arg a b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Arg a b -> m (MVector (PrimState m) (Arg a b)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Arg a b) -> Int -> m (Arg a b) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Arg a b) -> Int -> Arg a b -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Arg a b) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Arg a b) -> Arg a b -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Arg a b) -> MVector (PrimState m) (Arg a b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Arg a b) -> MVector (PrimState m) (Arg a b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Arg a b) -> Int -> m (MVector (PrimState m) (Arg a b)) #

Unbox a => MVector MVector (Rounded r a) Source # 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Rounded r a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Rounded r a -> m (MVector (PrimState m) (Rounded r a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> m (Rounded r a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> Rounded r a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Rounded r a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> m (MVector (PrimState m) (Rounded r a)) #

(Unbox a, Unbox b, Unbox c) => MVector MVector (a, b, c) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (a, b, c)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a, b, c) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b, c) -> m (MVector (PrimState m) (a, b, c)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a, b, c) -> Int -> m (a, b, c) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a, b, c) -> Int -> (a, b, c) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a, b, c) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a, b, c) -> (a, b, c) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a, b, c) -> MVector (PrimState m) (a, b, c) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a, b, c) -> MVector (PrimState m) (a, b, c) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a, b, c) -> Int -> m (MVector (PrimState m) (a, b, c)) #

Unbox a => MVector MVector (Const a b) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Const a b)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Const a b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Const a b -> m (MVector (PrimState m) (Const a b)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> m (Const a b) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> Const a b -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Const a b) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Const a b) -> Const a b -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Const a b) -> MVector (PrimState m) (Const a b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Const a b) -> MVector (PrimState m) (Const a b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> m (MVector (PrimState m) (Const a b)) #

Unbox (f a) => MVector MVector (Alt f a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Alt f a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Alt f a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Alt f a -> m (MVector (PrimState m) (Alt f a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Int -> m (Alt f a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Int -> Alt f a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Alt f a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Alt f a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Alt f a) -> MVector (PrimState m) (Alt f a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Alt f a) -> MVector (PrimState m) (Alt f a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Int -> m (MVector (PrimState m) (Alt f a)) #

(Unbox a, Unbox b, Unbox c, Unbox d) => MVector MVector (a, b, c, d) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (a, b, c, d)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b, c, d) -> m (MVector (PrimState m) (a, b, c, d)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> Int -> m (a, b, c, d) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> Int -> (a, b, c, d) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> (a, b, c, d) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> MVector (PrimState m) (a, b, c, d) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> MVector (PrimState m) (a, b, c, d) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> Int -> m (MVector (PrimState m) (a, b, c, d)) #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => MVector MVector (a, b, c, d, e) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (a, b, c, d, e)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b, c, d, e) -> m (MVector (PrimState m) (a, b, c, d, e)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> Int -> m (a, b, c, d, e) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> Int -> (a, b, c, d, e) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> (a, b, c, d, e) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> MVector (PrimState m) (a, b, c, d, e) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> MVector (PrimState m) (a, b, c, d, e) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> Int -> m (MVector (PrimState m) (a, b, c, d, e)) #

Unbox (f (g a)) => MVector MVector (Compose f g a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Compose f g a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Compose f g a -> m (MVector (PrimState m) (Compose f g a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> Int -> m (Compose f g a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> Int -> Compose f g a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> Compose f g a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> MVector (PrimState m) (Compose f g a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> MVector (PrimState m) (Compose f g a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> Int -> m (MVector (PrimState m) (Compose f g a)) #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => MVector MVector (a, b, c, d, e, f) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (a, b, c, d, e, f)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b, c, d, e, f) -> m (MVector (PrimState m) (a, b, c, d, e, f)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> Int -> m (a, b, c, d, e, f) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> Int -> (a, b, c, d, e, f) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> MVector (PrimState m) (a, b, c, d, e, f) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> MVector (PrimState m) (a, b, c, d, e, f) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> Int -> m (MVector (PrimState m) (a, b, c, d, e, f)) #

NFData1 (MVector s)

Since: vector-0.12.1.0

Instance details

Defined in Data.Vector.Unboxed.Base

Methods

liftRnf :: (a -> ()) -> MVector s a -> () #

NFData (MVector s a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnf :: MVector s a -> () #

newtype MVector s All 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s All = MV_All (MVector s Bool)
newtype MVector s Any 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Any = MV_Any (MVector s Bool)
newtype MVector s Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Bool = MV_Bool (MVector s Word8)
newtype MVector s Char 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Char = MV_Char (MVector s Char)
newtype MVector s Double 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Float 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word = MV_Word (MVector s Word)
newtype MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 = MV_Int8 (MVector s Int8)
newtype MVector s Int 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int = MV_Int (MVector s Int)
newtype MVector s () 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s () = MV_Unit Int
newtype MVector s CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

newtype MVector s CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

newtype MVector s CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

newtype MVector s (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Last a) = MV_Last (MVector s a)
newtype MVector s (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (First a) = MV_First (MVector s a)
newtype MVector s (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Max a) = MV_Max (MVector s a)
newtype MVector s (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Min a) = MV_Min (MVector s a)
newtype MVector s (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Product a) = MV_Product (MVector s a)
newtype MVector s (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Sum a) = MV_Sum (MVector s a)
newtype MVector s (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Dual a) = MV_Dual (MVector s a)
newtype MVector s (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Down a) = MV_Down (MVector s a)
newtype MVector s (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Identity a) = MV_Identity (MVector s a)
newtype MVector s (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Complex a) = MV_Complex (MVector s (a, a))
newtype MVector s (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

newtype MVector s (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval.NonEmpty

newtype MVector s (Interval a) = MV_Interval (MVector s (a, a))
newtype MVector s (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval

newtype MVector s (Interval a) = MV_Interval (MVector s (a, a))
newtype MVector s (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

newtype MVector s (Rounded r a) = MV_Rounded (MVector s a)
data MVector s (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b) = MV_2 !Int !(MVector s a) !(MVector s b)
newtype MVector s (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Arg a b) = MV_Arg (MVector s (a, b))
data MVector s (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c) = MV_3 !Int !(MVector s a) !(MVector s b) !(MVector s c)
newtype MVector s (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Alt f a) = MV_Alt (MVector s (f a))
newtype MVector s (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Const a b) = MV_Const (MVector s a)
data MVector s (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c, d) = MV_4 !Int !(MVector s a) !(MVector s b) !(MVector s c) !(MVector s d)
data MVector s (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c, d, e) = MV_5 !Int !(MVector s a) !(MVector s b) !(MVector s c) !(MVector s d) !(MVector s e)
newtype MVector s (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Compose f g a) = MV_Compose (MVector s (f (g a)))
data MVector s (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c, d, e, f) = MV_6 !Int !(MVector s a) !(MVector s b) !(MVector s c) !(MVector s d) !(MVector s e) !(MVector s f)

data family Vector a #

Instances

Instances details
NFData1 Vector

Since: vector-0.12.1.0

Instance details

Defined in Data.Vector.Unboxed.Base

Methods

liftRnf :: (a -> ()) -> Vector a -> () #

Vector Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector () 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) () -> m (Vector ()) #

basicUnsafeThaw :: PrimMonad m => Vector () -> m (Mutable Vector (PrimState m) ()) #

basicLength :: Vector () -> Int #

basicUnsafeSlice :: Int -> Int -> Vector () -> Vector () #

basicUnsafeIndexM :: Monad m => Vector () -> Int -> m () #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) () -> Vector () -> m () #

elemseq :: Vector () -> () -> b -> b #

Vector Vector All 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Any 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

RoundedSqrt_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedSqrt_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedSqrt_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedSqrt_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedSqrt_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

RoundedFractional_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedFractional_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedFractional_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedFractional_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedFractional_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

RoundedRing_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedRing_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedRing_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedRing_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedRing_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

Unbox a => Vector Vector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Min a) -> m (Vector (Min a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Min a) -> m (Mutable Vector (PrimState m) (Min a)) #

basicLength :: Vector (Min a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Min a) -> Vector (Min a) #

basicUnsafeIndexM :: Monad m => Vector (Min a) -> Int -> m (Min a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Min a) -> Vector (Min a) -> m () #

elemseq :: Vector (Min a) -> Min a -> b -> b #

Unbox a => Vector Vector (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Max a) -> m (Vector (Max a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Max a) -> m (Mutable Vector (PrimState m) (Max a)) #

basicLength :: Vector (Max a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Max a) -> Vector (Max a) #

basicUnsafeIndexM :: Monad m => Vector (Max a) -> Int -> m (Max a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Max a) -> Vector (Max a) -> m () #

elemseq :: Vector (Max a) -> Max a -> b -> b #

Unbox a => Vector Vector (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Last a) -> m (Vector (Last a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Last a) -> m (Mutable Vector (PrimState m) (Last a)) #

basicLength :: Vector (Last a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Last a) -> Vector (Last a) #

basicUnsafeIndexM :: Monad m => Vector (Last a) -> Int -> m (Last a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Last a) -> Vector (Last a) -> m () #

elemseq :: Vector (Last a) -> Last a -> b -> b #

Unbox a => Vector Vector (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Dual a) -> m (Vector (Dual a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Dual a) -> m (Mutable Vector (PrimState m) (Dual a)) #

basicLength :: Vector (Dual a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Dual a) -> Vector (Dual a) #

basicUnsafeIndexM :: Monad m => Vector (Dual a) -> Int -> m (Dual a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Dual a) -> Vector (Dual a) -> m () #

elemseq :: Vector (Dual a) -> Dual a -> b -> b #

Unbox a => Vector Vector (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Sum a) -> m (Vector (Sum a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Sum a) -> m (Mutable Vector (PrimState m) (Sum a)) #

basicLength :: Vector (Sum a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Sum a) -> Vector (Sum a) #

basicUnsafeIndexM :: Monad m => Vector (Sum a) -> Int -> m (Sum a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Sum a) -> Vector (Sum a) -> m () #

elemseq :: Vector (Sum a) -> Sum a -> b -> b #

Unbox a => Vector Vector (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Down a) -> m (Vector (Down a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Down a) -> m (Mutable Vector (PrimState m) (Down a)) #

basicLength :: Vector (Down a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Down a) -> Vector (Down a) #

basicUnsafeIndexM :: Monad m => Vector (Down a) -> Int -> m (Down a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Down a) -> Vector (Down a) -> m () #

elemseq :: Vector (Down a) -> Down a -> b -> b #

Unbox a => Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(Unbox a, Ord a, Fractional a) => Vector Vector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval.NonEmpty

(Unbox a, Ord a, Fractional a) => Vector Vector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval

(RealFloat a, RealFloatConstants a, Unbox a) => RoundedSqrt_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(RealFloat a, RealFloatConstants a, Unbox a) => RoundedFractional_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(RealFloat a, RealFloatConstants a, Unbox a) => RoundedRing_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(Unbox a, Unbox b) => Vector Vector (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a, b) -> m (Vector (a, b)) #

basicUnsafeThaw :: PrimMonad m => Vector (a, b) -> m (Mutable Vector (PrimState m) (a, b)) #

basicLength :: Vector (a, b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a, b) -> Vector (a, b) #

basicUnsafeIndexM :: Monad m => Vector (a, b) -> Int -> m (a, b) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a, b) -> Vector (a, b) -> m () #

elemseq :: Vector (a, b) -> (a, b) -> b0 -> b0 #

(Unbox a, Unbox b) => Vector Vector (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Arg a b) -> m (Vector (Arg a b)) #

basicUnsafeThaw :: PrimMonad m => Vector (Arg a b) -> m (Mutable Vector (PrimState m) (Arg a b)) #

basicLength :: Vector (Arg a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Arg a b) -> Vector (Arg a b) #

basicUnsafeIndexM :: Monad m => Vector (Arg a b) -> Int -> m (Arg a b) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Arg a b) -> Vector (Arg a b) -> m () #

elemseq :: Vector (Arg a b) -> Arg a b -> b0 -> b0 #

Unbox a => Vector Vector (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Rounded r a) -> m (Vector (Rounded r a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Rounded r a) -> m (Mutable Vector (PrimState m) (Rounded r a)) #

basicLength :: Vector (Rounded r a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Rounded r a) -> Vector (Rounded r a) #

basicUnsafeIndexM :: Monad m => Vector (Rounded r a) -> Int -> m (Rounded r a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Rounded r a) -> Vector (Rounded r a) -> m () #

elemseq :: Vector (Rounded r a) -> Rounded r a -> b -> b #

(Unbox a, Unbox b, Unbox c) => Vector Vector (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c) -> m (Vector (a, b, c)) #

basicUnsafeThaw :: PrimMonad m => Vector (a, b, c) -> m (Mutable Vector (PrimState m) (a, b, c)) #

basicLength :: Vector (a, b, c) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a, b, c) -> Vector (a, b, c) #

basicUnsafeIndexM :: Monad m => Vector (a, b, c) -> Int -> m (a, b, c) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c) -> Vector (a, b, c) -> m () #

elemseq :: Vector (a, b, c) -> (a, b, c) -> b0 -> b0 #

Unbox a => Vector Vector (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Const a b) -> m (Vector (Const a b)) #

basicUnsafeThaw :: PrimMonad m => Vector (Const a b) -> m (Mutable Vector (PrimState m) (Const a b)) #

basicLength :: Vector (Const a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Const a b) -> Vector (Const a b) #

basicUnsafeIndexM :: Monad m => Vector (Const a b) -> Int -> m (Const a b) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Const a b) -> Vector (Const a b) -> m () #

elemseq :: Vector (Const a b) -> Const a b -> b0 -> b0 #

Unbox (f a) => Vector Vector (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Alt f a) -> m (Vector (Alt f a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Alt f a) -> m (Mutable Vector (PrimState m) (Alt f a)) #

basicLength :: Vector (Alt f a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Alt f a) -> Vector (Alt f a) #

basicUnsafeIndexM :: Monad m => Vector (Alt f a) -> Int -> m (Alt f a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Alt f a) -> Vector (Alt f a) -> m () #

elemseq :: Vector (Alt f a) -> Alt f a -> b -> b #

(Unbox a, Unbox b, Unbox c, Unbox d) => Vector Vector (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d) -> m (Vector (a, b, c, d)) #

basicUnsafeThaw :: PrimMonad m => Vector (a, b, c, d) -> m (Mutable Vector (PrimState m) (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 :: Monad m => Vector (a, b, c, d) -> Int -> m (a, b, c, d) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d) -> Vector (a, b, c, d) -> m () #

elemseq :: Vector (a, b, c, d) -> (a, b, c, d) -> b0 -> b0 #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Vector Vector (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d, e) -> m (Vector (a, b, c, d, e)) #

basicUnsafeThaw :: PrimMonad m => Vector (a, b, c, d, e) -> m (Mutable Vector (PrimState m) (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 :: Monad m => Vector (a, b, c, d, e) -> Int -> m (a, b, c, d, e) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d, e) -> Vector (a, b, c, d, e) -> m () #

elemseq :: Vector (a, b, c, d, e) -> (a, b, c, d, e) -> b0 -> b0 #

Unbox (f (g a)) => Vector Vector (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Compose f g a) -> m (Vector (Compose f g a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Compose f g a) -> m (Mutable Vector (PrimState m) (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 :: Monad m => Vector (Compose f g a) -> Int -> m (Compose f g a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Compose f g a) -> Vector (Compose f g a) -> m () #

elemseq :: Vector (Compose f g a) -> Compose f g a -> b -> b #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Vector Vector (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d, e, f) -> m (Vector (a, b, c, d, e, f)) #

basicUnsafeThaw :: PrimMonad m => Vector (a, b, c, d, e, f) -> m (Mutable Vector (PrimState m) (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 :: Monad m => Vector (a, b, c, d, e, f) -> Int -> m (a, b, c, d, e, f) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d, e, f) -> Vector (a, b, c, d, e, f) -> m () #

elemseq :: Vector (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> b0 -> b0 #

(Data a, Unbox a) => Data (Vector a) 
Instance details

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) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnf :: Vector a -> () #

newtype Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int = V_Int (Vector Int)
newtype Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector () 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector () = V_Unit Int
newtype Vector All 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector All = V_All (Vector Bool)
newtype Vector Any 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Any = V_Any (Vector Bool)
newtype Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

newtype Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

newtype Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

type Mutable Vector 
Instance details

Defined in Data.Vector.Unboxed.Base

type Item (Vector e) 
Instance details

Defined in Data.Vector.Unboxed

type Item (Vector e) = e
newtype Vector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Complex a) = V_Complex (Vector (a, a))
newtype Vector (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Min a) = V_Min (Vector a)
newtype Vector (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Max a) = V_Max (Vector a)
newtype Vector (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (First a) = V_First (Vector a)
newtype Vector (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Last a) = V_Last (Vector a)
newtype Vector (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Identity a) = V_Identity (Vector a)
newtype Vector (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Dual a) = V_Dual (Vector a)
newtype Vector (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Sum a) = V_Sum (Vector a)
newtype Vector (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Product a) = V_Product (Vector a)
newtype Vector (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Down a) = V_Down (Vector a)
newtype Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

newtype Vector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval.NonEmpty

newtype Vector (Interval a) = V_Interval (Vector (a, a))
newtype Vector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval

newtype Vector (Interval a) = V_Interval (Vector (a, a))
data Vector (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b) = V_2 !Int !(Vector a) !(Vector b)
newtype Vector (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Arg a b) = V_Arg (Vector (a, b))
newtype Vector (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

newtype Vector (Rounded r a) = V_Rounded (Vector a)
data Vector (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c) = V_3 !Int !(Vector a) !(Vector b) !(Vector c)
newtype Vector (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Const a b) = V_Const (Vector a)
newtype Vector (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Alt f a) = V_Alt (Vector (f a))
data Vector (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c, d) = V_4 !Int !(Vector a) !(Vector b) !(Vector c) !(Vector d)
data Vector (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c, d, e) = V_5 !Int !(Vector a) !(Vector b) !(Vector c) !(Vector d) !(Vector e)
newtype Vector (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Compose f g a) = V_Compose (Vector (f (g a)))
data Vector (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c, d, e, f) = V_6 !Int !(Vector a) !(Vector b) !(Vector c) !(Vector d) !(Vector e) !(Vector f)

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 zero
0.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 zero
0.0
>>> nextTowardZero (-0 :: Double) -- returns negative zero
-0.0
>>> nextTowardZero 0x1p-1074 :: Double
0.0

fusedMultiplyAdd :: RealFloat a => a -> a -> a -> a #

fusedMultiplyAdd a b c computes a * 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)

class RealFloatConstants a where Source #

Methods

positiveInfinity :: a Source #

\(+\infty\)

negativeInfinity :: a Source #

\(-\infty\)

maxFinite :: a Source #

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

Instances details
RealFloatConstants Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Constants

RealFloatConstants Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Constants

RealFloatConstants LongDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.X87LongDouble

class (RoundedSqrt a, RoundedRing_Vector vector a) => RoundedSqrt_Vector vector a where Source #

Lifted version of RoundedSqrt

Minimal complete definition

Nothing

Methods

map_roundedSqrt :: RoundingMode -> vector a -> vector a Source #

Equivalent to map . roundedSqrt

default map_roundedSqrt :: Vector vector a => RoundingMode -> vector a -> vector a Source #

Instances

Instances details
RoundedSqrt_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedSqrt_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedSqrt_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedSqrt_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedSqrt_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

RoundedSqrt_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedSqrt_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedSqrt_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedSqrt_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedSqrt_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

(RealFloat a, RealFloatConstants a, Unbox a) => RoundedSqrt_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(RealFloat a, RealFloatConstants a, Storable a) => RoundedSqrt_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

class (RoundedFractional a, RoundedRing_Vector vector a) => RoundedFractional_Vector vector a where Source #

Lifted version of RoundedFractional

Minimal complete definition

Nothing

Methods

zipWith_roundedDiv :: RoundingMode -> vector a -> vector a -> vector a Source #

Equivalent to zipWith . roundedDiv

default zipWith_roundedDiv :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #

Instances

Instances details
RoundedFractional_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedFractional_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedFractional_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedFractional_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedFractional_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

RoundedFractional_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedFractional_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedFractional_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedFractional_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedFractional_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

(RealFloat a, RealFloatConstants a, Unbox a) => RoundedFractional_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(RealFloat a, RealFloatConstants a, Storable a) => RoundedFractional_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

class RoundedRing a => RoundedRing_Vector vector a where Source #

Lifted version of RoundedRing

Minimal complete definition

Nothing

Methods

roundedSum :: RoundingMode -> vector a -> a Source #

Equivalent to \r -> foldl (roundedAdd r) 0

default roundedSum :: (Vector vector a, Num a) => RoundingMode -> vector a -> a Source #

zipWith_roundedAdd :: RoundingMode -> vector a -> vector a -> vector a Source #

Equivalent to zipWith . roundedAdd

default zipWith_roundedAdd :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #

zipWith_roundedSub :: RoundingMode -> vector a -> vector a -> vector a Source #

Equivalent to zipWith . roundedSub

default zipWith_roundedSub :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #

zipWith_roundedMul :: RoundingMode -> vector a -> vector a -> vector a Source #

Equivalent to zipWith . roundedMul

default zipWith_roundedMul :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a Source #

zipWith3_roundedFusedMultiplyAdd :: RoundingMode -> vector a -> vector a -> vector a -> vector a Source #

Equivalent to zipWith3 . roundedFusedMultiplyAdd

default zipWith3_roundedFusedMultiplyAdd :: Vector vector a => RoundingMode -> vector a -> vector a -> vector a -> vector a Source #

Instances

Instances details
RoundedRing_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedRing_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedRing_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedRing_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedRing_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

RoundedRing_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedRing_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedRing_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedRing_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedRing_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

(RealFloat a, RealFloatConstants a, Unbox a) => RoundedRing_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(RealFloat a, RealFloatConstants a, Storable a) => RoundedRing_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

class RoundedRing a => RoundedSqrt a where Source #

Rounding-controlled version of sqrt.

Minimal complete definition

roundedSqrt

Instances

Instances details
RoundedSqrt Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedSqrt Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedSqrt LongDouble Source #

Only available on x86/x86_64 systems. Note that LongDouble may not work correctly on Win64.

Instance details

Defined in Numeric.Rounded.Hardware.Backend.X87LongDouble

RoundedSqrt CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedSqrt CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedSqrt CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

(RealFloat a, RealFloatConstants a) => RoundedSqrt (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

class RoundedRing a => RoundedFractional a where Source #

Rounding-controlled version of Fractional.

Minimal complete definition

roundedDiv

Instances

Instances details
RoundedFractional Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedFractional Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedFractional Integer Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

RoundedFractional LongDouble Source #

Only available on x86/x86_64 systems. Note that LongDouble may not work correctly on Win64.

Instance details

Defined in Numeric.Rounded.Hardware.Backend.X87LongDouble

RoundedFractional CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedFractional CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedFractional CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

Integral a => RoundedFractional (Ratio a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

(RealFloat a, Num a, RealFloatConstants a) => RoundedFractional (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

class Ord a => RoundedRing a where Source #

Rounding-controlled version of Num.

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 #

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

Instances details
RoundedRing Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedRing Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedRing Integer Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

RoundedRing LongDouble Source #

Only available on x86/x86_64 systems. Note that LongDouble may not work correctly on Win64.

Instance details

Defined in Numeric.Rounded.Hardware.Backend.X87LongDouble

Methods

roundedAdd :: RoundingMode -> LongDouble -> LongDouble -> LongDouble Source #

roundedSub :: RoundingMode -> LongDouble -> LongDouble -> LongDouble Source #

roundedMul :: RoundingMode -> LongDouble -> LongDouble -> LongDouble Source #

roundedFusedMultiplyAdd :: RoundingMode -> LongDouble -> LongDouble -> LongDouble -> LongDouble Source #

roundedFromInteger :: RoundingMode -> Integer -> LongDouble Source #

intervalAdd :: Rounded 'TowardNegInf LongDouble -> Rounded 'TowardInf LongDouble -> Rounded 'TowardNegInf LongDouble -> Rounded 'TowardInf LongDouble -> (Rounded 'TowardNegInf LongDouble, Rounded 'TowardInf LongDouble) Source #

intervalSub :: Rounded 'TowardNegInf LongDouble -> Rounded 'TowardInf LongDouble -> Rounded 'TowardNegInf LongDouble -> Rounded 'TowardInf LongDouble -> (Rounded 'TowardNegInf LongDouble, Rounded 'TowardInf LongDouble) Source #

intervalMul :: Rounded 'TowardNegInf LongDouble -> Rounded 'TowardInf LongDouble -> Rounded 'TowardNegInf LongDouble -> Rounded 'TowardInf LongDouble -> (Rounded 'TowardNegInf LongDouble, Rounded 'TowardInf LongDouble) Source #

intervalMulAdd :: Rounded 'TowardNegInf LongDouble -> Rounded 'TowardInf LongDouble -> Rounded 'TowardNegInf LongDouble -> Rounded 'TowardInf LongDouble -> Rounded 'TowardNegInf LongDouble -> Rounded 'TowardInf LongDouble -> (Rounded 'TowardNegInf LongDouble, Rounded 'TowardInf LongDouble) Source #

intervalFromInteger :: Integer -> (Rounded 'TowardNegInf LongDouble, Rounded 'TowardInf LongDouble) Source #

backendNameT :: Tagged LongDouble String Source #

RoundedRing CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedRing CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedRing CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

Integral a => RoundedRing (Ratio a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

(RealFloat a, Num a, RealFloatConstants a) => RoundedRing (ViaRational a) Source # 
Instance details

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 #

backendName :: RoundedRing a => proxy a -> String Source #

Returns the name of backend as a string.

Example:

>>> :m + Data.Proxy
>>> backendName (Proxy :: Proxy Double)
"FastFFI+SSE2"

data RoundingMode Source #

The type for IEEE754 rounding-direction attributes.

Constructors

ToNearest

Round to the nearest value (IEEE754 roundTiesToEven)

TowardNegInf

Round downward (IEEE754 roundTowardNegative)

TowardInf

Round upward (IEEE754 roundTowardPositive)

TowardZero

Round toward zero (IEEE754 roundTowardZero)

Instances

Instances details
Bounded RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Enum RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Eq RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Ord RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Read RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Show RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Generic RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Associated Types

type Rep RoundingMode :: Type -> Type #

NFData RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

rnf :: RoundingMode -> () #

type Rep RoundingMode Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

type Rep RoundingMode = D1 ('MetaData "RoundingMode" "Numeric.Rounded.Hardware.Internal.Rounding" "rounded-hw-0.2.0-G2mMTdTBXOG87Ub6xfZ4rG" '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)))

oppositeRoundingMode :: RoundingMode -> RoundingMode Source #

Returns the opposite rounding direction.

TowardNegInf and TowardInf are swapped.

class Rounding (r :: RoundingMode) Source #

This class allows you to recover the runtime value from a type-level rounding mode.

See rounding.

Minimal complete definition

roundingT

rounding :: Rounding r => proxy r -> RoundingMode Source #

Recovers the value from type-level rounding mode.

reifyRounding :: RoundingMode -> (forall s. Rounding s => Proxy s -> a) -> a Source #

Lifts a rounding mode to type-level.

newtype Rounded (r :: RoundingMode) a Source #

A type tagged with a rounding direction.

The rounding direction is effective for a single operation. You won't get the correctly-rounded result for a compound expression like (a - b * c) :: Rounded 'TowardInf Double.

In particular, a negative literal like -0.1 :: Rounded r Double doesn't yield the correctly-rounded value for -0.1. To get the correct value, call fromRational explicitly (i.e. fromRational (-0.1) :: Rounded r Double) or use NegativeLiterals extension.

Constructors

Rounded 

Fields

Instances

Instances details
Unbox a => Vector Vector (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Rounded r a) -> m (Vector (Rounded r a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Rounded r a) -> m (Mutable Vector (PrimState m) (Rounded r a)) #

basicLength :: Vector (Rounded r a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Rounded r a) -> Vector (Rounded r a) #

basicUnsafeIndexM :: Monad m => Vector (Rounded r a) -> Int -> m (Rounded r a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Rounded r a) -> Vector (Rounded r a) -> m () #

elemseq :: Vector (Rounded r a) -> Rounded r a -> b -> b #

Unbox a => MVector MVector (Rounded r a) Source # 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Rounded r a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Rounded r a -> m (MVector (PrimState m) (Rounded r a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> m (Rounded r a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> Rounded r a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Rounded r a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> m (MVector (PrimState m) (Rounded r a)) #

Functor (Rounded r) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

fmap :: (a -> b) -> Rounded r a -> Rounded r b #

(<$) :: a -> Rounded r b -> Rounded r a #

Eq a => Eq (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

(==) :: Rounded r a -> Rounded r a -> Bool #

(/=) :: Rounded r a -> Rounded r a -> Bool #

(Rounding r, Num a, RoundedFractional a) => Fractional (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

Methods

(/) :: Rounded r a -> Rounded r a -> Rounded r a #

recip :: Rounded r a -> Rounded r a #

fromRational :: Rational -> Rounded r a #

(Rounding r, Num a, RoundedRing a) => Num (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

Methods

(+) :: Rounded r a -> Rounded r a -> Rounded r a #

(-) :: Rounded r a -> Rounded r a -> Rounded r a #

(*) :: Rounded r a -> Rounded r a -> Rounded r a #

negate :: Rounded r a -> Rounded r a #

abs :: Rounded r a -> Rounded r a #

signum :: Rounded r a -> Rounded r a #

fromInteger :: Integer -> Rounded r a #

Ord a => Ord (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

compare :: Rounded r a -> Rounded r a -> Ordering #

(<) :: Rounded r a -> Rounded r a -> Bool #

(<=) :: Rounded r a -> Rounded r a -> Bool #

(>) :: Rounded r a -> Rounded r a -> Bool #

(>=) :: Rounded r a -> Rounded r a -> Bool #

max :: Rounded r a -> Rounded r a -> Rounded r a #

min :: Rounded r a -> Rounded r a -> Rounded r a #

(Rounding r, Real a, RoundedFractional a) => Real (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

Methods

toRational :: Rounded r a -> Rational #

(Rounding r, RealFrac a, RoundedFractional a) => RealFrac (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Class

Methods

properFraction :: Integral b => Rounded r a -> (b, Rounded r a) #

truncate :: Integral b => Rounded r a -> b #

round :: Integral b => Rounded r a -> b #

ceiling :: Integral b => Rounded r a -> b #

floor :: Integral b => Rounded r a -> b #

Show a => Show (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

showsPrec :: Int -> Rounded r a -> ShowS #

show :: Rounded r a -> String #

showList :: [Rounded r a] -> ShowS #

Generic (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Associated Types

type Rep (Rounded r a) :: Type -> Type #

Methods

from :: Rounded r a -> Rep (Rounded r a) x #

to :: Rep (Rounded r a) x -> Rounded r a #

Storable a => Storable (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

sizeOf :: Rounded r a -> Int #

alignment :: Rounded r a -> Int #

peekElemOff :: Ptr (Rounded r a) -> Int -> IO (Rounded r a) #

pokeElemOff :: Ptr (Rounded r a) -> Int -> Rounded r a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rounded r a) #

pokeByteOff :: Ptr b -> Int -> Rounded r a -> IO () #

peek :: Ptr (Rounded r a) -> IO (Rounded r a) #

poke :: Ptr (Rounded r a) -> Rounded r a -> IO () #

NFData a => NFData (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

rnf :: Rounded r a -> () #

Unbox a => Unbox (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

newtype MVector s (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

newtype MVector s (Rounded r a) = MV_Rounded (MVector s a)
type Rep (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

type Rep (Rounded r a) = D1 ('MetaData "Rounded" "Numeric.Rounded.Hardware.Internal.Rounding" "rounded-hw-0.2.0-G2mMTdTBXOG87Ub6xfZ4rG" 'True) (C1 ('MetaCons "Rounded" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRounded") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
newtype Vector (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

newtype Vector (Rounded r a) = V_Rounded (Vector a)

data family MVector s a #

Instances

Instances details
MVector MVector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector () 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) ()) #

basicInitialize :: PrimMonad m => MVector (PrimState m) () -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> () -> m (MVector (PrimState m) ()) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) () -> Int -> m () #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) () -> Int -> () -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) () -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) () -> () -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) () -> MVector (PrimState m) () -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) () -> MVector (PrimState m) () -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) () -> Int -> m (MVector (PrimState m) ()) #

MVector MVector All 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Any 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

MVector MVector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

MVector MVector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

Unbox a => MVector MVector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Min a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Min a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Min a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Min a -> m (MVector (PrimState m) (Min a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Min a) -> Int -> m (Min a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Min a) -> Int -> Min a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Min a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Min a) -> Min a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Min a) -> MVector (PrimState m) (Min a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Min a) -> MVector (PrimState m) (Min a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Min a) -> Int -> m (MVector (PrimState m) (Min a)) #

Unbox a => MVector MVector (Max a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Max a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Max a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Max a -> m (MVector (PrimState m) (Max a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Max a) -> Int -> m (Max a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Max a) -> Int -> Max a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Max a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Max a) -> Max a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Max a) -> MVector (PrimState m) (Max a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Max a) -> MVector (PrimState m) (Max a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Max a) -> Int -> m (MVector (PrimState m) (Max a)) #

Unbox a => MVector MVector (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Last a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Last a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Last a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Last a -> m (MVector (PrimState m) (Last a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Last a) -> Int -> m (Last a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Last a) -> Int -> Last a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Last a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Last a) -> Last a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Last a) -> MVector (PrimState m) (Last a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Last a) -> MVector (PrimState m) (Last a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Last a) -> Int -> m (MVector (PrimState m) (Last a)) #

Unbox a => MVector MVector (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Dual a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Dual a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Dual a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Dual a -> m (MVector (PrimState m) (Dual a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Dual a) -> Int -> m (Dual a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Dual a) -> Int -> Dual a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Dual a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Dual a) -> Dual a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Dual a) -> MVector (PrimState m) (Dual a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Dual a) -> MVector (PrimState m) (Dual a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Dual a) -> Int -> m (MVector (PrimState m) (Dual a)) #

Unbox a => MVector MVector (Sum a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Sum a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Sum a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Sum a -> m (MVector (PrimState m) (Sum a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Sum a) -> Int -> m (Sum a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Sum a) -> Int -> Sum a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Sum a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Sum a) -> Sum a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Sum a) -> MVector (PrimState m) (Sum a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Sum a) -> MVector (PrimState m) (Sum a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Sum a) -> Int -> m (MVector (PrimState m) (Sum a)) #

Unbox a => MVector MVector (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Down a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Down a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Down a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Down a -> m (MVector (PrimState m) (Down a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Down a) -> Int -> m (Down a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Down a) -> Int -> Down a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Down a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Down a) -> Down a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Down a) -> MVector (PrimState m) (Down a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Down a) -> MVector (PrimState m) (Down a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Down a) -> Int -> m (MVector (PrimState m) (Down a)) #

Unbox a => MVector MVector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(Unbox a, Ord a, Fractional a) => MVector MVector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval.NonEmpty

(Unbox a, Ord a, Fractional a) => MVector MVector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval

(Unbox a, Unbox b) => MVector MVector (a, b) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (a, b)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a, b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b) -> m (MVector (PrimState m) (a, b)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a, b) -> Int -> m (a, b) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a, b) -> Int -> (a, b) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a, b) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a, b) -> (a, b) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a, b) -> MVector (PrimState m) (a, b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a, b) -> MVector (PrimState m) (a, b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a, b) -> Int -> m (MVector (PrimState m) (a, b)) #

(Unbox a, Unbox b) => MVector MVector (Arg a b) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Arg a b)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Arg a b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Arg a b -> m (MVector (PrimState m) (Arg a b)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Arg a b) -> Int -> m (Arg a b) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Arg a b) -> Int -> Arg a b -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Arg a b) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Arg a b) -> Arg a b -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Arg a b) -> MVector (PrimState m) (Arg a b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Arg a b) -> MVector (PrimState m) (Arg a b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Arg a b) -> Int -> m (MVector (PrimState m) (Arg a b)) #

Unbox a => MVector MVector (Rounded r a) Source # 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Rounded r a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Rounded r a -> m (MVector (PrimState m) (Rounded r a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> m (Rounded r a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> Rounded r a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Rounded r a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> MVector (PrimState m) (Rounded r a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Rounded r a) -> Int -> m (MVector (PrimState m) (Rounded r a)) #

(Unbox a, Unbox b, Unbox c) => MVector MVector (a, b, c) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (a, b, c)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a, b, c) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b, c) -> m (MVector (PrimState m) (a, b, c)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a, b, c) -> Int -> m (a, b, c) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a, b, c) -> Int -> (a, b, c) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a, b, c) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a, b, c) -> (a, b, c) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a, b, c) -> MVector (PrimState m) (a, b, c) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a, b, c) -> MVector (PrimState m) (a, b, c) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a, b, c) -> Int -> m (MVector (PrimState m) (a, b, c)) #

Unbox a => MVector MVector (Const a b) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Const a b)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Const a b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Const a b -> m (MVector (PrimState m) (Const a b)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> m (Const a b) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> Const a b -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Const a b) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Const a b) -> Const a b -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Const a b) -> MVector (PrimState m) (Const a b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Const a b) -> MVector (PrimState m) (Const a b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> m (MVector (PrimState m) (Const a b)) #

Unbox (f a) => MVector MVector (Alt f a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Alt f a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Alt f a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Alt f a -> m (MVector (PrimState m) (Alt f a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Int -> m (Alt f a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Int -> Alt f a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Alt f a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Alt f a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Alt f a) -> MVector (PrimState m) (Alt f a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Alt f a) -> MVector (PrimState m) (Alt f a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Alt f a) -> Int -> m (MVector (PrimState m) (Alt f a)) #

(Unbox a, Unbox b, Unbox c, Unbox d) => MVector MVector (a, b, c, d) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (a, b, c, d)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b, c, d) -> m (MVector (PrimState m) (a, b, c, d)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> Int -> m (a, b, c, d) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> Int -> (a, b, c, d) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> (a, b, c, d) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> MVector (PrimState m) (a, b, c, d) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> MVector (PrimState m) (a, b, c, d) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a, b, c, d) -> Int -> m (MVector (PrimState m) (a, b, c, d)) #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => MVector MVector (a, b, c, d, e) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (a, b, c, d, e)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b, c, d, e) -> m (MVector (PrimState m) (a, b, c, d, e)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> Int -> m (a, b, c, d, e) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> Int -> (a, b, c, d, e) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> (a, b, c, d, e) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> MVector (PrimState m) (a, b, c, d, e) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> MVector (PrimState m) (a, b, c, d, e) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e) -> Int -> m (MVector (PrimState m) (a, b, c, d, e)) #

Unbox (f (g a)) => MVector MVector (Compose f g a) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Compose f g a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Compose f g a -> m (MVector (PrimState m) (Compose f g a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> Int -> m (Compose f g a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> Int -> Compose f g a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> Compose f g a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> MVector (PrimState m) (Compose f g a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> MVector (PrimState m) (Compose f g a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Compose f g a) -> Int -> m (MVector (PrimState m) (Compose f g a)) #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => MVector MVector (a, b, c, d, e, f) 
Instance details

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 :: PrimMonad m => Int -> m (MVector (PrimState m) (a, b, c, d, e, f)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b, c, d, e, f) -> m (MVector (PrimState m) (a, b, c, d, e, f)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> Int -> m (a, b, c, d, e, f) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> Int -> (a, b, c, d, e, f) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> MVector (PrimState m) (a, b, c, d, e, f) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> MVector (PrimState m) (a, b, c, d, e, f) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a, b, c, d, e, f) -> Int -> m (MVector (PrimState m) (a, b, c, d, e, f)) #

NFData1 (MVector s)

Since: vector-0.12.1.0

Instance details

Defined in Data.Vector.Unboxed.Base

Methods

liftRnf :: (a -> ()) -> MVector s a -> () #

NFData (MVector s a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnf :: MVector s a -> () #

newtype MVector s All 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s All = MV_All (MVector s Bool)
newtype MVector s Any 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Any = MV_Any (MVector s Bool)
newtype MVector s Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Bool = MV_Bool (MVector s Word8)
newtype MVector s Char 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Char = MV_Char (MVector s Char)
newtype MVector s Double 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Float 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word = MV_Word (MVector s Word)
newtype MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 = MV_Int8 (MVector s Int8)
newtype MVector s Int 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int = MV_Int (MVector s Int)
newtype MVector s () 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s () = MV_Unit Int
newtype MVector s CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

newtype MVector s CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

newtype MVector s CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

newtype MVector s (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Last a) = MV_Last (MVector s a)
newtype MVector s (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (First a) = MV_First (MVector s a)
newtype MVector s (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Max a) = MV_Max (MVector s a)
newtype MVector s (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Min a) = MV_Min (MVector s a)
newtype MVector s (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Product a) = MV_Product (MVector s a)
newtype MVector s (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Sum a) = MV_Sum (MVector s a)
newtype MVector s (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Dual a) = MV_Dual (MVector s a)
newtype MVector s (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Down a) = MV_Down (MVector s a)
newtype MVector s (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Identity a) = MV_Identity (MVector s a)
newtype MVector s (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Complex a) = MV_Complex (MVector s (a, a))
newtype MVector s (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

newtype MVector s (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval.NonEmpty

newtype MVector s (Interval a) = MV_Interval (MVector s (a, a))
newtype MVector s (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval

newtype MVector s (Interval a) = MV_Interval (MVector s (a, a))
newtype MVector s (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

newtype MVector s (Rounded r a) = MV_Rounded (MVector s a)
data MVector s (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b) = MV_2 !Int !(MVector s a) !(MVector s b)
newtype MVector s (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Arg a b) = MV_Arg (MVector s (a, b))
data MVector s (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c) = MV_3 !Int !(MVector s a) !(MVector s b) !(MVector s c)
newtype MVector s (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Alt f a) = MV_Alt (MVector s (f a))
newtype MVector s (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Const a b) = MV_Const (MVector s a)
data MVector s (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c, d) = MV_4 !Int !(MVector s a) !(MVector s b) !(MVector s c) !(MVector s d)
data MVector s (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c, d, e) = MV_5 !Int !(MVector s a) !(MVector s b) !(MVector s c) !(MVector s d) !(MVector s e)
newtype MVector s (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Compose f g a) = MV_Compose (MVector s (f (g a)))
data MVector s (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c, d, e, f) = MV_6 !Int !(MVector s a) !(MVector s b) !(MVector s c) !(MVector s d) !(MVector s e) !(MVector s f)

data family Vector a #

Instances

Instances details
NFData1 Vector

Since: vector-0.12.1.0

Instance details

Defined in Data.Vector.Unboxed.Base

Methods

liftRnf :: (a -> ()) -> Vector a -> () #

Vector Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector () 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) () -> m (Vector ()) #

basicUnsafeThaw :: PrimMonad m => Vector () -> m (Mutable Vector (PrimState m) ()) #

basicLength :: Vector () -> Int #

basicUnsafeSlice :: Int -> Int -> Vector () -> Vector () #

basicUnsafeIndexM :: Monad m => Vector () -> Int -> m () #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) () -> Vector () -> m () #

elemseq :: Vector () -> () -> b -> b #

Vector Vector All 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Any 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

RoundedSqrt_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedSqrt_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedSqrt_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedSqrt_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedSqrt_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

RoundedFractional_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedFractional_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedFractional_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedFractional_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedFractional_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

RoundedRing_Vector Vector Double Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedRing_Vector Vector Float Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.Default

RoundedRing_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedRing_Vector Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

RoundedRing_Vector Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

Unbox a => Vector Vector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Min a) -> m (Vector (Min a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Min a) -> m (Mutable Vector (PrimState m) (Min a)) #

basicLength :: Vector (Min a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Min a) -> Vector (Min a) #

basicUnsafeIndexM :: Monad m => Vector (Min a) -> Int -> m (Min a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Min a) -> Vector (Min a) -> m () #

elemseq :: Vector (Min a) -> Min a -> b -> b #

Unbox a => Vector Vector (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Max a) -> m (Vector (Max a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Max a) -> m (Mutable Vector (PrimState m) (Max a)) #

basicLength :: Vector (Max a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Max a) -> Vector (Max a) #

basicUnsafeIndexM :: Monad m => Vector (Max a) -> Int -> m (Max a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Max a) -> Vector (Max a) -> m () #

elemseq :: Vector (Max a) -> Max a -> b -> b #

Unbox a => Vector Vector (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Last a) -> m (Vector (Last a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Last a) -> m (Mutable Vector (PrimState m) (Last a)) #

basicLength :: Vector (Last a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Last a) -> Vector (Last a) #

basicUnsafeIndexM :: Monad m => Vector (Last a) -> Int -> m (Last a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Last a) -> Vector (Last a) -> m () #

elemseq :: Vector (Last a) -> Last a -> b -> b #

Unbox a => Vector Vector (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Dual a) -> m (Vector (Dual a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Dual a) -> m (Mutable Vector (PrimState m) (Dual a)) #

basicLength :: Vector (Dual a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Dual a) -> Vector (Dual a) #

basicUnsafeIndexM :: Monad m => Vector (Dual a) -> Int -> m (Dual a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Dual a) -> Vector (Dual a) -> m () #

elemseq :: Vector (Dual a) -> Dual a -> b -> b #

Unbox a => Vector Vector (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Sum a) -> m (Vector (Sum a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Sum a) -> m (Mutable Vector (PrimState m) (Sum a)) #

basicLength :: Vector (Sum a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Sum a) -> Vector (Sum a) #

basicUnsafeIndexM :: Monad m => Vector (Sum a) -> Int -> m (Sum a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Sum a) -> Vector (Sum a) -> m () #

elemseq :: Vector (Sum a) -> Sum a -> b -> b #

Unbox a => Vector Vector (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Down a) -> m (Vector (Down a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Down a) -> m (Mutable Vector (PrimState m) (Down a)) #

basicLength :: Vector (Down a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Down a) -> Vector (Down a) #

basicUnsafeIndexM :: Monad m => Vector (Down a) -> Int -> m (Down a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Down a) -> Vector (Down a) -> m () #

elemseq :: Vector (Down a) -> Down a -> b -> b #

Unbox a => Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(Unbox a, Ord a, Fractional a) => Vector Vector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval.NonEmpty

(Unbox a, Ord a, Fractional a) => Vector Vector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval

(RealFloat a, RealFloatConstants a, Unbox a) => RoundedSqrt_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(RealFloat a, RealFloatConstants a, Unbox a) => RoundedFractional_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(RealFloat a, RealFloatConstants a, Unbox a) => RoundedRing_Vector Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

(Unbox a, Unbox b) => Vector Vector (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a, b) -> m (Vector (a, b)) #

basicUnsafeThaw :: PrimMonad m => Vector (a, b) -> m (Mutable Vector (PrimState m) (a, b)) #

basicLength :: Vector (a, b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a, b) -> Vector (a, b) #

basicUnsafeIndexM :: Monad m => Vector (a, b) -> Int -> m (a, b) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a, b) -> Vector (a, b) -> m () #

elemseq :: Vector (a, b) -> (a, b) -> b0 -> b0 #

(Unbox a, Unbox b) => Vector Vector (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Arg a b) -> m (Vector (Arg a b)) #

basicUnsafeThaw :: PrimMonad m => Vector (Arg a b) -> m (Mutable Vector (PrimState m) (Arg a b)) #

basicLength :: Vector (Arg a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Arg a b) -> Vector (Arg a b) #

basicUnsafeIndexM :: Monad m => Vector (Arg a b) -> Int -> m (Arg a b) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Arg a b) -> Vector (Arg a b) -> m () #

elemseq :: Vector (Arg a b) -> Arg a b -> b0 -> b0 #

Unbox a => Vector Vector (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Rounded r a) -> m (Vector (Rounded r a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Rounded r a) -> m (Mutable Vector (PrimState m) (Rounded r a)) #

basicLength :: Vector (Rounded r a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Rounded r a) -> Vector (Rounded r a) #

basicUnsafeIndexM :: Monad m => Vector (Rounded r a) -> Int -> m (Rounded r a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Rounded r a) -> Vector (Rounded r a) -> m () #

elemseq :: Vector (Rounded r a) -> Rounded r a -> b -> b #

(Unbox a, Unbox b, Unbox c) => Vector Vector (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c) -> m (Vector (a, b, c)) #

basicUnsafeThaw :: PrimMonad m => Vector (a, b, c) -> m (Mutable Vector (PrimState m) (a, b, c)) #

basicLength :: Vector (a, b, c) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a, b, c) -> Vector (a, b, c) #

basicUnsafeIndexM :: Monad m => Vector (a, b, c) -> Int -> m (a, b, c) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c) -> Vector (a, b, c) -> m () #

elemseq :: Vector (a, b, c) -> (a, b, c) -> b0 -> b0 #

Unbox a => Vector Vector (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Const a b) -> m (Vector (Const a b)) #

basicUnsafeThaw :: PrimMonad m => Vector (Const a b) -> m (Mutable Vector (PrimState m) (Const a b)) #

basicLength :: Vector (Const a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Const a b) -> Vector (Const a b) #

basicUnsafeIndexM :: Monad m => Vector (Const a b) -> Int -> m (Const a b) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Const a b) -> Vector (Const a b) -> m () #

elemseq :: Vector (Const a b) -> Const a b -> b0 -> b0 #

Unbox (f a) => Vector Vector (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Alt f a) -> m (Vector (Alt f a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Alt f a) -> m (Mutable Vector (PrimState m) (Alt f a)) #

basicLength :: Vector (Alt f a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Alt f a) -> Vector (Alt f a) #

basicUnsafeIndexM :: Monad m => Vector (Alt f a) -> Int -> m (Alt f a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Alt f a) -> Vector (Alt f a) -> m () #

elemseq :: Vector (Alt f a) -> Alt f a -> b -> b #

(Unbox a, Unbox b, Unbox c, Unbox d) => Vector Vector (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d) -> m (Vector (a, b, c, d)) #

basicUnsafeThaw :: PrimMonad m => Vector (a, b, c, d) -> m (Mutable Vector (PrimState m) (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 :: Monad m => Vector (a, b, c, d) -> Int -> m (a, b, c, d) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d) -> Vector (a, b, c, d) -> m () #

elemseq :: Vector (a, b, c, d) -> (a, b, c, d) -> b0 -> b0 #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Vector Vector (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d, e) -> m (Vector (a, b, c, d, e)) #

basicUnsafeThaw :: PrimMonad m => Vector (a, b, c, d, e) -> m (Mutable Vector (PrimState m) (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 :: Monad m => Vector (a, b, c, d, e) -> Int -> m (a, b, c, d, e) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d, e) -> Vector (a, b, c, d, e) -> m () #

elemseq :: Vector (a, b, c, d, e) -> (a, b, c, d, e) -> b0 -> b0 #

Unbox (f (g a)) => Vector Vector (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Compose f g a) -> m (Vector (Compose f g a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Compose f g a) -> m (Mutable Vector (PrimState m) (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 :: Monad m => Vector (Compose f g a) -> Int -> m (Compose f g a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Compose f g a) -> Vector (Compose f g a) -> m () #

elemseq :: Vector (Compose f g a) -> Compose f g a -> b -> b #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Vector Vector (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d, e, f) -> m (Vector (a, b, c, d, e, f)) #

basicUnsafeThaw :: PrimMonad m => Vector (a, b, c, d, e, f) -> m (Mutable Vector (PrimState m) (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 :: Monad m => Vector (a, b, c, d, e, f) -> Int -> m (a, b, c, d, e, f) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a, b, c, d, e, f) -> Vector (a, b, c, d, e, f) -> m () #

elemseq :: Vector (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> b0 -> b0 #

(Data a, Unbox a) => Data (Vector a) 
Instance details

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) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnf :: Vector a -> () #

newtype Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int = V_Int (Vector Int)
newtype Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector () 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector () = V_Unit Int
newtype Vector All 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector All = V_All (Vector Bool)
newtype Vector Any 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Any = V_Any (Vector Bool)
newtype Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

newtype Vector CFloat Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.C

newtype Vector CDouble Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.FastFFI

type Mutable Vector 
Instance details

Defined in Data.Vector.Unboxed.Base

type Item (Vector e) 
Instance details

Defined in Data.Vector.Unboxed

type Item (Vector e) = e
newtype Vector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Complex a) = V_Complex (Vector (a, a))
newtype Vector (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Min a) = V_Min (Vector a)
newtype Vector (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Max a) = V_Max (Vector a)
newtype Vector (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (First a) = V_First (Vector a)
newtype Vector (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Last a) = V_Last (Vector a)
newtype Vector (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Identity a) = V_Identity (Vector a)
newtype Vector (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Dual a) = V_Dual (Vector a)
newtype Vector (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Sum a) = V_Sum (Vector a)
newtype Vector (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Product a) = V_Product (Vector a)
newtype Vector (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Down a) = V_Down (Vector a)
newtype Vector (ViaRational a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Backend.ViaRational

newtype Vector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval.NonEmpty

newtype Vector (Interval a) = V_Interval (Vector (a, a))
newtype Vector (Interval a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Interval

newtype Vector (Interval a) = V_Interval (Vector (a, a))
data Vector (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b) = V_2 !Int !(Vector a) !(Vector b)
newtype Vector (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Arg a b) = V_Arg (Vector (a, b))
newtype Vector (Rounded r a) Source # 
Instance details

Defined in Numeric.Rounded.Hardware.Internal.Rounding

newtype Vector (Rounded r a) = V_Rounded (Vector a)
data Vector (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c) = V_3 !Int !(Vector a) !(Vector b) !(Vector c)
newtype Vector (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Const a b) = V_Const (Vector a)
newtype Vector (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Alt f a) = V_Alt (Vector (f a))
data Vector (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c, d) = V_4 !Int !(Vector a) !(Vector b) !(Vector c) !(Vector d)
data Vector (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c, d, e) = V_5 !Int !(Vector a) !(Vector b) !(Vector c) !(Vector d) !(Vector e)
newtype Vector (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Compose f g a) = V_Compose (Vector (f (g a)))
data Vector (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c, d, e, f) = V_6 !Int !(Vector a) !(Vector b) !(Vector c) !(Vector d) !(Vector e) !(Vector f)