PrimitiveArray-0.10.1.0: Efficient multidimensional arrays
Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Index

Synopsis

Documentation

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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, 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, Unbox b) => Vector Vector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 #

Vector Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Vector Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Vector Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Vector Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Vector Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

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

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

basicLength :: Vector (Unit t) -> Int #

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

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

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

elemseq :: Vector (Unit t) -> Unit t -> 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 #

Vector Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

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

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

basicLength :: Vector (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (PInt t p) -> Vector (PInt t p) #

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

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

elemseq :: Vector (PInt t p) -> PInt t p -> 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 #

Vector Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Vector Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

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

basicLength :: Vector (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (BitSet1 i ioc) -> Vector (BitSet1 i ioc) #

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

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

elemseq :: Vector (BitSet1 i ioc) -> BitSet1 i ioc -> b -> b #

(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 -> () #

(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Unbox a => Ixed (Vector a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Vector a) -> Traversal' (Vector a) (IxValue (Vector a)) #

Unbox a => Wrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

Unbox a => AsEmpty (Vector a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Vector a) () #

Unbox a => Reversing (Vector a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a #

(Unbox a, t ~ Vector a') => Rewrapped (Vector a) t 
Instance details

Defined in Control.Lens.Wrapped

(Unbox a, Unbox b) => Each (Vector a) (Vector b) a b
each :: (Unbox a, Unbox b) => Traversal (Vector a) (Vector b) a b
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal (Vector a) (Vector b) a b #

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

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

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

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector Z = V_Z (Vector ())
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)
type Index (Vector a) 
Instance details

Defined in Control.Lens.At

type Index (Vector a) = Int
type IxValue (Vector a) 
Instance details

Defined in Control.Lens.At

type IxValue (Vector a) = a
type Unwrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (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 (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector (a :. b) = V_StrictPair (Vector (a, b))
newtype Vector (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector (a :> b) = V_StrictIxPair (Vector (a, b))
newtype Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype Vector (BitSet t) = V_BitSet (Vector Int)
newtype Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointL t) = V_PointL (Vector Int)
newtype Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointR t) = V_PointR (Vector Int)
newtype Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype Vector (Subword t) = V_Subword (Vector (Int, Int))
newtype Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

newtype Vector (Unit t) = V_Unit (Vector ())
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))
newtype Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype Vector (PInt t p) = V_PInt (Vector Int)
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)
newtype Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype Vector (Boundary i t) = V_Boundary (Vector Int)
newtype Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype Vector (BitSet1 i ioc) = V_BitSet1 (Vector (Int, Int))
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)

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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, 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, Unbox b) => MVector MVector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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)) #

MVector MVector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

MVector MVector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

MVector MVector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

basicLength :: MVector s (Unit t) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Unit t) -> MVector s (Unit t) #

basicOverlaps :: MVector s (Unit t) -> MVector s (Unit t) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Unit t)) #

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

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

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

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

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

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

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

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

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

(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)) #

MVector MVector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

basicLength :: MVector s (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (PInt t p) -> MVector s (PInt t p) #

basicOverlaps :: MVector s (PInt t p) -> MVector s (PInt t p) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PInt t p)) #

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

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

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

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

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

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

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

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

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

(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)) #

MVector MVector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

MVector MVector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

basicLength :: MVector s (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) #

basicOverlaps :: MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (BitSet1 i ioc)) #

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

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

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

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

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

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

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

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

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

(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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s Z = MV_Z (MVector s ())
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 (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s (a :. b) = MV_StrictPair (MVector s (a, b))
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))
newtype MVector s (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s (a :> b) = MV_StrictIxPair (MVector s (a, b))
newtype MVector s (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype MVector s (BitSet t) = MV_BitSet (MVector s Int)
newtype MVector s (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointL t) = MV_PointL (MVector s Int)
newtype MVector s (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointR t) = MV_PointR (MVector s Int)
newtype MVector s (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype MVector s (Subword t) = MV_Subword (MVector s (Int, Int))
newtype MVector s (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

newtype MVector s (Unit t) = MV_Unit (MVector s ())
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)
newtype MVector s (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype MVector s (PInt t p) = MV_PInt (MVector s Int)
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)
newtype MVector s (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype MVector s (Boundary i t) = MV_Boundary (MVector s Int)
newtype MVector s (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype MVector s (BitSet1 i ioc) = MV_BitSet1 (MVector s (Int, Int))
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 LimitType i :: * Source #

Data structure encoding the upper limit for each array.

Instances

Instances details
(Bounded (LimitType zs), Bounded (LimitType z)) => Bounded (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

minBound :: LimitType (zs :. z) #

maxBound :: LimitType (zs :. z) #

Bounded (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

(Eq (LimitType zs), Eq (LimitType z)) => Eq (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

(==) :: LimitType (zs :. z) -> LimitType (zs :. z) -> Bool #

(/=) :: LimitType (zs :. z) -> LimitType (zs :. z) -> Bool #

Eq (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Eq (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(==) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

(/=) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

Eq (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

(/=) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

Eq (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

(/=) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

Eq (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Eq (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

(==) :: LimitType (Unit t) -> LimitType (Unit t) -> Bool #

(/=) :: LimitType (Unit t) -> LimitType (Unit t) -> Bool #

(Data zs, Data (LimitType zs), Typeable zs, Data z, Data (LimitType z), Typeable z) => Data (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitType (zs :. z) -> c (LimitType (zs :. z)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LimitType (zs :. z)) #

toConstr :: LimitType (zs :. z) -> Constr #

dataTypeOf :: LimitType (zs :. z) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LimitType (zs :. z))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LimitType (zs :. z))) #

gmapT :: (forall b. Data b => b -> b) -> LimitType (zs :. z) -> LimitType (zs :. z) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitType (zs :. z) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitType (zs :. z) -> r #

gmapQ :: (forall d. Data d => d -> u) -> LimitType (zs :. z) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitType (zs :. z) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

Data (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitType Z -> c (LimitType Z) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LimitType Z) #

toConstr :: LimitType Z -> Constr #

dataTypeOf :: LimitType Z -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LimitType Z)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LimitType Z)) #

gmapT :: (forall b. Data b => b -> b) -> LimitType Z -> LimitType Z #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitType Z -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitType Z -> r #

gmapQ :: (forall d. Data d => d -> u) -> LimitType Z -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitType Z -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

(Read (LimitType zs), Read (LimitType z)) => Read (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Read (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Read (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Read (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Read (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Read (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Read (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Show (LimitType Int) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

(Show (LimitType zs), Show (LimitType z)) => Show (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

showsPrec :: Int -> LimitType (zs :. z) -> ShowS #

show :: LimitType (zs :. z) -> String #

showList :: [LimitType (zs :. z)] -> ShowS #

Show (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Show (LimitType (BitSet1 bnd ioc)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

showsPrec :: Int -> LimitType (BitSet1 bnd ioc) -> ShowS #

show :: LimitType (BitSet1 bnd ioc) -> String #

showList :: [LimitType (BitSet1 bnd ioc)] -> ShowS #

Show (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

showsPrec :: Int -> LimitType (PInt t p) -> ShowS #

show :: LimitType (PInt t p) -> String #

showList :: [LimitType (PInt t p)] -> ShowS #

Show (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Show (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

showsPrec :: Int -> LimitType (Unit t) -> ShowS #

show :: LimitType (Unit t) -> String #

showList :: [LimitType (Unit t)] -> ShowS #

(Generic (LimitType zs), Generic (LimitType z)) => Generic (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (LimitType (zs :. z)) :: Type -> Type #

Methods

from :: LimitType (zs :. z) -> Rep (LimitType (zs :. z)) x #

to :: Rep (LimitType (zs :. z)) x -> LimitType (zs :. z) #

Generic (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (LimitType Z) :: Type -> Type #

Methods

from :: LimitType Z -> Rep (LimitType Z) x #

to :: Rep (LimitType Z) x -> LimitType Z #

Generic (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

type Rep (LimitType (PInt t p)) :: Type -> Type #

Methods

from :: LimitType (PInt t p) -> Rep (LimitType (PInt t p)) x #

to :: Rep (LimitType (PInt t p)) x -> LimitType (PInt t p) #

Generic (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointL t)) :: Type -> Type #

Methods

from :: LimitType (PointL t) -> Rep (LimitType (PointL t)) x #

to :: Rep (LimitType (PointL t)) x -> LimitType (PointL t) #

Generic (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointR t)) :: Type -> Type #

Methods

from :: LimitType (PointR t) -> Rep (LimitType (PointR t)) x #

to :: Rep (LimitType (PointR t)) x -> LimitType (PointR t) #

Generic (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

type Rep (LimitType (Subword t)) :: Type -> Type #

Methods

from :: LimitType (Subword t) -> Rep (LimitType (Subword t)) x #

to :: Rep (LimitType (Subword t)) x -> LimitType (Subword t) #

Generic (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Associated Types

type Rep (LimitType (Unit t)) :: Type -> Type #

Methods

from :: LimitType (Unit t) -> Rep (LimitType (Unit t)) x #

to :: Rep (LimitType (Unit t)) x -> LimitType (Unit t) #

newtype LimitType Int Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

data LimitType Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType Z = ZZ
type Rep (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (LimitType (zs :. z)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons ":.." ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LimitType zs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LimitType z))))
type Rep (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (LimitType Z) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "ZZ" 'PrefixI 'False) (U1 :: Type -> Type))
type Rep (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

type Rep (LimitType (PInt t p)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.PhantomInt" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointL t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointR t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

type Rep (LimitType (Subword t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Subword" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtSubword" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

type Rep (LimitType (Unit t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Unit" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "LtUnit" 'PrefixI 'False) (U1 :: Type -> Type))
data LimitType (zs :. z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType (zs :. z) = !(LimitType zs) :.. !(LimitType z)
newtype LimitType (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype LimitType (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype LimitType (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype LimitType (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

data LimitType (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

data LimitType (Unit t) = LtUnit
newtype LimitType (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype LimitType (PInt t p) = LtPInt Int
newtype LimitType (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype LimitType (BitSet1 bnd ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype LimitType (BitSet1 bnd ioc) = LtNumBits1 Int

newtype BitSet t Source #

Newtype for a bitset.

Int integrates better with the rest of the framework. But we should consider moving to Word-based indexing, if possible.

Constructors

BitSet 

Fields

Instances

Instances details
Vector Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

MVector MVector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Eq (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

(==) :: BitSet t -> BitSet t -> Bool #

(/=) :: BitSet t -> BitSet t -> Bool #

Num (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

(+) :: BitSet t -> BitSet t -> BitSet t #

(-) :: BitSet t -> BitSet t -> BitSet t #

(*) :: BitSet t -> BitSet t -> BitSet t #

negate :: BitSet t -> BitSet t #

abs :: BitSet t -> BitSet t #

signum :: BitSet t -> BitSet t #

fromInteger :: Integer -> BitSet t #

Ord (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

compare :: BitSet t -> BitSet t -> Ordering #

(<) :: BitSet t -> BitSet t -> Bool #

(<=) :: BitSet t -> BitSet t -> Bool #

(>) :: BitSet t -> BitSet t -> Bool #

(>=) :: BitSet t -> BitSet t -> Bool #

max :: BitSet t -> BitSet t -> BitSet t #

min :: BitSet t -> BitSet t -> BitSet t #

Show (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

showsPrec :: Int -> BitSet t -> ShowS #

show :: BitSet t -> String #

showList :: [BitSet t] -> ShowS #

Generic (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Associated Types

type Rep (BitSet t) :: Type -> Type #

Methods

from :: BitSet t -> Rep (BitSet t) x #

to :: Rep (BitSet t) x -> BitSet t #

Arbitrary (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

arbitrary :: Gen (BitSet t) #

shrink :: BitSet t -> [BitSet t] #

NFData (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

rnf :: BitSet t -> () #

Hashable (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

hashWithSalt :: Int -> BitSet t -> Int #

hash :: BitSet t -> Int #

ToJSON (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

ToJSONKey (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

FromJSON (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

FromJSONKey (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Bits (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

(.&.) :: BitSet t -> BitSet t -> BitSet t #

(.|.) :: BitSet t -> BitSet t -> BitSet t #

xor :: BitSet t -> BitSet t -> BitSet t #

complement :: BitSet t -> BitSet t #

shift :: BitSet t -> Int -> BitSet t #

rotate :: BitSet t -> Int -> BitSet t #

zeroBits :: BitSet t #

bit :: Int -> BitSet t #

setBit :: BitSet t -> Int -> BitSet t #

clearBit :: BitSet t -> Int -> BitSet t #

complementBit :: BitSet t -> Int -> BitSet t #

testBit :: BitSet t -> Int -> Bool #

bitSizeMaybe :: BitSet t -> Maybe Int #

bitSize :: BitSet t -> Int #

isSigned :: BitSet t -> Bool #

shiftL :: BitSet t -> Int -> BitSet t #

unsafeShiftL :: BitSet t -> Int -> BitSet t #

shiftR :: BitSet t -> Int -> BitSet t #

unsafeShiftR :: BitSet t -> Int -> BitSet t #

rotateL :: BitSet t -> Int -> BitSet t #

rotateR :: BitSet t -> Int -> BitSet t #

popCount :: BitSet t -> Int #

FiniteBits (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Binary (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

put :: BitSet t -> Put #

get :: Get (BitSet t) #

putList :: [BitSet t] -> Put #

Ranked (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

lsb :: BitSet t -> Int #

rank :: BitSet t -> Int #

nlz :: BitSet t -> Int #

Serialize (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

put :: Putter (BitSet t) #

get :: Get (BitSet t) #

Unbox (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

IndexStream z => IndexStream (z :. BitSet C) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet C) -> LimitType (z :. BitSet C) -> Stream m (z :. BitSet C) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet C) -> LimitType (z :. BitSet C) -> Stream m (z :. BitSet C) Source #

IndexStream z => IndexStream (z :. BitSet O) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet O) -> LimitType (z :. BitSet O) -> Stream m (z :. BitSet O) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet O) -> LimitType (z :. BitSet O) -> Stream m (z :. BitSet O) Source #

IndexStream z => IndexStream (z :. BitSet I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet I) -> LimitType (z :. BitSet I) -> Stream m (z :. BitSet I) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet I) -> LimitType (z :. BitSet I) -> Stream m (z :. BitSet I) Source #

IndexStream (Z :. BitSet t) => IndexStream (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (BitSet t) -> LimitType (BitSet t) -> Stream m (BitSet t) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (BitSet t) -> LimitType (BitSet t) -> Stream m (BitSet t) Source #

Index (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Associated Types

data LimitType (BitSet t) Source #

SetPredSucc (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

setSucc :: Int -> Int -> BitSet t -> Maybe (BitSet t) Source #

setPred :: Int -> Int -> BitSet t -> Maybe (BitSet t) Source #

newtype MVector s (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype MVector s (BitSet t) = MV_BitSet (MVector s Int)
type Rep (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

type Rep (BitSet t) = D1 ('MetaData "BitSet" "Data.PrimitiveArray.Index.BitSet0" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "BitSet" 'PrefixI 'True) (S1 ('MetaSel ('Just "_bitSet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
newtype Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype Vector (BitSet t) = V_BitSet (Vector Int)
newtype LimitType (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

bitSet :: forall k (t :: k) k (t :: k). Iso (BitSet (t :: k)) (BitSet (t :: k)) Int Int Source #

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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, 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, Unbox b) => Vector Vector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 #

Vector Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Vector Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Vector Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Vector Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Vector Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

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

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

basicLength :: Vector (Unit t) -> Int #

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

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

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

elemseq :: Vector (Unit t) -> Unit t -> 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 #

Vector Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

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

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

basicLength :: Vector (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (PInt t p) -> Vector (PInt t p) #

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

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

elemseq :: Vector (PInt t p) -> PInt t p -> 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 #

Vector Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Vector Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

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

basicLength :: Vector (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (BitSet1 i ioc) -> Vector (BitSet1 i ioc) #

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

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

elemseq :: Vector (BitSet1 i ioc) -> BitSet1 i ioc -> b -> b #

(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 -> () #

(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Unbox a => Ixed (Vector a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Vector a) -> Traversal' (Vector a) (IxValue (Vector a)) #

Unbox a => Wrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

Unbox a => AsEmpty (Vector a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Vector a) () #

Unbox a => Reversing (Vector a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a #

(Unbox a, t ~ Vector a') => Rewrapped (Vector a) t 
Instance details

Defined in Control.Lens.Wrapped

(Unbox a, Unbox b) => Each (Vector a) (Vector b) a b
each :: (Unbox a, Unbox b) => Traversal (Vector a) (Vector b) a b
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal (Vector a) (Vector b) a b #

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

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

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

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector Z = V_Z (Vector ())
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)
type Index (Vector a) 
Instance details

Defined in Control.Lens.At

type Index (Vector a) = Int
type IxValue (Vector a) 
Instance details

Defined in Control.Lens.At

type IxValue (Vector a) = a
type Unwrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (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 (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector (a :. b) = V_StrictPair (Vector (a, b))
newtype Vector (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector (a :> b) = V_StrictIxPair (Vector (a, b))
newtype Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype Vector (BitSet t) = V_BitSet (Vector Int)
newtype Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointL t) = V_PointL (Vector Int)
newtype Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointR t) = V_PointR (Vector Int)
newtype Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype Vector (Subword t) = V_Subword (Vector (Int, Int))
newtype Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

newtype Vector (Unit t) = V_Unit (Vector ())
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))
newtype Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype Vector (PInt t p) = V_PInt (Vector Int)
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)
newtype Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype Vector (Boundary i t) = V_Boundary (Vector Int)
newtype Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype Vector (BitSet1 i ioc) = V_BitSet1 (Vector (Int, Int))
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)

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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, 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, Unbox b) => MVector MVector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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)) #

MVector MVector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

MVector MVector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

MVector MVector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

basicLength :: MVector s (Unit t) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Unit t) -> MVector s (Unit t) #

basicOverlaps :: MVector s (Unit t) -> MVector s (Unit t) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Unit t)) #

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

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

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

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

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

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

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

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

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

(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)) #

MVector MVector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

basicLength :: MVector s (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (PInt t p) -> MVector s (PInt t p) #

basicOverlaps :: MVector s (PInt t p) -> MVector s (PInt t p) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PInt t p)) #

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

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

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

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

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

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

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

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

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

(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)) #

MVector MVector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

MVector MVector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

basicLength :: MVector s (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) #

basicOverlaps :: MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (BitSet1 i ioc)) #

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

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

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

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

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

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

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

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

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

(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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s Z = MV_Z (MVector s ())
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 (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s (a :. b) = MV_StrictPair (MVector s (a, b))
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))
newtype MVector s (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s (a :> b) = MV_StrictIxPair (MVector s (a, b))
newtype MVector s (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype MVector s (BitSet t) = MV_BitSet (MVector s Int)
newtype MVector s (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointL t) = MV_PointL (MVector s Int)
newtype MVector s (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointR t) = MV_PointR (MVector s Int)
newtype MVector s (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype MVector s (Subword t) = MV_Subword (MVector s (Int, Int))
newtype MVector s (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

newtype MVector s (Unit t) = MV_Unit (MVector s ())
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)
newtype MVector s (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype MVector s (PInt t p) = MV_PInt (MVector s Int)
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)
newtype MVector s (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype MVector s (Boundary i t) = MV_Boundary (MVector s Int)
newtype MVector s (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype MVector s (BitSet1 i ioc) = MV_BitSet1 (MVector s (Int, Int))
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 LimitType i :: * Source #

Data structure encoding the upper limit for each array.

Instances

Instances details
(Bounded (LimitType zs), Bounded (LimitType z)) => Bounded (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

minBound :: LimitType (zs :. z) #

maxBound :: LimitType (zs :. z) #

Bounded (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

(Eq (LimitType zs), Eq (LimitType z)) => Eq (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

(==) :: LimitType (zs :. z) -> LimitType (zs :. z) -> Bool #

(/=) :: LimitType (zs :. z) -> LimitType (zs :. z) -> Bool #

Eq (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Eq (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(==) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

(/=) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

Eq (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

(/=) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

Eq (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

(/=) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

Eq (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Eq (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

(==) :: LimitType (Unit t) -> LimitType (Unit t) -> Bool #

(/=) :: LimitType (Unit t) -> LimitType (Unit t) -> Bool #

(Data zs, Data (LimitType zs), Typeable zs, Data z, Data (LimitType z), Typeable z) => Data (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitType (zs :. z) -> c (LimitType (zs :. z)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LimitType (zs :. z)) #

toConstr :: LimitType (zs :. z) -> Constr #

dataTypeOf :: LimitType (zs :. z) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LimitType (zs :. z))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LimitType (zs :. z))) #

gmapT :: (forall b. Data b => b -> b) -> LimitType (zs :. z) -> LimitType (zs :. z) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitType (zs :. z) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitType (zs :. z) -> r #

gmapQ :: (forall d. Data d => d -> u) -> LimitType (zs :. z) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitType (zs :. z) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

Data (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitType Z -> c (LimitType Z) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LimitType Z) #

toConstr :: LimitType Z -> Constr #

dataTypeOf :: LimitType Z -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LimitType Z)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LimitType Z)) #

gmapT :: (forall b. Data b => b -> b) -> LimitType Z -> LimitType Z #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitType Z -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitType Z -> r #

gmapQ :: (forall d. Data d => d -> u) -> LimitType Z -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitType Z -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

(Read (LimitType zs), Read (LimitType z)) => Read (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Read (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Read (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Read (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Read (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Read (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Read (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Show (LimitType Int) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

(Show (LimitType zs), Show (LimitType z)) => Show (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

showsPrec :: Int -> LimitType (zs :. z) -> ShowS #

show :: LimitType (zs :. z) -> String #

showList :: [LimitType (zs :. z)] -> ShowS #

Show (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Show (LimitType (BitSet1 bnd ioc)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

showsPrec :: Int -> LimitType (BitSet1 bnd ioc) -> ShowS #

show :: LimitType (BitSet1 bnd ioc) -> String #

showList :: [LimitType (BitSet1 bnd ioc)] -> ShowS #

Show (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

showsPrec :: Int -> LimitType (PInt t p) -> ShowS #

show :: LimitType (PInt t p) -> String #

showList :: [LimitType (PInt t p)] -> ShowS #

Show (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Show (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

showsPrec :: Int -> LimitType (Unit t) -> ShowS #

show :: LimitType (Unit t) -> String #

showList :: [LimitType (Unit t)] -> ShowS #

(Generic (LimitType zs), Generic (LimitType z)) => Generic (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (LimitType (zs :. z)) :: Type -> Type #

Methods

from :: LimitType (zs :. z) -> Rep (LimitType (zs :. z)) x #

to :: Rep (LimitType (zs :. z)) x -> LimitType (zs :. z) #

Generic (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (LimitType Z) :: Type -> Type #

Methods

from :: LimitType Z -> Rep (LimitType Z) x #

to :: Rep (LimitType Z) x -> LimitType Z #

Generic (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

type Rep (LimitType (PInt t p)) :: Type -> Type #

Methods

from :: LimitType (PInt t p) -> Rep (LimitType (PInt t p)) x #

to :: Rep (LimitType (PInt t p)) x -> LimitType (PInt t p) #

Generic (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointL t)) :: Type -> Type #

Methods

from :: LimitType (PointL t) -> Rep (LimitType (PointL t)) x #

to :: Rep (LimitType (PointL t)) x -> LimitType (PointL t) #

Generic (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointR t)) :: Type -> Type #

Methods

from :: LimitType (PointR t) -> Rep (LimitType (PointR t)) x #

to :: Rep (LimitType (PointR t)) x -> LimitType (PointR t) #

Generic (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

type Rep (LimitType (Subword t)) :: Type -> Type #

Methods

from :: LimitType (Subword t) -> Rep (LimitType (Subword t)) x #

to :: Rep (LimitType (Subword t)) x -> LimitType (Subword t) #

Generic (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Associated Types

type Rep (LimitType (Unit t)) :: Type -> Type #

Methods

from :: LimitType (Unit t) -> Rep (LimitType (Unit t)) x #

to :: Rep (LimitType (Unit t)) x -> LimitType (Unit t) #

newtype LimitType Int Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

data LimitType Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType Z = ZZ
type Rep (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (LimitType (zs :. z)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons ":.." ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LimitType zs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LimitType z))))
type Rep (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (LimitType Z) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "ZZ" 'PrefixI 'False) (U1 :: Type -> Type))
type Rep (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

type Rep (LimitType (PInt t p)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.PhantomInt" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointL t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointR t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

type Rep (LimitType (Subword t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Subword" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtSubword" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

type Rep (LimitType (Unit t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Unit" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "LtUnit" 'PrefixI 'False) (U1 :: Type -> Type))
data LimitType (zs :. z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType (zs :. z) = !(LimitType zs) :.. !(LimitType z)
newtype LimitType (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype LimitType (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype LimitType (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype LimitType (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

data LimitType (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

data LimitType (Unit t) = LtUnit
newtype LimitType (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype LimitType (PInt t p) = LtPInt Int
newtype LimitType (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype LimitType (BitSet1 bnd ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype LimitType (BitSet1 bnd ioc) = LtNumBits1 Int

data BitSet1 i ioc Source #

The bitset with one interface or boundary.

Constructors

BitSet1 

Fields

Instances

Instances details
Vector Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

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

basicLength :: Vector (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (BitSet1 i ioc) -> Vector (BitSet1 i ioc) #

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

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

elemseq :: Vector (BitSet1 i ioc) -> BitSet1 i ioc -> b -> b #

MVector MVector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

basicLength :: MVector s (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) #

basicOverlaps :: MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (BitSet1 i ioc)) #

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

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

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

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

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

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

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

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

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

Show (LimitType (BitSet1 bnd ioc)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

showsPrec :: Int -> LimitType (BitSet1 bnd ioc) -> ShowS #

show :: LimitType (BitSet1 bnd ioc) -> String #

showList :: [LimitType (BitSet1 bnd ioc)] -> ShowS #

SetPredSucc (FixedMask (BitSet1 t ioc)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

setSucc :: Int -> Int -> FixedMask (BitSet1 t ioc) -> Maybe (FixedMask (BitSet1 t ioc)) Source #

setPred :: Int -> Int -> FixedMask (BitSet1 t ioc) -> Maybe (FixedMask (BitSet1 t ioc)) Source #

IndexStream z => IndexStream (z :. BitSet1 i O) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet1 i O) -> LimitType (z :. BitSet1 i O) -> Stream m (z :. BitSet1 i O) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet1 i O) -> LimitType (z :. BitSet1 i O) -> Stream m (z :. BitSet1 i O) Source #

IndexStream z => IndexStream (z :. BitSet1 i I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet1 i I) -> LimitType (z :. BitSet1 i I) -> Stream m (z :. BitSet1 i I) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. BitSet1 i I) -> LimitType (z :. BitSet1 i I) -> Stream m (z :. BitSet1 i I) Source #

Eq (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

(==) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

(/=) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

Ord (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

compare :: BitSet1 i ioc -> BitSet1 i ioc -> Ordering #

(<) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

(<=) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

(>) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

(>=) :: BitSet1 i ioc -> BitSet1 i ioc -> Bool #

max :: BitSet1 i ioc -> BitSet1 i ioc -> BitSet1 i ioc #

min :: BitSet1 i ioc -> BitSet1 i ioc -> BitSet1 i ioc #

Show (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

showsPrec :: Int -> BitSet1 i ioc -> ShowS #

show :: BitSet1 i ioc -> String #

showList :: [BitSet1 i ioc] -> ShowS #

Generic (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Associated Types

type Rep (BitSet1 i ioc) :: Type -> Type #

Methods

from :: BitSet1 i ioc -> Rep (BitSet1 i ioc) x #

to :: Rep (BitSet1 i ioc) x -> BitSet1 i ioc #

Arbitrary (BitSet1 t ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

arbitrary :: Gen (BitSet1 t ioc) #

shrink :: BitSet1 t ioc -> [BitSet1 t ioc] #

Unbox (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

IndexStream (Z :. BitSet1 i t) => IndexStream (BitSet1 i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (BitSet1 i t) -> LimitType (BitSet1 i t) -> Stream m (BitSet1 i t) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (BitSet1 i t) -> LimitType (BitSet1 i t) -> Stream m (BitSet1 i t) Source #

Index (BitSet1 bnd ioc) Source #

NOTE We linearize a bitset as follows: we need 2^number-of-bits * number-of-bits elements. The first is due to having a binary set structure. The second is due to pointing to each of those elements as being the boundary. This overcommits on memory since only those bits can be a boundary bits that are actually set. Furthermore, in case no bit is set at all, then there should be no boundary. This is currently rather awkwardly done by restricting enumeration and mapping the 0-set to boundary 0.

| TODO The size calculations are off by a factor of two, exactly. Each bitset (say) 00110 has a mirror image 11001, whose elements do not have to be indexed. It has to be investigated if a version with exact memory bounds is slower in indexing.

Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Associated Types

data LimitType (BitSet1 bnd ioc) Source #

Methods

linearIndex :: LimitType (BitSet1 bnd ioc) -> BitSet1 bnd ioc -> Int Source #

fromLinearIndex :: LimitType (BitSet1 bnd ioc) -> Int -> BitSet1 bnd ioc Source #

size :: LimitType (BitSet1 bnd ioc) -> Int Source #

inBounds :: LimitType (BitSet1 bnd ioc) -> BitSet1 bnd ioc -> Bool Source #

zeroBound :: BitSet1 bnd ioc Source #

zeroBound' :: LimitType (BitSet1 bnd ioc) Source #

totalSize :: LimitType (BitSet1 bnd ioc) -> [Integer] Source #

showBound :: LimitType (BitSet1 bnd ioc) -> [String] Source #

showIndex :: BitSet1 bnd ioc -> [String] Source #

SetPredSucc (BitSet1 t ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

setSucc :: Int -> Int -> BitSet1 t ioc -> Maybe (BitSet1 t ioc) Source #

setPred :: Int -> Int -> BitSet1 t ioc -> Maybe (BitSet1 t ioc) Source #

newtype MVector s (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype MVector s (BitSet1 i ioc) = MV_BitSet1 (MVector s (Int, Int))
type Rep (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

type Rep (BitSet1 i ioc) = D1 ('MetaData "BitSet1" "Data.PrimitiveArray.Index.BitSet1" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "BitSet1" 'PrefixI 'True) (S1 ('MetaSel ('Just "_bitset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BitSet ioc)) :*: S1 ('MetaSel ('Just "_boundary") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Boundary i ioc))))
newtype Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype Vector (BitSet1 i ioc) = V_BitSet1 (Vector (Int, Int))
newtype LimitType (BitSet1 bnd ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype LimitType (BitSet1 bnd ioc) = LtNumBits1 Int

bitset :: forall k (i :: k) k (ioc :: k). Lens' (BitSet1 (i :: k) (ioc :: k)) (BitSet ioc) Source #

boundary :: forall k (i :: k) k (ioc :: k) k (i :: k). Lens (BitSet1 (i :: k) (ioc :: k)) (BitSet1 (i :: k) (ioc :: k)) (Boundary i ioc) (Boundary i ioc) Source #

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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, 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, Unbox b) => Vector Vector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 #

Vector Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Vector Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Vector Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Vector Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Vector Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

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

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

basicLength :: Vector (Unit t) -> Int #

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

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

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

elemseq :: Vector (Unit t) -> Unit t -> 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 #

Vector Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

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

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

basicLength :: Vector (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (PInt t p) -> Vector (PInt t p) #

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

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

elemseq :: Vector (PInt t p) -> PInt t p -> 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 #

Vector Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Vector Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

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

basicLength :: Vector (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (BitSet1 i ioc) -> Vector (BitSet1 i ioc) #

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

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

elemseq :: Vector (BitSet1 i ioc) -> BitSet1 i ioc -> b -> b #

(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 -> () #

(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Unbox a => Ixed (Vector a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Vector a) -> Traversal' (Vector a) (IxValue (Vector a)) #

Unbox a => Wrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

Unbox a => AsEmpty (Vector a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Vector a) () #

Unbox a => Reversing (Vector a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a #

(Unbox a, t ~ Vector a') => Rewrapped (Vector a) t 
Instance details

Defined in Control.Lens.Wrapped

(Unbox a, Unbox b) => Each (Vector a) (Vector b) a b
each :: (Unbox a, Unbox b) => Traversal (Vector a) (Vector b) a b
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal (Vector a) (Vector b) a b #

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

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

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

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector Z = V_Z (Vector ())
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)
type Index (Vector a) 
Instance details

Defined in Control.Lens.At

type Index (Vector a) = Int
type IxValue (Vector a) 
Instance details

Defined in Control.Lens.At

type IxValue (Vector a) = a
type Unwrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (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 (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector (a :. b) = V_StrictPair (Vector (a, b))
newtype Vector (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector (a :> b) = V_StrictIxPair (Vector (a, b))
newtype Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype Vector (BitSet t) = V_BitSet (Vector Int)
newtype Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointL t) = V_PointL (Vector Int)
newtype Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointR t) = V_PointR (Vector Int)
newtype Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype Vector (Subword t) = V_Subword (Vector (Int, Int))
newtype Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

newtype Vector (Unit t) = V_Unit (Vector ())
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))
newtype Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype Vector (PInt t p) = V_PInt (Vector Int)
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)
newtype Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype Vector (Boundary i t) = V_Boundary (Vector Int)
newtype Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype Vector (BitSet1 i ioc) = V_BitSet1 (Vector (Int, Int))
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)

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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, 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, Unbox b) => MVector MVector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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)) #

MVector MVector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

MVector MVector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

MVector MVector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

basicLength :: MVector s (Unit t) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Unit t) -> MVector s (Unit t) #

basicOverlaps :: MVector s (Unit t) -> MVector s (Unit t) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Unit t)) #

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

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

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

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

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

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

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

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

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

(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)) #

MVector MVector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

basicLength :: MVector s (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (PInt t p) -> MVector s (PInt t p) #

basicOverlaps :: MVector s (PInt t p) -> MVector s (PInt t p) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PInt t p)) #

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

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

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

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

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

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

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

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

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

(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)) #

MVector MVector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

MVector MVector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

basicLength :: MVector s (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) #

basicOverlaps :: MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (BitSet1 i ioc)) #

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

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

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

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

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

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

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

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

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

(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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s Z = MV_Z (MVector s ())
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 (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s (a :. b) = MV_StrictPair (MVector s (a, b))
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))
newtype MVector s (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s (a :> b) = MV_StrictIxPair (MVector s (a, b))
newtype MVector s (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype MVector s (BitSet t) = MV_BitSet (MVector s Int)
newtype MVector s (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointL t) = MV_PointL (MVector s Int)
newtype MVector s (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointR t) = MV_PointR (MVector s Int)
newtype MVector s (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype MVector s (Subword t) = MV_Subword (MVector s (Int, Int))
newtype MVector s (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

newtype MVector s (Unit t) = MV_Unit (MVector s ())
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)
newtype MVector s (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype MVector s (PInt t p) = MV_PInt (MVector s Int)
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)
newtype MVector s (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype MVector s (Boundary i t) = MV_Boundary (MVector s Int)
newtype MVector s (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype MVector s (BitSet1 i ioc) = MV_BitSet1 (MVector s (Int, Int))
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 LimitType i :: * Source #

Data structure encoding the upper limit for each array.

Instances

Instances details
(Bounded (LimitType zs), Bounded (LimitType z)) => Bounded (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

minBound :: LimitType (zs :. z) #

maxBound :: LimitType (zs :. z) #

Bounded (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

(Eq (LimitType zs), Eq (LimitType z)) => Eq (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

(==) :: LimitType (zs :. z) -> LimitType (zs :. z) -> Bool #

(/=) :: LimitType (zs :. z) -> LimitType (zs :. z) -> Bool #

Eq (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Eq (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(==) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

(/=) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

Eq (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

(/=) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

Eq (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

(/=) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

Eq (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Eq (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

(==) :: LimitType (Unit t) -> LimitType (Unit t) -> Bool #

(/=) :: LimitType (Unit t) -> LimitType (Unit t) -> Bool #

(Data zs, Data (LimitType zs), Typeable zs, Data z, Data (LimitType z), Typeable z) => Data (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitType (zs :. z) -> c (LimitType (zs :. z)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LimitType (zs :. z)) #

toConstr :: LimitType (zs :. z) -> Constr #

dataTypeOf :: LimitType (zs :. z) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LimitType (zs :. z))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LimitType (zs :. z))) #

gmapT :: (forall b. Data b => b -> b) -> LimitType (zs :. z) -> LimitType (zs :. z) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitType (zs :. z) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitType (zs :. z) -> r #

gmapQ :: (forall d. Data d => d -> u) -> LimitType (zs :. z) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitType (zs :. z) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

Data (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitType Z -> c (LimitType Z) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LimitType Z) #

toConstr :: LimitType Z -> Constr #

dataTypeOf :: LimitType Z -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LimitType Z)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LimitType Z)) #

gmapT :: (forall b. Data b => b -> b) -> LimitType Z -> LimitType Z #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitType Z -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitType Z -> r #

gmapQ :: (forall d. Data d => d -> u) -> LimitType Z -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitType Z -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

(Read (LimitType zs), Read (LimitType z)) => Read (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Read (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Read (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Read (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Read (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Read (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Read (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Show (LimitType Int) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

(Show (LimitType zs), Show (LimitType z)) => Show (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

showsPrec :: Int -> LimitType (zs :. z) -> ShowS #

show :: LimitType (zs :. z) -> String #

showList :: [LimitType (zs :. z)] -> ShowS #

Show (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Show (LimitType (BitSet1 bnd ioc)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

showsPrec :: Int -> LimitType (BitSet1 bnd ioc) -> ShowS #

show :: LimitType (BitSet1 bnd ioc) -> String #

showList :: [LimitType (BitSet1 bnd ioc)] -> ShowS #

Show (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

showsPrec :: Int -> LimitType (PInt t p) -> ShowS #

show :: LimitType (PInt t p) -> String #

showList :: [LimitType (PInt t p)] -> ShowS #

Show (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Show (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

showsPrec :: Int -> LimitType (Unit t) -> ShowS #

show :: LimitType (Unit t) -> String #

showList :: [LimitType (Unit t)] -> ShowS #

(Generic (LimitType zs), Generic (LimitType z)) => Generic (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (LimitType (zs :. z)) :: Type -> Type #

Methods

from :: LimitType (zs :. z) -> Rep (LimitType (zs :. z)) x #

to :: Rep (LimitType (zs :. z)) x -> LimitType (zs :. z) #

Generic (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (LimitType Z) :: Type -> Type #

Methods

from :: LimitType Z -> Rep (LimitType Z) x #

to :: Rep (LimitType Z) x -> LimitType Z #

Generic (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

type Rep (LimitType (PInt t p)) :: Type -> Type #

Methods

from :: LimitType (PInt t p) -> Rep (LimitType (PInt t p)) x #

to :: Rep (LimitType (PInt t p)) x -> LimitType (PInt t p) #

Generic (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointL t)) :: Type -> Type #

Methods

from :: LimitType (PointL t) -> Rep (LimitType (PointL t)) x #

to :: Rep (LimitType (PointL t)) x -> LimitType (PointL t) #

Generic (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointR t)) :: Type -> Type #

Methods

from :: LimitType (PointR t) -> Rep (LimitType (PointR t)) x #

to :: Rep (LimitType (PointR t)) x -> LimitType (PointR t) #

Generic (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

type Rep (LimitType (Subword t)) :: Type -> Type #

Methods

from :: LimitType (Subword t) -> Rep (LimitType (Subword t)) x #

to :: Rep (LimitType (Subword t)) x -> LimitType (Subword t) #

Generic (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Associated Types

type Rep (LimitType (Unit t)) :: Type -> Type #

Methods

from :: LimitType (Unit t) -> Rep (LimitType (Unit t)) x #

to :: Rep (LimitType (Unit t)) x -> LimitType (Unit t) #

newtype LimitType Int Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

data LimitType Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType Z = ZZ
type Rep (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (LimitType (zs :. z)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons ":.." ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LimitType zs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LimitType z))))
type Rep (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (LimitType Z) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "ZZ" 'PrefixI 'False) (U1 :: Type -> Type))
type Rep (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

type Rep (LimitType (PInt t p)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.PhantomInt" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointL t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointR t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

type Rep (LimitType (Subword t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Subword" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtSubword" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

type Rep (LimitType (Unit t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Unit" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "LtUnit" 'PrefixI 'False) (U1 :: Type -> Type))
data LimitType (zs :. z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType (zs :. z) = !(LimitType zs) :.. !(LimitType z)
newtype LimitType (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype LimitType (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype LimitType (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype LimitType (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

data LimitType (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

data LimitType (Unit t) = LtUnit
newtype LimitType (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype LimitType (PInt t p) = LtPInt Int
newtype LimitType (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype LimitType (BitSet1 bnd ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype LimitType (BitSet1 bnd ioc) = LtNumBits1 Int

newtype PInt (ioc :: k) (p :: k) Source #

A PInt behaves exactly like an Int, but has an attached phantom type p. In particular, the Index and IndexStream instances are the same as for raw Ints.

Constructors

PInt 

Fields

Instances

Instances details
Vector Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

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

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

basicLength :: Vector (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (PInt t p) -> Vector (PInt t p) #

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

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

elemseq :: Vector (PInt t p) -> PInt t p -> b -> b #

MVector MVector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

basicLength :: MVector s (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (PInt t p) -> MVector s (PInt t p) #

basicOverlaps :: MVector s (PInt t p) -> MVector s (PInt t p) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PInt t p)) #

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

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

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

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

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

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

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

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

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

Eq (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(==) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

(/=) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

Read (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Show (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

showsPrec :: Int -> LimitType (PInt t p) -> ShowS #

show :: LimitType (PInt t p) -> String #

showList :: [LimitType (PInt t p)] -> ShowS #

Generic (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

type Rep (LimitType (PInt t p)) :: Type -> Type #

Methods

from :: LimitType (PInt t p) -> Rep (LimitType (PInt t p)) x #

to :: Rep (LimitType (PInt t p)) x -> LimitType (PInt t p) #

IndexStream z => IndexStream (z :. PInt C p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. PInt C p) -> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. PInt C p) -> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

IndexStream z => IndexStream (z :. PInt O p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. PInt O p) -> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. PInt O p) -> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

IndexStream z => IndexStream (z :. PInt I p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

Enum (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

succ :: PInt ioc p -> PInt ioc p #

pred :: PInt ioc p -> PInt ioc p #

toEnum :: Int -> PInt ioc p #

fromEnum :: PInt ioc p -> Int #

enumFrom :: PInt ioc p -> [PInt ioc p] #

enumFromThen :: PInt ioc p -> PInt ioc p -> [PInt ioc p] #

enumFromTo :: PInt ioc p -> PInt ioc p -> [PInt ioc p] #

enumFromThenTo :: PInt ioc p -> PInt ioc p -> PInt ioc p -> [PInt ioc p] #

Eq (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(==) :: PInt ioc p -> PInt ioc p -> Bool #

(/=) :: PInt ioc p -> PInt ioc p -> Bool #

Integral (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

quot :: PInt ioc p -> PInt ioc p -> PInt ioc p #

rem :: PInt ioc p -> PInt ioc p -> PInt ioc p #

div :: PInt ioc p -> PInt ioc p -> PInt ioc p #

mod :: PInt ioc p -> PInt ioc p -> PInt ioc p #

quotRem :: PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p) #

divMod :: PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p) #

toInteger :: PInt ioc p -> Integer #

(Typeable ioc, Typeable p, Typeable k) => Data (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PInt ioc p -> c (PInt ioc p) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PInt ioc p) #

toConstr :: PInt ioc p -> Constr #

dataTypeOf :: PInt ioc p -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PInt ioc p)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PInt ioc p)) #

gmapT :: (forall b. Data b => b -> b) -> PInt ioc p -> PInt ioc p #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r #

gmapQ :: (forall d. Data d => d -> u) -> PInt ioc p -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PInt ioc p -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p) #

Num (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(+) :: PInt ioc p -> PInt ioc p -> PInt ioc p #

(-) :: PInt ioc p -> PInt ioc p -> PInt ioc p #

(*) :: PInt ioc p -> PInt ioc p -> PInt ioc p #

negate :: PInt ioc p -> PInt ioc p #

abs :: PInt ioc p -> PInt ioc p #

signum :: PInt ioc p -> PInt ioc p #

fromInteger :: Integer -> PInt ioc p #

Ord (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

compare :: PInt ioc p -> PInt ioc p -> Ordering #

(<) :: PInt ioc p -> PInt ioc p -> Bool #

(<=) :: PInt ioc p -> PInt ioc p -> Bool #

(>) :: PInt ioc p -> PInt ioc p -> Bool #

(>=) :: PInt ioc p -> PInt ioc p -> Bool #

max :: PInt ioc p -> PInt ioc p -> PInt ioc p #

min :: PInt ioc p -> PInt ioc p -> PInt ioc p #

Read (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

readsPrec :: Int -> ReadS (PInt ioc p) #

readList :: ReadS [PInt ioc p] #

readPrec :: ReadPrec (PInt ioc p) #

readListPrec :: ReadPrec [PInt ioc p] #

Real (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

toRational :: PInt ioc p -> Rational #

Show (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

showsPrec :: Int -> PInt ioc p -> ShowS #

show :: PInt ioc p -> String #

showList :: [PInt ioc p] -> ShowS #

Ix (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

range :: (PInt ioc p, PInt ioc p) -> [PInt ioc p] #

index :: (PInt ioc p, PInt ioc p) -> PInt ioc p -> Int #

unsafeIndex :: (PInt ioc p, PInt ioc p) -> PInt ioc p -> Int #

inRange :: (PInt ioc p, PInt ioc p) -> PInt ioc p -> Bool #

rangeSize :: (PInt ioc p, PInt ioc p) -> Int #

unsafeRangeSize :: (PInt ioc p, PInt ioc p) -> Int #

Generic (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

type Rep (PInt ioc p) :: Type -> Type #

Methods

from :: PInt ioc p -> Rep (PInt ioc p) x #

to :: Rep (PInt ioc p) x -> PInt ioc p #

NFData (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

rnf :: PInt t p -> () #

Hashable (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

hashWithSalt :: Int -> PInt t p -> Int #

hash :: PInt t p -> Int #

ToJSON (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

toJSON :: PInt t p -> Value #

toEncoding :: PInt t p -> Encoding #

toJSONList :: [PInt t p] -> Value #

toEncodingList :: [PInt t p] -> Encoding #

ToJSONKey (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

FromJSON (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

parseJSON :: Value -> Parser (PInt t p) #

parseJSONList :: Value -> Parser [PInt t p] #

FromJSONKey (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Binary (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

put :: PInt t p -> Put #

get :: Get (PInt t p) #

putList :: [PInt t p] -> Put #

Serialize (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

put :: Putter (PInt t p) #

get :: Get (PInt t p) #

Unbox (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

IndexStream (Z :. PInt ioc p) => IndexStream (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (PInt ioc p) -> LimitType (PInt ioc p) -> Stream m (PInt ioc p) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (PInt ioc p) -> LimitType (PInt ioc p) -> Stream m (PInt ioc p) Source #

Index (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

data LimitType (PInt t p) Source #

newtype MVector s (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype MVector s (PInt t p) = MV_PInt (MVector s Int)
type Rep (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

type Rep (LimitType (PInt t p)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.PhantomInt" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

type Rep (PInt ioc p) = D1 ('MetaData "PInt" "Data.PrimitiveArray.Index.PhantomInt" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "PInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPInt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
newtype Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype Vector (PInt t p) = V_PInt (Vector Int)
newtype LimitType (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype LimitType (PInt t p) = LtPInt Int

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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, 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, Unbox b) => Vector Vector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 #

Vector Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Vector Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Vector Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Vector Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Vector Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

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

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

basicLength :: Vector (Unit t) -> Int #

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

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

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

elemseq :: Vector (Unit t) -> Unit t -> 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 #

Vector Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

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

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

basicLength :: Vector (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (PInt t p) -> Vector (PInt t p) #

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

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

elemseq :: Vector (PInt t p) -> PInt t p -> 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 #

Vector Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Vector Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

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

basicLength :: Vector (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (BitSet1 i ioc) -> Vector (BitSet1 i ioc) #

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

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

elemseq :: Vector (BitSet1 i ioc) -> BitSet1 i ioc -> b -> b #

(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 -> () #

(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Unbox a => Ixed (Vector a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Vector a) -> Traversal' (Vector a) (IxValue (Vector a)) #

Unbox a => Wrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

Unbox a => AsEmpty (Vector a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Vector a) () #

Unbox a => Reversing (Vector a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a #

(Unbox a, t ~ Vector a') => Rewrapped (Vector a) t 
Instance details

Defined in Control.Lens.Wrapped

(Unbox a, Unbox b) => Each (Vector a) (Vector b) a b
each :: (Unbox a, Unbox b) => Traversal (Vector a) (Vector b) a b
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal (Vector a) (Vector b) a b #

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

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

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

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector Z = V_Z (Vector ())
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)
type Index (Vector a) 
Instance details

Defined in Control.Lens.At

type Index (Vector a) = Int
type IxValue (Vector a) 
Instance details

Defined in Control.Lens.At

type IxValue (Vector a) = a
type Unwrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (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 (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector (a :. b) = V_StrictPair (Vector (a, b))
newtype Vector (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector (a :> b) = V_StrictIxPair (Vector (a, b))
newtype Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype Vector (BitSet t) = V_BitSet (Vector Int)
newtype Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointL t) = V_PointL (Vector Int)
newtype Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointR t) = V_PointR (Vector Int)
newtype Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype Vector (Subword t) = V_Subword (Vector (Int, Int))
newtype Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

newtype Vector (Unit t) = V_Unit (Vector ())
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))
newtype Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype Vector (PInt t p) = V_PInt (Vector Int)
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)
newtype Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype Vector (Boundary i t) = V_Boundary (Vector Int)
newtype Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype Vector (BitSet1 i ioc) = V_BitSet1 (Vector (Int, Int))
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)

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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, 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, Unbox b) => MVector MVector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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)) #

MVector MVector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

MVector MVector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

MVector MVector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

basicLength :: MVector s (Unit t) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Unit t) -> MVector s (Unit t) #

basicOverlaps :: MVector s (Unit t) -> MVector s (Unit t) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Unit t)) #

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

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

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

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

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

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

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

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

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

(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)) #

MVector MVector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

basicLength :: MVector s (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (PInt t p) -> MVector s (PInt t p) #

basicOverlaps :: MVector s (PInt t p) -> MVector s (PInt t p) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PInt t p)) #

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

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

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

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

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

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

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

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

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

(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)) #

MVector MVector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

MVector MVector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

basicLength :: MVector s (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) #

basicOverlaps :: MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (BitSet1 i ioc)) #

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

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

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

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

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

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

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

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

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

(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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s Z = MV_Z (MVector s ())
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 (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s (a :. b) = MV_StrictPair (MVector s (a, b))
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))
newtype MVector s (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s (a :> b) = MV_StrictIxPair (MVector s (a, b))
newtype MVector s (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype MVector s (BitSet t) = MV_BitSet (MVector s Int)
newtype MVector s (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointL t) = MV_PointL (MVector s Int)
newtype MVector s (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointR t) = MV_PointR (MVector s Int)
newtype MVector s (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype MVector s (Subword t) = MV_Subword (MVector s (Int, Int))
newtype MVector s (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

newtype MVector s (Unit t) = MV_Unit (MVector s ())
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)
newtype MVector s (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype MVector s (PInt t p) = MV_PInt (MVector s Int)
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)
newtype MVector s (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype MVector s (Boundary i t) = MV_Boundary (MVector s Int)
newtype MVector s (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype MVector s (BitSet1 i ioc) = MV_BitSet1 (MVector s (Int, Int))
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 LimitType i :: * Source #

Data structure encoding the upper limit for each array.

Instances

Instances details
(Bounded (LimitType zs), Bounded (LimitType z)) => Bounded (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

minBound :: LimitType (zs :. z) #

maxBound :: LimitType (zs :. z) #

Bounded (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

(Eq (LimitType zs), Eq (LimitType z)) => Eq (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

(==) :: LimitType (zs :. z) -> LimitType (zs :. z) -> Bool #

(/=) :: LimitType (zs :. z) -> LimitType (zs :. z) -> Bool #

Eq (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Eq (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(==) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

(/=) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

Eq (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

(/=) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

Eq (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

(/=) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

Eq (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Eq (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

(==) :: LimitType (Unit t) -> LimitType (Unit t) -> Bool #

(/=) :: LimitType (Unit t) -> LimitType (Unit t) -> Bool #

(Data zs, Data (LimitType zs), Typeable zs, Data z, Data (LimitType z), Typeable z) => Data (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitType (zs :. z) -> c (LimitType (zs :. z)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LimitType (zs :. z)) #

toConstr :: LimitType (zs :. z) -> Constr #

dataTypeOf :: LimitType (zs :. z) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LimitType (zs :. z))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LimitType (zs :. z))) #

gmapT :: (forall b. Data b => b -> b) -> LimitType (zs :. z) -> LimitType (zs :. z) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitType (zs :. z) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitType (zs :. z) -> r #

gmapQ :: (forall d. Data d => d -> u) -> LimitType (zs :. z) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitType (zs :. z) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

Data (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitType Z -> c (LimitType Z) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LimitType Z) #

toConstr :: LimitType Z -> Constr #

dataTypeOf :: LimitType Z -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LimitType Z)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LimitType Z)) #

gmapT :: (forall b. Data b => b -> b) -> LimitType Z -> LimitType Z #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitType Z -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitType Z -> r #

gmapQ :: (forall d. Data d => d -> u) -> LimitType Z -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitType Z -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

(Read (LimitType zs), Read (LimitType z)) => Read (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Read (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Read (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Read (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Read (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Read (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Read (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Show (LimitType Int) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

(Show (LimitType zs), Show (LimitType z)) => Show (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

showsPrec :: Int -> LimitType (zs :. z) -> ShowS #

show :: LimitType (zs :. z) -> String #

showList :: [LimitType (zs :. z)] -> ShowS #

Show (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Show (LimitType (BitSet1 bnd ioc)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

showsPrec :: Int -> LimitType (BitSet1 bnd ioc) -> ShowS #

show :: LimitType (BitSet1 bnd ioc) -> String #

showList :: [LimitType (BitSet1 bnd ioc)] -> ShowS #

Show (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

showsPrec :: Int -> LimitType (PInt t p) -> ShowS #

show :: LimitType (PInt t p) -> String #

showList :: [LimitType (PInt t p)] -> ShowS #

Show (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Show (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

showsPrec :: Int -> LimitType (Unit t) -> ShowS #

show :: LimitType (Unit t) -> String #

showList :: [LimitType (Unit t)] -> ShowS #

(Generic (LimitType zs), Generic (LimitType z)) => Generic (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (LimitType (zs :. z)) :: Type -> Type #

Methods

from :: LimitType (zs :. z) -> Rep (LimitType (zs :. z)) x #

to :: Rep (LimitType (zs :. z)) x -> LimitType (zs :. z) #

Generic (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (LimitType Z) :: Type -> Type #

Methods

from :: LimitType Z -> Rep (LimitType Z) x #

to :: Rep (LimitType Z) x -> LimitType Z #

Generic (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

type Rep (LimitType (PInt t p)) :: Type -> Type #

Methods

from :: LimitType (PInt t p) -> Rep (LimitType (PInt t p)) x #

to :: Rep (LimitType (PInt t p)) x -> LimitType (PInt t p) #

Generic (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointL t)) :: Type -> Type #

Methods

from :: LimitType (PointL t) -> Rep (LimitType (PointL t)) x #

to :: Rep (LimitType (PointL t)) x -> LimitType (PointL t) #

Generic (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointR t)) :: Type -> Type #

Methods

from :: LimitType (PointR t) -> Rep (LimitType (PointR t)) x #

to :: Rep (LimitType (PointR t)) x -> LimitType (PointR t) #

Generic (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

type Rep (LimitType (Subword t)) :: Type -> Type #

Methods

from :: LimitType (Subword t) -> Rep (LimitType (Subword t)) x #

to :: Rep (LimitType (Subword t)) x -> LimitType (Subword t) #

Generic (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Associated Types

type Rep (LimitType (Unit t)) :: Type -> Type #

Methods

from :: LimitType (Unit t) -> Rep (LimitType (Unit t)) x #

to :: Rep (LimitType (Unit t)) x -> LimitType (Unit t) #

newtype LimitType Int Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

data LimitType Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType Z = ZZ
type Rep (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (LimitType (zs :. z)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons ":.." ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LimitType zs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LimitType z))))
type Rep (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (LimitType Z) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "ZZ" 'PrefixI 'False) (U1 :: Type -> Type))
type Rep (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

type Rep (LimitType (PInt t p)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.PhantomInt" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointL t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointR t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

type Rep (LimitType (Subword t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Subword" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtSubword" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

type Rep (LimitType (Unit t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Unit" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "LtUnit" 'PrefixI 'False) (U1 :: Type -> Type))
data LimitType (zs :. z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType (zs :. z) = !(LimitType zs) :.. !(LimitType z)
newtype LimitType (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype LimitType (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype LimitType (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype LimitType (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

data LimitType (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

data LimitType (Unit t) = LtUnit
newtype LimitType (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype LimitType (PInt t p) = LtPInt Int
newtype LimitType (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype LimitType (BitSet1 bnd ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype LimitType (BitSet1 bnd ioc) = LtNumBits1 Int

newtype PointL t Source #

A point in a left-linear grammar. The syntactic symbol is in left-most position.

Constructors

PointL 

Fields

Instances

Instances details
Vector Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Monad m => Serial m (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

series :: Series m (PointL t) #

MVector MVector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Eq (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

(/=) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

Read (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Generic (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointL t)) :: Type -> Type #

Methods

from :: LimitType (PointL t) -> Rep (LimitType (PointL t)) x #

to :: Rep (LimitType (PointL t)) x -> LimitType (PointL t) #

Eq (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: PointL t -> PointL t -> Bool #

(/=) :: PointL t -> PointL t -> Bool #

Num (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(+) :: PointL t -> PointL t -> PointL t #

(-) :: PointL t -> PointL t -> PointL t #

(*) :: PointL t -> PointL t -> PointL t #

negate :: PointL t -> PointL t #

abs :: PointL t -> PointL t #

signum :: PointL t -> PointL t #

fromInteger :: Integer -> PointL t #

Ord (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

compare :: PointL t -> PointL t -> Ordering #

(<) :: PointL t -> PointL t -> Bool #

(<=) :: PointL t -> PointL t -> Bool #

(>) :: PointL t -> PointL t -> Bool #

(>=) :: PointL t -> PointL t -> Bool #

max :: PointL t -> PointL t -> PointL t #

min :: PointL t -> PointL t -> PointL t #

Read (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

showsPrec :: Int -> PointL t -> ShowS #

show :: PointL t -> String #

showList :: [PointL t] -> ShowS #

Generic (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (PointL t) :: Type -> Type #

Methods

from :: PointL t -> Rep (PointL t) x #

to :: Rep (PointL t) x -> PointL t #

Arbitrary (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

arbitrary :: Gen (PointL t) #

shrink :: PointL t -> [PointL t] #

NFData (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

rnf :: PointL t -> () #

Hashable (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

hashWithSalt :: Int -> PointL t -> Int #

hash :: PointL t -> Int #

ToJSON (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

ToJSONKey (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

FromJSON (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

FromJSONKey (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Binary (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

put :: PointL t -> Put #

get :: Get (PointL t) #

putList :: [PointL t] -> Put #

Serialize (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

put :: Putter (PointL t) #

get :: Get (PointL t) #

Unbox (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

SparseBucket (PointL O) Source #

TODO Is this instance correct? Outside indices shrink?

Instance details

Defined in Data.PrimitiveArray.Index.Point

SparseBucket (PointL I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

IndexStream z => IndexStream (z :. PointL C) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointL C) -> LimitType (z :. PointL C) -> Stream m (z :. PointL C) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointL C) -> LimitType (z :. PointL C) -> Stream m (z :. PointL C) Source #

IndexStream z => IndexStream (z :. PointL O) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointL O) -> LimitType (z :. PointL O) -> Stream m (z :. PointL O) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointL O) -> LimitType (z :. PointL O) -> Stream m (z :. PointL O) Source #

IndexStream z => IndexStream (z :. PointL I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointL I) -> LimitType (z :. PointL I) -> Stream m (z :. PointL I) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointL I) -> LimitType (z :. PointL I) -> Stream m (z :. PointL I) Source #

IndexStream (Z :. PointL t) => IndexStream (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (PointL t) -> LimitType (PointL t) -> Stream m (PointL t) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (PointL t) -> LimitType (PointL t) -> Stream m (PointL t) Source #

Index (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

data LimitType (PointL t) Source #

newtype MVector s (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointL t) = MV_PointL (MVector s Int)
type Rep (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointL t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (PointL t) = D1 ('MetaData "PointL" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "PointL" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromPointL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
newtype Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointL t) = V_PointL (Vector Int)
newtype LimitType (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype PointR t Source #

A point in a right-linear grammars.

Constructors

PointR 

Fields

Instances

Instances details
Vector Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Eq (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

(/=) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

Read (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Generic (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointR t)) :: Type -> Type #

Methods

from :: LimitType (PointR t) -> Rep (LimitType (PointR t)) x #

to :: Rep (LimitType (PointR t)) x -> LimitType (PointR t) #

Eq (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: PointR t -> PointR t -> Bool #

(/=) :: PointR t -> PointR t -> Bool #

Num (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(+) :: PointR t -> PointR t -> PointR t #

(-) :: PointR t -> PointR t -> PointR t #

(*) :: PointR t -> PointR t -> PointR t #

negate :: PointR t -> PointR t #

abs :: PointR t -> PointR t #

signum :: PointR t -> PointR t #

fromInteger :: Integer -> PointR t #

Ord (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

compare :: PointR t -> PointR t -> Ordering #

(<) :: PointR t -> PointR t -> Bool #

(<=) :: PointR t -> PointR t -> Bool #

(>) :: PointR t -> PointR t -> Bool #

(>=) :: PointR t -> PointR t -> Bool #

max :: PointR t -> PointR t -> PointR t #

min :: PointR t -> PointR t -> PointR t #

Read (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

showsPrec :: Int -> PointR t -> ShowS #

show :: PointR t -> String #

showList :: [PointR t] -> ShowS #

Generic (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (PointR t) :: Type -> Type #

Methods

from :: PointR t -> Rep (PointR t) x #

to :: Rep (PointR t) x -> PointR t #

Arbitrary (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

arbitrary :: Gen (PointR t) #

shrink :: PointR t -> [PointR t] #

NFData (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

rnf :: PointR t -> () #

Hashable (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

hashWithSalt :: Int -> PointR t -> Int #

hash :: PointR t -> Int #

ToJSON (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

ToJSONKey (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

FromJSON (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

FromJSONKey (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Binary (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

put :: PointR t -> Put #

get :: Get (PointR t) #

putList :: [PointR t] -> Put #

Serialize (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

put :: Putter (PointR t) #

get :: Get (PointR t) #

Unbox (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

IndexStream z => IndexStream (z :. PointR O) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointR O) -> LimitType (z :. PointR O) -> Stream m (z :. PointR O) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointR O) -> LimitType (z :. PointR O) -> Stream m (z :. PointR O) Source #

IndexStream z => IndexStream (z :. PointR I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointR I) -> LimitType (z :. PointR I) -> Stream m (z :. PointR I) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointR I) -> LimitType (z :. PointR I) -> Stream m (z :. PointR I) Source #

IndexStream (Z :. PointR t) => IndexStream (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (PointR t) -> LimitType (PointR t) -> Stream m (PointR t) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (PointR t) -> LimitType (PointR t) -> Stream m (PointR t) Source #

Index (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

data LimitType (PointR t) Source #

newtype MVector s (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointR t) = MV_PointR (MVector s Int)
type Rep (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointR t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (PointR t) = D1 ('MetaData "PointR" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "PointR" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromPointR") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
newtype Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointR t) = V_PointR (Vector Int)
newtype LimitType (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

data SP z Source #

Constructors

SP !z !Int# 

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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, 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, Unbox b) => Vector Vector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 #

Vector Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Vector Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Vector Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Vector Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Vector Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

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

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

basicLength :: Vector (Unit t) -> Int #

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

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

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

elemseq :: Vector (Unit t) -> Unit t -> 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 #

Vector Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

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

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

basicLength :: Vector (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (PInt t p) -> Vector (PInt t p) #

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

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

elemseq :: Vector (PInt t p) -> PInt t p -> 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 #

Vector Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Vector Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

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

basicLength :: Vector (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (BitSet1 i ioc) -> Vector (BitSet1 i ioc) #

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

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

elemseq :: Vector (BitSet1 i ioc) -> BitSet1 i ioc -> b -> b #

(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 -> () #

(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Unbox a => Ixed (Vector a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Vector a) -> Traversal' (Vector a) (IxValue (Vector a)) #

Unbox a => Wrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

Unbox a => AsEmpty (Vector a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Vector a) () #

Unbox a => Reversing (Vector a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a #

(Unbox a, t ~ Vector a') => Rewrapped (Vector a) t 
Instance details

Defined in Control.Lens.Wrapped

(Unbox a, Unbox b) => Each (Vector a) (Vector b) a b
each :: (Unbox a, Unbox b) => Traversal (Vector a) (Vector b) a b
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal (Vector a) (Vector b) a b #

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

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

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

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector Z = V_Z (Vector ())
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)
type Index (Vector a) 
Instance details

Defined in Control.Lens.At

type Index (Vector a) = Int
type IxValue (Vector a) 
Instance details

Defined in Control.Lens.At

type IxValue (Vector a) = a
type Unwrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (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 (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector (a :. b) = V_StrictPair (Vector (a, b))
newtype Vector (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype Vector (a :> b) = V_StrictIxPair (Vector (a, b))
newtype Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype Vector (BitSet t) = V_BitSet (Vector Int)
newtype Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointL t) = V_PointL (Vector Int)
newtype Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointR t) = V_PointR (Vector Int)
newtype Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype Vector (Subword t) = V_Subword (Vector (Int, Int))
newtype Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

newtype Vector (Unit t) = V_Unit (Vector ())
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))
newtype Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype Vector (PInt t p) = V_PInt (Vector Int)
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)
newtype Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype Vector (Boundary i t) = V_Boundary (Vector Int)
newtype Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype Vector (BitSet1 i ioc) = V_BitSet1 (Vector (Int, Int))
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)

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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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, 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, Unbox b) => MVector MVector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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)) #

MVector MVector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

MVector MVector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

MVector MVector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

basicLength :: MVector s (Unit t) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Unit t) -> MVector s (Unit t) #

basicOverlaps :: MVector s (Unit t) -> MVector s (Unit t) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Unit t)) #

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

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

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

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

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

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

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

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

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

(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)) #

MVector MVector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

basicLength :: MVector s (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (PInt t p) -> MVector s (PInt t p) #

basicOverlaps :: MVector s (PInt t p) -> MVector s (PInt t p) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PInt t p)) #

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

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

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

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

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

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

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

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

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

(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)) #

MVector MVector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

MVector MVector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

basicLength :: MVector s (BitSet1 i ioc) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) #

basicOverlaps :: MVector s (BitSet1 i ioc) -> MVector s (BitSet1 i ioc) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (BitSet1 i ioc)) #

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

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

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

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

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

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

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

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

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

(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 Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s Z = MV_Z (MVector s ())
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 (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s (a :. b) = MV_StrictPair (MVector s (a, b))
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))
newtype MVector s (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype MVector s (a :> b) = MV_StrictIxPair (MVector s (a, b))
newtype MVector s (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype MVector s (BitSet t) = MV_BitSet (MVector s Int)
newtype MVector s (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointL t) = MV_PointL (MVector s Int)
newtype MVector s (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointR t) = MV_PointR (MVector s Int)
newtype MVector s (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype MVector s (Subword t) = MV_Subword (MVector s (Int, Int))
newtype MVector s (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

newtype MVector s (Unit t) = MV_Unit (MVector s ())
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)
newtype MVector s (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype MVector s (PInt t p) = MV_PInt (MVector s Int)
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)
newtype MVector s (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype MVector s (Boundary i t) = MV_Boundary (MVector s Int)
newtype MVector s (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype MVector s (BitSet1 i ioc) = MV_BitSet1 (MVector s (Int, Int))
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 LimitType i :: * Source #

Data structure encoding the upper limit for each array.

Instances

Instances details
(Bounded (LimitType zs), Bounded (LimitType z)) => Bounded (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

minBound :: LimitType (zs :. z) #

maxBound :: LimitType (zs :. z) #

Bounded (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

(Eq (LimitType zs), Eq (LimitType z)) => Eq (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

(==) :: LimitType (zs :. z) -> LimitType (zs :. z) -> Bool #

(/=) :: LimitType (zs :. z) -> LimitType (zs :. z) -> Bool #

Eq (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Eq (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(==) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

(/=) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

Eq (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

(/=) :: LimitType (PointL t) -> LimitType (PointL t) -> Bool #

Eq (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

(==) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

(/=) :: LimitType (PointR t) -> LimitType (PointR t) -> Bool #

Eq (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Eq (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

(==) :: LimitType (Unit t) -> LimitType (Unit t) -> Bool #

(/=) :: LimitType (Unit t) -> LimitType (Unit t) -> Bool #

(Data zs, Data (LimitType zs), Typeable zs, Data z, Data (LimitType z), Typeable z) => Data (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitType (zs :. z) -> c (LimitType (zs :. z)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LimitType (zs :. z)) #

toConstr :: LimitType (zs :. z) -> Constr #

dataTypeOf :: LimitType (zs :. z) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LimitType (zs :. z))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LimitType (zs :. z))) #

gmapT :: (forall b. Data b => b -> b) -> LimitType (zs :. z) -> LimitType (zs :. z) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitType (zs :. z) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitType (zs :. z) -> r #

gmapQ :: (forall d. Data d => d -> u) -> LimitType (zs :. z) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitType (zs :. z) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType (zs :. z) -> m (LimitType (zs :. z)) #

Data (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitType Z -> c (LimitType Z) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LimitType Z) #

toConstr :: LimitType Z -> Constr #

dataTypeOf :: LimitType Z -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LimitType Z)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LimitType Z)) #

gmapT :: (forall b. Data b => b -> b) -> LimitType Z -> LimitType Z #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitType Z -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitType Z -> r #

gmapQ :: (forall d. Data d => d -> u) -> LimitType Z -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitType Z -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitType Z -> m (LimitType Z) #

(Read (LimitType zs), Read (LimitType z)) => Read (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Read (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Read (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Read (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Read (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Read (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Read (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Show (LimitType Int) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

(Show (LimitType zs), Show (LimitType z)) => Show (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

showsPrec :: Int -> LimitType (zs :. z) -> ShowS #

show :: LimitType (zs :. z) -> String #

showList :: [LimitType (zs :. z)] -> ShowS #

Show (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Show (LimitType (BitSet1 bnd ioc)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

showsPrec :: Int -> LimitType (BitSet1 bnd ioc) -> ShowS #

show :: LimitType (BitSet1 bnd ioc) -> String #

showList :: [LimitType (BitSet1 bnd ioc)] -> ShowS #

Show (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

showsPrec :: Int -> LimitType (PInt t p) -> ShowS #

show :: LimitType (PInt t p) -> String #

showList :: [LimitType (PInt t p)] -> ShowS #

Show (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Show (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

showsPrec :: Int -> LimitType (Unit t) -> ShowS #

show :: LimitType (Unit t) -> String #

showList :: [LimitType (Unit t)] -> ShowS #

(Generic (LimitType zs), Generic (LimitType z)) => Generic (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (LimitType (zs :. z)) :: Type -> Type #

Methods

from :: LimitType (zs :. z) -> Rep (LimitType (zs :. z)) x #

to :: Rep (LimitType (zs :. z)) x -> LimitType (zs :. z) #

Generic (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (LimitType Z) :: Type -> Type #

Methods

from :: LimitType Z -> Rep (LimitType Z) x #

to :: Rep (LimitType Z) x -> LimitType Z #

Generic (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

type Rep (LimitType (PInt t p)) :: Type -> Type #

Methods

from :: LimitType (PInt t p) -> Rep (LimitType (PInt t p)) x #

to :: Rep (LimitType (PInt t p)) x -> LimitType (PInt t p) #

Generic (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointL t)) :: Type -> Type #

Methods

from :: LimitType (PointL t) -> Rep (LimitType (PointL t)) x #

to :: Rep (LimitType (PointL t)) x -> LimitType (PointL t) #

Generic (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointR t)) :: Type -> Type #

Methods

from :: LimitType (PointR t) -> Rep (LimitType (PointR t)) x #

to :: Rep (LimitType (PointR t)) x -> LimitType (PointR t) #

Generic (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

type Rep (LimitType (Subword t)) :: Type -> Type #

Methods

from :: LimitType (Subword t) -> Rep (LimitType (Subword t)) x #

to :: Rep (LimitType (Subword t)) x -> LimitType (Subword t) #

Generic (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Associated Types

type Rep (LimitType (Unit t)) :: Type -> Type #

Methods

from :: LimitType (Unit t) -> Rep (LimitType (Unit t)) x #

to :: Rep (LimitType (Unit t)) x -> LimitType (Unit t) #

newtype LimitType Int Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

data LimitType Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType Z = ZZ
type Rep (LimitType (zs :. z)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (LimitType (zs :. z)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons ":.." ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LimitType zs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LimitType z))))
type Rep (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (LimitType Z) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "ZZ" 'PrefixI 'False) (U1 :: Type -> Type))
type Rep (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

type Rep (LimitType (PInt t p)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.PhantomInt" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointL t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointR t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

type Rep (LimitType (Subword t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Subword" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtSubword" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (LimitType (Unit t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

type Rep (LimitType (Unit t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Unit" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons "LtUnit" 'PrefixI 'False) (U1 :: Type -> Type))
data LimitType (zs :. z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType (zs :. z) = !(LimitType zs) :.. !(LimitType z)
newtype LimitType (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

newtype LimitType (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype LimitType (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype LimitType (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

data LimitType (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

data LimitType (Unit t) = LtUnit
newtype LimitType (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

newtype LimitType (PInt t p) = LtPInt Int
newtype LimitType (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype LimitType (BitSet1 bnd ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

newtype LimitType (BitSet1 bnd ioc) = LtNumBits1 Int

newtype Subword t Source #

A subword wraps a pair of Int indices i,j with i<=j.

Subwords always yield the upper-triangular part of a rect-angular array. This gives the quite curious effect that (0,N) points to the `largest' index, while (0,0) ... (1,1) ... (k,k) ... (N,N) point to the smallest. We do, however, use (0,0) as the smallest as (0,k) gives successively smaller upper triangular parts.

Constructors

Subword 

Fields

Instances

Instances details
Vector Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Monad m => Serial m (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

series :: Series m (Subword t) #

MVector MVector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Eq (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Read (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Show (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Generic (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

type Rep (LimitType (Subword t)) :: Type -> Type #

Methods

from :: LimitType (Subword t) -> Rep (LimitType (Subword t)) x #

to :: Rep (LimitType (Subword t)) x -> LimitType (Subword t) #

Eq (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

(==) :: Subword t -> Subword t -> Bool #

(/=) :: Subword t -> Subword t -> Bool #

Ord (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

compare :: Subword t -> Subword t -> Ordering #

(<) :: Subword t -> Subword t -> Bool #

(<=) :: Subword t -> Subword t -> Bool #

(>) :: Subword t -> Subword t -> Bool #

(>=) :: Subword t -> Subword t -> Bool #

max :: Subword t -> Subword t -> Subword t #

min :: Subword t -> Subword t -> Subword t #

Read (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Show (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

showsPrec :: Int -> Subword t -> ShowS #

show :: Subword t -> String #

showList :: [Subword t] -> ShowS #

Generic (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

type Rep (Subword t) :: Type -> Type #

Methods

from :: Subword t -> Rep (Subword t) x #

to :: Rep (Subword t) x -> Subword t #

Arbitrary (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

arbitrary :: Gen (Subword t) #

shrink :: Subword t -> [Subword t] #

NFData (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

rnf :: Subword t -> () #

Hashable (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

hashWithSalt :: Int -> Subword t -> Int #

hash :: Subword t -> Int #

ToJSON (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

ToJSONKey (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

FromJSON (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

FromJSONKey (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Binary (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

put :: Subword t -> Put #

get :: Get (Subword t) #

putList :: [Subword t] -> Put #

Serialize (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

put :: Putter (Subword t) #

get :: Get (Subword t) #

Unbox (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

IndexStream z => IndexStream (z :. Subword C) Source #

Subword C (complement)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. Subword C) -> LimitType (z :. Subword C) -> Stream m (z :. Subword C) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. Subword C) -> LimitType (z :. Subword C) -> Stream m (z :. Subword C) Source #

IndexStream z => IndexStream (z :. Subword O) Source #

Subword O (outside).

Note: streamUp really needs to use streamDownMk / streamDownStep for the right order of indices!

Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. Subword O) -> LimitType (z :. Subword O) -> Stream m (z :. Subword O) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. Subword O) -> LimitType (z :. Subword O) -> Stream m (z :. Subword O) Source #

IndexStream z => IndexStream (z :. Subword I) Source #

Subword I (inside)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. Subword I) -> LimitType (z :. Subword I) -> Stream m (z :. Subword I) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. Subword I) -> LimitType (z :. Subword I) -> Stream m (z :. Subword I) Source #

IndexStream (Z :. Subword t) => IndexStream (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (Subword t) -> LimitType (Subword t) -> Stream m (Subword t) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (Subword t) -> LimitType (Subword t) -> Stream m (Subword t) Source #

Index (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

data LimitType (Subword t) Source #

newtype MVector s (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype MVector s (Subword t) = MV_Subword (MVector s (Int, Int))
type Rep (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

type Rep (LimitType (Subword t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Subword" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtSubword" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

type Rep (Subword t) = D1 ('MetaData "Subword" "Data.PrimitiveArray.Index.Subword" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "Subword" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromSubword") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int :. Int))))
newtype Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype Vector (Subword t) = V_Subword (Vector (Int, Int))
newtype LimitType (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

subword :: Int -> Int -> Subword t Source #

Create a Subword t where t is inferred.