PrimitiveArray-0.9.0.0: Efficient multidimensional arrays

Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Checked

Description

This module exports everything that Data.PrimitiveArray exports, but it will do some bounds-checking on certain operations.

Checked are: (!)

Synopsis

Documentation

data family Vector a :: Type #

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

Defined in Data.PrimitiveArray.Index.Class

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

Defined in Data.Vector.Unboxed.Base

(RealFloat a, Unbox a) => Vector Vector (Log a) 
Instance details

Defined in Numeric.Log

Methods

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

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

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

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

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

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

elemseq :: Vector (Log a) -> Log 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 (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 (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 #

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

(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

NFData (Vector a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnf :: Vector a -> () #

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

Methods

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

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

Defined in Control.Lens.Wrapped

data Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector () 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector () = V_Unit Int
data Vector Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data 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
data Vector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (Complex a) = V_Complex (Vector (a, a))
data Vector (Log a) 
Instance details

Defined in Numeric.Log

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

Defined in Data.PrimitiveArray.Index.Class

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

Defined in Data.PrimitiveArray.Index.Class

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

Defined in Data.PrimitiveArray.Index.BitSet0

data Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

data Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

data Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

data 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)
data Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

data 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)
data Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

data Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

data 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)
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 :: Type #

Instances
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 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 (Log a) 
Instance details

Defined in Numeric.Log

Methods

basicLength :: MVector s (Log a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Log a) -> MVector s (Log a) #

basicOverlaps :: MVector s (Log a) -> MVector s (Log a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Log a)) #

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

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

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

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

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

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

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

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

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

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

NFData (MVector s a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnf :: MVector s a -> () #

data MVector s Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Char 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Double 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Float 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Word 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Int 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s () 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s () = MV_Unit Int
data MVector s Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data MVector s Z = MV_Z (MVector s ())
data MVector s (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (Complex a) = MV_Complex (MVector s (a, a))
data MVector s (Log a) 
Instance details

Defined in Numeric.Log

data MVector s (Log a) = MV_Log (MVector s a)
data MVector s (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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

Defined in Data.PrimitiveArray.Index.Class

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

Defined in Data.PrimitiveArray.Index.BitSet0

data MVector s (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

data MVector s (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

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

Defined in Data.PrimitiveArray.Index.Unit

data 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)
data MVector s (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

data 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)
data MVector s (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

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

Defined in Data.PrimitiveArray.Index.BitSet1

data 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)
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 a :. b infixl 3 Source #

Strict pairs -- as in repa.

Constructors

!a :. !b infixl 3 
Instances
(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) => 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)) #

(Functor m, Applicative m, Monad m, PrimMonad m, FreezeTables m ts, PrimArrayOps arr sh elm) => FreezeTables m (ts :. MutArr m (arr sh elm)) Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Associated Types

type Frozen (ts :. MutArr m (arr sh elm)) :: Type Source #

Methods

freezeTables :: (ts :. MutArr m (arr sh elm)) -> m (Frozen (ts :. MutArr m (arr sh elm))) Source #

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

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

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

Defined in Data.PrimitiveArray.Index.Class

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

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

(Eq a, Eq b) => Eq (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

(==) :: (a :. b) -> (a :. b) -> Bool #

(/=) :: (a :. b) -> (a :. b) -> Bool #

(Data a, Data b) => Data (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :. b) -> c (a :. b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :. b) #

toConstr :: (a :. b) -> Constr #

dataTypeOf :: (a :. b) -> DataType #

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

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

gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :. b) -> a :. b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :. b) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :. b) -> r #

gmapQ :: (forall d. Data d => d -> u) -> (a :. b) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :. b) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :. b) -> m (a :. b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :. b) -> m (a :. b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :. b) -> m (a :. b) #

(Ord a, Ord b) => Ord (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

compare :: (a :. b) -> (a :. b) -> Ordering #

(<) :: (a :. b) -> (a :. b) -> Bool #

(<=) :: (a :. b) -> (a :. b) -> Bool #

(>) :: (a :. b) -> (a :. b) -> Bool #

(>=) :: (a :. b) -> (a :. b) -> Bool #

max :: (a :. b) -> (a :. b) -> a :. b #

min :: (a :. b) -> (a :. b) -> a :. b #

(Read a, Read b) => Read (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

readsPrec :: Int -> ReadS (a :. b) #

readList :: ReadS [a :. b] #

readPrec :: ReadPrec (a :. b) #

readListPrec :: ReadPrec [a :. b] #

(Show a, Show b) => Show (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

showsPrec :: Int -> (a :. b) -> ShowS #

show :: (a :. b) -> String #

showList :: [a :. b] -> ShowS #

Generic (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (a :. b) :: Type -> Type #

Methods

from :: (a :. b) -> Rep (a :. b) x #

to :: Rep (a :. b) x -> a :. b #

(Arbitrary a, Arbitrary b) => Arbitrary (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

arbitrary :: Gen (a :. b) #

shrink :: (a :. b) -> [a :. b] #

(Hashable a, Hashable b) => Hashable (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

hashWithSalt :: Int -> (a :. b) -> Int #

hash :: (a :. b) -> Int #

(ToJSON a, ToJSON b) => ToJSON (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

toJSON :: (a :. b) -> Value #

toEncoding :: (a :. b) -> Encoding #

toJSONList :: [a :. b] -> Value #

toEncodingList :: [a :. b] -> Encoding #

(ToJSON a, ToJSONKey a, ToJSON b, ToJSONKey b) => ToJSONKey (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

(FromJSON a, FromJSON b) => FromJSON (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

parseJSON :: Value -> Parser (a :. b) #

parseJSONList :: Value -> Parser [a :. b] #

(FromJSON a, FromJSONKey a, FromJSON b, FromJSONKey b) => FromJSONKey (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

(Binary a, Binary b) => Binary (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

put :: (a :. b) -> Put #

get :: Get (a :. b) #

putList :: [a :. b] -> Put #

(Serialize a, Serialize b) => Serialize (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

put :: Putter (a :. b) #

get :: Get (a :. b) #

(NFData a, NFData b) => NFData (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

rnf :: (a :. b) -> () #

(Unbox a, Unbox b) => Unbox (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

streamUp :: Monad m => LimitType (z :. Boundary k2 I) -> LimitType (z :. Boundary k2 I) -> Stream m (z :. Boundary k2 I) Source #

streamDown :: Monad m => LimitType (z :. Boundary k2 I) -> LimitType (z :. Boundary k2 I) -> Stream m (z :. Boundary k2 I) Source #

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

streamDown :: 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 :: Monad m => LimitType (z :. BitSet1 i I) -> LimitType (z :. BitSet1 i I) -> Stream m (z :. BitSet1 i I) Source #

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

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

Defined in Data.PrimitiveArray.Index.Int

Methods

streamUp :: Monad m => LimitType (z :. Int) -> LimitType (z :. Int) -> Stream m (z :. Int) Source #

streamDown :: Monad m => LimitType (z :. Int) -> LimitType (z :. Int) -> Stream m (z :. Int) Source #

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

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: Monad m => LimitType (z :. PInt C p) -> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

streamDown :: 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 :: Monad m => LimitType (z :. PInt O p) -> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

streamDown :: 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 :: Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

streamDown :: Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

IndexStream z => IndexStream (z :. Subword C) Source #

Subword C (complement)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

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

IndexStream z => IndexStream (z :. Subword I) Source #

Subword I (inside)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

IndexStream z => IndexStream (z :. Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

streamUp :: Monad m => LimitType (z :. Unit t) -> LimitType (z :. Unit t) -> Stream m (z :. Unit t) Source #

streamDown :: Monad m => LimitType (z :. Unit t) -> LimitType (z :. Unit t) -> Stream m (z :. Unit t) Source #

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

Defined in Data.PrimitiveArray.Index.Class

Associated Types

data LimitType (zs :. z) :: Type Source #

Methods

linearIndex :: LimitType (zs :. z) -> (zs :. z) -> Int Source #

size :: LimitType (zs :. z) -> Int Source #

inBounds :: LimitType (zs :. z) -> (zs :. z) -> Bool Source #

zeroBound :: zs :. z Source #

zeroBound' :: LimitType (zs :. z) Source #

totalSize :: LimitType (zs :. z) -> [Integer] Source #

data MVector s (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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

Defined in Data.PrimitiveArray.Index.Class

type Rep (a :. b) = D1 (MetaData ":." "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons ":." (InfixI LeftAssociative 3) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b)))
data Vector (a :. b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data Vector (a :. b) = V_StrictPair (Vector (a, b))
data LimitType (zs :. z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType (zs :. z) = !(LimitType zs) :.. !(LimitType z)
type Frozen (ts :. MutArr m (arr sh elm)) Source # 
Instance details

Defined in Data.PrimitiveArray.Class

type Frozen (ts :. MutArr m (arr sh elm)) = Frozen ts :. arr sh elm

data a :> b infixr 3 Source #

A different version of strict pairs. Makes for simpler type inference in multi-tape grammars. We use :> when we have special needs, like non-recursive instances on inductives tuples, as used for set indices.

This one is infixr so that in a :> b we can have the main type in a and the specializing types in b and then dispatch on a :> ts with ts maybe a chain of :>.

Constructors

!a :> !b infixr 3 
Instances
(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) => 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)) #

(Eq a, Eq b) => Eq (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

(==) :: (a :> b) -> (a :> b) -> Bool #

(/=) :: (a :> b) -> (a :> b) -> Bool #

(Data a, Data b) => Data (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :> b) -> c (a :> b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :> b) #

toConstr :: (a :> b) -> Constr #

dataTypeOf :: (a :> b) -> DataType #

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

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

gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :> b) -> a :> b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :> b) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :> b) -> r #

gmapQ :: (forall d. Data d => d -> u) -> (a :> b) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :> b) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :> b) -> m (a :> b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :> b) -> m (a :> b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :> b) -> m (a :> b) #

(Ord a, Ord b) => Ord (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

compare :: (a :> b) -> (a :> b) -> Ordering #

(<) :: (a :> b) -> (a :> b) -> Bool #

(<=) :: (a :> b) -> (a :> b) -> Bool #

(>) :: (a :> b) -> (a :> b) -> Bool #

(>=) :: (a :> b) -> (a :> b) -> Bool #

max :: (a :> b) -> (a :> b) -> a :> b #

min :: (a :> b) -> (a :> b) -> a :> b #

(Read a, Read b) => Read (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

readsPrec :: Int -> ReadS (a :> b) #

readList :: ReadS [a :> b] #

readPrec :: ReadPrec (a :> b) #

readListPrec :: ReadPrec [a :> b] #

(Show a, Show b) => Show (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

showsPrec :: Int -> (a :> b) -> ShowS #

show :: (a :> b) -> String #

showList :: [a :> b] -> ShowS #

Generic (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep (a :> b) :: Type -> Type #

Methods

from :: (a :> b) -> Rep (a :> b) x #

to :: Rep (a :> b) x -> a :> b #

(Hashable a, Hashable b) => Hashable (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

hashWithSalt :: Int -> (a :> b) -> Int #

hash :: (a :> b) -> Int #

(ToJSON a, ToJSON b) => ToJSON (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

toJSON :: (a :> b) -> Value #

toEncoding :: (a :> b) -> Encoding #

toJSONList :: [a :> b] -> Value #

toEncodingList :: [a :> b] -> Encoding #

(FromJSON a, FromJSON b) => FromJSON (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

parseJSON :: Value -> Parser (a :> b) #

parseJSONList :: Value -> Parser [a :> b] #

(Binary a, Binary b) => Binary (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

put :: (a :> b) -> Put #

get :: Get (a :> b) #

putList :: [a :> b] -> Put #

(Serialize a, Serialize b) => Serialize (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

put :: Putter (a :> b) #

get :: Get (a :> b) #

(NFData a, NFData b) => NFData (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

rnf :: (a :> b) -> () #

(Unbox a, Unbox b) => Unbox (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data MVector s (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data MVector s (a :> b) = MV_StrictIxPair (MVector s (a, b))
type Rep (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep (a :> b) = D1 (MetaData ":>" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons ":>" (InfixI RightAssociative 3) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b)))
data Vector (a :> b) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data Vector (a :> b) = V_StrictIxPair (Vector (a, b))

data Z Source #

Base data constructor for multi-dimensional indices.

Constructors

Z 
Instances
Eq Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

(==) :: Z -> Z -> Bool #

(/=) :: Z -> Z -> Bool #

Data 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) -> Z -> c Z #

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

toConstr :: Z -> Constr #

dataTypeOf :: Z -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

compare :: Z -> Z -> Ordering #

(<) :: Z -> Z -> Bool #

(<=) :: Z -> Z -> Bool #

(>) :: Z -> Z -> Bool #

(>=) :: Z -> Z -> Bool #

max :: Z -> Z -> Z #

min :: Z -> Z -> Z #

Read Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Show Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

showsPrec :: Int -> Z -> ShowS #

show :: Z -> String #

showList :: [Z] -> ShowS #

Generic Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

type Rep Z :: Type -> Type #

Methods

from :: Z -> Rep Z x #

to :: Rep Z x -> Z #

Arbitrary Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

arbitrary :: Gen Z #

shrink :: Z -> [Z] #

Hashable Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

hashWithSalt :: Int -> Z -> Int #

hash :: Z -> Int #

ToJSON Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

FromJSON Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Binary Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

put :: Z -> Put #

get :: Get Z #

putList :: [Z] -> Put #

Serialize Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

put :: Putter Z #

get :: Get Z #

NFData Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Methods

rnf :: Z -> () #

Unbox Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

IndexStream Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Index Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

data LimitType Z :: Type Source #

Vector Vector Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

MVector MVector Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Applicative m => FreezeTables m Z Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Associated Types

type Frozen Z :: Type Source #

Methods

freezeTables :: Z -> m (Frozen Z) Source #

Eq (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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

Defined in Data.PrimitiveArray.Index.Class

Show (LimitType Z) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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 #

type Rep Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

type Rep Z = D1 (MetaData "Z" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "Z" PrefixI False) (U1 :: Type -> Type))
data Vector Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data Vector Z = V_Z (Vector ())
data LimitType Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data LimitType Z = ZZ
type Frozen Z Source # 
Instance details

Defined in Data.PrimitiveArray.Class

type Frozen Z = Z
data MVector s Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

data MVector s Z = MV_Z (MVector s ())
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.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "ZZ" PrefixI False) (U1 :: Type -> Type))

class Index i => IndexStream i where Source #

Generate a stream of indices in correct order for dynamic programming. Since the stream generators require concatMap / flatten we have to write more specialized code for (z:.IX) stuff.

Methods

streamUp :: Monad m => LimitType i -> LimitType i -> Stream m i Source #

Generate an index stream using LimitTypes. This prevents having to figure out how the actual limits for complicated index types (like Set) would look like, since for Set, for example, the LimitType Set == Int provides just the number of bits.

This generates an index stream suitable for forward structure filling. The first index is the smallest (or the first indices considered are all equally small in partially ordered sets). Larger indices follow up until the largest one.

streamDown :: Monad m => LimitType i -> LimitType i -> Stream m i Source #

If streamUp generates indices from smallest to largest, then streamDown generates indices from largest to smallest. Outside grammars make implicit use of this. Asking for an axiom in backtracking requests the first element from this stream.

Instances
IndexStream Int Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

IndexStream Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

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

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

streamUp :: Monad m => LimitType (z :. Boundary k2 I) -> LimitType (z :. Boundary k2 I) -> Stream m (z :. Boundary k2 I) Source #

streamDown :: Monad m => LimitType (z :. Boundary k2 I) -> LimitType (z :. Boundary k2 I) -> Stream m (z :. Boundary k2 I) Source #

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

streamDown :: 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 :: Monad m => LimitType (z :. BitSet1 i I) -> LimitType (z :. BitSet1 i I) -> Stream m (z :. BitSet1 i I) Source #

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

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

Defined in Data.PrimitiveArray.Index.Int

Methods

streamUp :: Monad m => LimitType (z :. Int) -> LimitType (z :. Int) -> Stream m (z :. Int) Source #

streamDown :: Monad m => LimitType (z :. Int) -> LimitType (z :. Int) -> Stream m (z :. Int) Source #

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

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: Monad m => LimitType (z :. PInt C p) -> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

streamDown :: 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 :: Monad m => LimitType (z :. PInt O p) -> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

streamDown :: 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 :: Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

streamDown :: Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

IndexStream z => IndexStream (z :. Subword C) Source #

Subword C (complement)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

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

IndexStream z => IndexStream (z :. Subword I) Source #

Subword I (inside)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

IndexStream z => IndexStream (z :. Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

streamUp :: Monad m => LimitType (z :. Unit t) -> LimitType (z :. Unit t) -> Stream m (z :. Unit t) Source #

streamDown :: Monad m => LimitType (z :. Unit t) -> LimitType (z :. Unit t) -> Stream m (z :. Unit t) Source #

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Subword

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

Defined in Data.PrimitiveArray.Index.Unit

Methods

streamUp :: Monad m => LimitType (Unit t) -> LimitType (Unit t) -> Stream m (Unit t) Source #

streamDown :: Monad m => LimitType (Unit t) -> LimitType (Unit t) -> Stream m (Unit t) Source #

IndexStream (Z :. PInt ioc p) => IndexStream (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: Monad m => LimitType (PInt ioc p) -> LimitType (PInt ioc p) -> Stream m (PInt ioc p) Source #

streamDown :: Monad m => LimitType (PInt ioc p) -> LimitType (PInt ioc p) -> Stream m (PInt ioc p) Source #

IndexStream (Z :. Boundary k2 I) => IndexStream (Boundary k2 I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

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

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

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

newtype CellSize Source #

The total number of cells that are allocated.

Constructors

CellSize Word 
Instances
Bounded CellSize Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Enum CellSize Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Eq CellSize Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Integral CellSize Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Num CellSize Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Ord CellSize Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Real CellSize Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Show CellSize Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

newtype SizeError Source #

In case totalSize or variants thereof produce a size that is too big to handle.

Constructors

SizeError String 

class Index i where Source #

Index structures for complex, heterogeneous indexing. Mostly designed for indexing in DP grammars, where the indices work for linear and context-free grammars on one or more tapes, for strings, sets, later on tree structures.

Associated Types

data LimitType i :: * Source #

Data structure encoding the upper limit for each array.

Methods

linearIndex :: LimitType i -> i -> Int Source #

Given a maximal size, and a current index, calculate the linear index.

size :: LimitType i -> Int Source #

Given the LimitType, return the number of cells required for storage.

inBounds :: LimitType i -> i -> Bool Source #

Check if an index is within the bounds.

zeroBound :: i Source #

A lower bound of zero

zeroBound' :: LimitType i Source #

A lower bound of zero but for a LimitType i.

totalSize :: LimitType i -> [Integer] Source #

The list of cell sizes for each dimension. its product yields the total size.

Instances
Index Int Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Int

Associated Types

data LimitType Int :: Type Source #

Index Z Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Class

Associated Types

data LimitType Z :: Type Source #

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

Defined in Data.PrimitiveArray.Index.Class

Associated Types

data LimitType (zs :. z) :: Type Source #

Methods

linearIndex :: LimitType (zs :. z) -> (zs :. z) -> Int Source #

size :: LimitType (zs :. z) -> Int Source #

inBounds :: LimitType (zs :. z) -> (zs :. z) -> Bool Source #

zeroBound :: zs :. z Source #

zeroBound' :: LimitType (zs :. z) Source #

totalSize :: LimitType (zs :. z) -> [Integer] Source #

Index (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Associated Types

data LimitType (BitSet t) :: Type Source #

Index (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

data LimitType (PointL t) :: Type Source #

Index (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

data LimitType (Subword t) :: Type Source #

Index (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Associated Types

data LimitType (Unit t) :: Type Source #

Index (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

data LimitType (PInt t p) :: Type Source #

Index (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Associated Types

data LimitType (Boundary i t) :: Type 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) :: Type Source #

Methods

linearIndex :: LimitType (BitSet1 bnd ioc) -> BitSet1 bnd ioc -> Int 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 #

sizeIsValid :: Monad m => Word -> [[Integer]] -> ExceptT SizeError m CellSize Source #

Given the maximal number of cells (Word, because this is the pointer limit for the machine), and the list of sizes, will check if this is still legal. Consider dividing the Word by the actual memory requirements for each cell, to get better exception handling for too large arrays.

One list should be given for each array.

class FreezeTables m t where Source #

freezeTables freezes a stack of tables.

Associated Types

type Frozen t :: * Source #

Methods

freezeTables :: t -> m (Frozen t) Source #

Instances
Applicative m => FreezeTables m Z Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Associated Types

type Frozen Z :: Type Source #

Methods

freezeTables :: Z -> m (Frozen Z) Source #

(Functor m, Applicative m, Monad m, PrimMonad m, FreezeTables m ts, PrimArrayOps arr sh elm) => FreezeTables m (ts :. MutArr m (arr sh elm)) Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Associated Types

type Frozen (ts :. MutArr m (arr sh elm)) :: Type Source #

Methods

freezeTables :: (ts :. MutArr m (arr sh elm)) -> m (Frozen (ts :. MutArr m (arr sh elm))) Source #

data PAErrors Source #

Constructors

PAEUpperBound 
Instances
Eq PAErrors Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Show PAErrors Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Generic PAErrors Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Associated Types

type Rep PAErrors :: Type -> Type #

Methods

from :: PAErrors -> Rep PAErrors x #

to :: Rep PAErrors x -> PAErrors #

type Rep PAErrors Source # 
Instance details

Defined in Data.PrimitiveArray.Class

type Rep PAErrors = D1 (MetaData "PAErrors" "Data.PrimitiveArray.Class" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "PAEUpperBound" PrefixI False) (U1 :: Type -> Type))

class Index sh => PrimArrayMap arr sh e e' where Source #

Methods

map :: (e -> e') -> arr sh e -> arr sh e' Source #

Map a function over each element, keeping the shape intact.

Instances
Index sh => PrimArrayMap Boxed sh e e' Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

map :: (e -> e') -> Boxed sh e -> Boxed sh e' Source #

(Index sh, Unbox e, Unbox e') => PrimArrayMap Unboxed sh e e' Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

map :: (e -> e') -> Unboxed sh e -> Unboxed sh e' Source #

class Index sh => PrimArrayOps arr sh elm where Source #

The core set of functions on immutable arrays.

Methods

upperBound :: arr sh elm -> LimitType sh Source #

Returns the bounds of an immutable array, again inclusive bounds: [lb..ub] .

unsafeFreeze :: PrimMonad m => MutArr m (arr sh elm) -> m (arr sh elm) Source #

Freezes a mutable array an returns its immutable version. This operation is O(1) and both arrays share the same memory. Do not use the mutable array afterwards.

unsafeThaw :: PrimMonad m => arr sh elm -> m (MutArr m (arr sh elm)) Source #

Thaw an immutable array into a mutable one. Both versions share memory.

unsafeIndex :: arr sh elm -> sh -> elm Source #

Extract a single element from the array. Generally unsafe as not bounds-checking is performed.

transformShape :: Index sh' => (LimitType sh -> LimitType sh') -> arr sh elm -> arr sh' elm Source #

Savely transform the shape space of a table.

Instances
Index sh => PrimArrayOps Boxed sh elm Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

upperBound :: Boxed sh elm -> LimitType sh Source #

unsafeFreeze :: PrimMonad m => MutArr m (Boxed sh elm) -> m (Boxed sh elm) Source #

unsafeThaw :: PrimMonad m => Boxed sh elm -> m (MutArr m (Boxed sh elm)) Source #

unsafeIndex :: Boxed sh elm -> sh -> elm Source #

transformShape :: Index sh' => (LimitType sh -> LimitType sh') -> Boxed sh elm -> Boxed sh' elm Source #

(Index sh, Unbox elm) => PrimArrayOps Unboxed sh elm Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

upperBound :: Unboxed sh elm -> LimitType sh Source #

unsafeFreeze :: PrimMonad m => MutArr m (Unboxed sh elm) -> m (Unboxed sh elm) Source #

unsafeThaw :: PrimMonad m => Unboxed sh elm -> m (MutArr m (Unboxed sh elm)) Source #

unsafeIndex :: Unboxed sh elm -> sh -> elm Source #

transformShape :: Index sh' => (LimitType sh -> LimitType sh') -> Unboxed sh elm -> Unboxed sh' elm Source #

class Index sh => MPrimArrayOps arr sh elm where Source #

The core set of operations for monadic arrays.

Methods

upperBoundM :: MutArr m (arr sh elm) -> LimitType sh Source #

Return the bounds of the array. All bounds are inclusive, as in [lb..ub]

fromListM :: PrimMonad m => LimitType sh -> [elm] -> m (MutArr m (arr sh elm)) Source #

Given lower and upper bounds and a list of all elements, produce a mutable array.

newM :: PrimMonad m => LimitType sh -> m (MutArr m (arr sh elm)) Source #

Creates a new array with the given bounds with each element within the array being in an undefined state.

newWithM :: PrimMonad m => LimitType sh -> elm -> m (MutArr m (arr sh elm)) Source #

Creates a new array with all elements being equal to elm.

readM :: PrimMonad m => MutArr m (arr sh elm) -> sh -> m elm Source #

Reads a single element in the array.

writeM :: PrimMonad m => MutArr m (arr sh elm) -> sh -> elm -> m () Source #

Writes a single element in the array.

Instances
Index sh => MPrimArrayOps Boxed sh elm Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

upperBoundM :: MutArr m (Boxed sh elm) -> LimitType sh Source #

fromListM :: PrimMonad m => LimitType sh -> [elm] -> m (MutArr m (Boxed sh elm)) Source #

newM :: PrimMonad m => LimitType sh -> m (MutArr m (Boxed sh elm)) Source #

newWithM :: PrimMonad m => LimitType sh -> elm -> m (MutArr m (Boxed sh elm)) Source #

readM :: PrimMonad m => MutArr m (Boxed sh elm) -> sh -> m elm Source #

writeM :: PrimMonad m => MutArr m (Boxed sh elm) -> sh -> elm -> m () Source #

(Index sh, Unbox elm) => MPrimArrayOps Unboxed sh elm Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

upperBoundM :: MutArr m (Unboxed sh elm) -> LimitType sh Source #

fromListM :: PrimMonad m => LimitType sh -> [elm] -> m (MutArr m (Unboxed sh elm)) Source #

newM :: PrimMonad m => LimitType sh -> m (MutArr m (Unboxed sh elm)) Source #

newWithM :: PrimMonad m => LimitType sh -> elm -> m (MutArr m (Unboxed sh elm)) Source #

readM :: PrimMonad m => MutArr m (Unboxed sh elm) -> sh -> m elm Source #

writeM :: PrimMonad m => MutArr m (Unboxed sh elm) -> sh -> elm -> m () Source #

data family MutArr (m :: * -> *) (arr :: *) :: * Source #

Mutable version of an array.

Instances
(Functor m, Applicative m, Monad m, PrimMonad m, FreezeTables m ts, PrimArrayOps arr sh elm) => FreezeTables m (ts :. MutArr m (arr sh elm)) Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Associated Types

type Frozen (ts :. MutArr m (arr sh elm)) :: Type Source #

Methods

freezeTables :: (ts :. MutArr m (arr sh elm)) -> m (Frozen (ts :. MutArr m (arr sh elm))) Source #

Generic (MutArr m (Boxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Associated Types

type Rep (MutArr m (Boxed sh e)) :: Type -> Type #

Methods

from :: MutArr m (Boxed sh e) -> Rep (MutArr m (Boxed sh e)) x #

to :: Rep (MutArr m (Boxed sh e)) x -> MutArr m (Boxed sh e) #

Generic (MutArr m (Unboxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Associated Types

type Rep (MutArr m (Unboxed sh e)) :: Type -> Type #

Methods

from :: MutArr m (Unboxed sh e) -> Rep (MutArr m (Unboxed sh e)) x #

to :: Rep (MutArr m (Unboxed sh e)) x -> MutArr m (Unboxed sh e) #

NFData (LimitType sh) => NFData (MutArr m (Boxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

rnf :: MutArr m (Boxed sh e) -> () #

NFData (LimitType sh) => NFData (MutArr m (Unboxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

rnf :: MutArr m (Unboxed sh e) -> () #

data MutArr m (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

data MutArr m (Unboxed sh e) = MUnboxed !(LimitType sh) !(MVector (PrimState m) e)
data MutArr m (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

data MutArr m (Boxed sh e) = MBoxed !(LimitType sh) !(MVector (PrimState m) e)
type Rep (MutArr m (Boxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

type Rep (MutArr m (Boxed sh e)) = D1 (MetaData "MutArr" "Data.PrimitiveArray.Dense" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "MBoxed" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (LimitType sh)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MVector (PrimState m) e))))
type Rep (MutArr m (Unboxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

type Rep (MutArr m (Unboxed sh e)) = D1 (MetaData "MutArr" "Data.PrimitiveArray.Dense" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "MUnboxed" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (LimitType sh)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MVector (PrimState m) e))))
type Frozen (ts :. MutArr m (arr sh elm)) Source # 
Instance details

Defined in Data.PrimitiveArray.Class

type Frozen (ts :. MutArr m (arr sh elm)) = Frozen ts :. arr sh elm

inBoundsM :: (Monad m, MPrimArrayOps arr sh elm) => MutArr m (arr sh elm) -> sh -> Bool Source #

Returns true if the index is valid for the array.

fromAssocsM :: (PrimMonad m, MPrimArrayOps arr sh elm) => LimitType sh -> elm -> [(sh, elm)] -> m (MutArr m (arr sh elm)) Source #

Construct a mutable primitive array from a lower and an upper bound, a default element, and a list of associations.

newWithPA :: (PrimMonad m, MPrimArrayOps arr sh elm, PrimArrayOps arr sh elm) => LimitType sh -> elm -> m (arr sh elm) Source #

Initialize an immutable array but stay within the primitive monad m.

safeNewWithPA :: forall m arr sh elm. (PrimMonad m, MonadError PAErrors m, MPrimArrayOps arr sh elm, PrimArrayOps arr sh elm) => LimitType sh -> elm -> m (arr sh elm) Source #

Safely prepare a primitive array.

TODO Check if having a MonadError instance degrades performance. (We should see this once the test with NeedlemanWunsch is under way).

assocs :: forall arr sh elm. (IndexStream sh, PrimArrayOps arr sh elm) => arr sh elm -> [(sh, elm)] Source #

Return all associations from an array.

fromList :: (PrimArrayOps arr sh elm, MPrimArrayOps arr sh elm) => LimitType sh -> [elm] -> arr sh elm Source #

Creates an immutable array from lower and upper bounds and a complete list of elements.

fromAssocs :: (PrimArrayOps arr sh elm, MPrimArrayOps arr sh elm) => LimitType sh -> elm -> [(sh, elm)] -> arr sh elm Source #

Creates an immutable array from lower and upper bounds, a default element, and a list of associations.

toList :: forall arr sh elm. (IndexStream sh, PrimArrayOps arr sh elm) => arr sh elm -> [elm] Source #

Returns all elements of an immutable array as a list.

data Boxed sh e Source #

Constructors

Boxed !(LimitType sh) !(Vector e) 
Instances
Index sh => PrimArrayOps Boxed sh elm Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

upperBound :: Boxed sh elm -> LimitType sh Source #

unsafeFreeze :: PrimMonad m => MutArr m (Boxed sh elm) -> m (Boxed sh elm) Source #

unsafeThaw :: PrimMonad m => Boxed sh elm -> m (MutArr m (Boxed sh elm)) Source #

unsafeIndex :: Boxed sh elm -> sh -> elm Source #

transformShape :: Index sh' => (LimitType sh -> LimitType sh') -> Boxed sh elm -> Boxed sh' elm Source #

Index sh => MPrimArrayOps Boxed sh elm Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

upperBoundM :: MutArr m (Boxed sh elm) -> LimitType sh Source #

fromListM :: PrimMonad m => LimitType sh -> [elm] -> m (MutArr m (Boxed sh elm)) Source #

newM :: PrimMonad m => LimitType sh -> m (MutArr m (Boxed sh elm)) Source #

newWithM :: PrimMonad m => LimitType sh -> elm -> m (MutArr m (Boxed sh elm)) Source #

readM :: PrimMonad m => MutArr m (Boxed sh elm) -> sh -> m elm Source #

writeM :: PrimMonad m => MutArr m (Boxed sh elm) -> sh -> elm -> m () Source #

Index sh => PrimArrayMap Boxed sh e e' Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

map :: (e -> e') -> Boxed sh e -> Boxed sh e' Source #

(Eq (LimitType sh), Eq e) => Eq (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

(==) :: Boxed sh e -> Boxed sh e -> Bool #

(/=) :: Boxed sh e -> Boxed sh e -> Bool #

(Data sh, Data (LimitType sh), Data e) => Data (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Boxed sh e -> c (Boxed sh e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Boxed sh e) #

toConstr :: Boxed sh e -> Constr #

dataTypeOf :: Boxed sh e -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Boxed sh e)) #

dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (Boxed sh e)) #

gmapT :: (forall b. Data b => b -> b) -> Boxed sh e -> Boxed sh e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boxed sh e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boxed sh e -> r #

gmapQ :: (forall d. Data d => d -> u) -> Boxed sh e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Boxed sh e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Boxed sh e -> m (Boxed sh e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxed sh e -> m (Boxed sh e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxed sh e -> m (Boxed sh e) #

(Read (LimitType sh), Read e) => Read (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

readsPrec :: Int -> ReadS (Boxed sh e) #

readList :: ReadS [Boxed sh e] #

readPrec :: ReadPrec (Boxed sh e) #

readListPrec :: ReadPrec [Boxed sh e] #

(Show (LimitType sh), Show e) => Show (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

showsPrec :: Int -> Boxed sh e -> ShowS #

show :: Boxed sh e -> String #

showList :: [Boxed sh e] -> ShowS #

Generic (MutArr m (Boxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Associated Types

type Rep (MutArr m (Boxed sh e)) :: Type -> Type #

Methods

from :: MutArr m (Boxed sh e) -> Rep (MutArr m (Boxed sh e)) x #

to :: Rep (MutArr m (Boxed sh e)) x -> MutArr m (Boxed sh e) #

(Generic (LimitType sh), Generic e) => Generic (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Associated Types

type Rep (Boxed sh e) :: Type -> Type #

Methods

from :: Boxed sh e -> Rep (Boxed sh e) x #

to :: Rep (Boxed sh e) x -> Boxed sh e #

(Hashable (LimitType sh), Hashable e, Hashable (Vector e), Unbox e, Generic (LimitType sh), Generic e) => Hashable (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

hashWithSalt :: Int -> Boxed sh e -> Int #

hash :: Boxed sh e -> Int #

(ToJSON (LimitType sh), ToJSON e, Unbox e, Generic (LimitType sh), Generic e) => ToJSON (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

toJSON :: Boxed sh e -> Value #

toEncoding :: Boxed sh e -> Encoding #

toJSONList :: [Boxed sh e] -> Value #

toEncodingList :: [Boxed sh e] -> Encoding #

(FromJSON (LimitType sh), FromJSON e, Unbox e, Generic (LimitType sh), Generic e) => FromJSON (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

parseJSON :: Value -> Parser (Boxed sh e) #

parseJSONList :: Value -> Parser [Boxed sh e] #

(Binary (LimitType sh), Binary e, Unbox e, Generic (LimitType sh), Generic e) => Binary (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

put :: Boxed sh e -> Put #

get :: Get (Boxed sh e) #

putList :: [Boxed sh e] -> Put #

(Serialize (LimitType sh), Serialize e, Unbox e, Generic (LimitType sh), Generic e) => Serialize (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

put :: Putter (Boxed sh e) #

get :: Get (Boxed sh e) #

NFData (LimitType sh) => NFData (MutArr m (Boxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

rnf :: MutArr m (Boxed sh e) -> () #

(NFData (LimitType sh), NFData e) => NFData (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

rnf :: Boxed sh e -> () #

data MutArr m (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

data MutArr m (Boxed sh e) = MBoxed !(LimitType sh) !(MVector (PrimState m) e)
type Rep (MutArr m (Boxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

type Rep (MutArr m (Boxed sh e)) = D1 (MetaData "MutArr" "Data.PrimitiveArray.Dense" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "MBoxed" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (LimitType sh)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MVector (PrimState m) e))))
type Rep (Boxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

type Rep (Boxed sh e) = D1 (MetaData "Boxed" "Data.PrimitiveArray.Dense" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "Boxed" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (LimitType sh)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector e))))

data Unboxed sh e Source #

Constructors

Unboxed !(LimitType sh) !(Vector e) 
Instances
(Index sh, Unbox elm) => PrimArrayOps Unboxed sh elm Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

upperBound :: Unboxed sh elm -> LimitType sh Source #

unsafeFreeze :: PrimMonad m => MutArr m (Unboxed sh elm) -> m (Unboxed sh elm) Source #

unsafeThaw :: PrimMonad m => Unboxed sh elm -> m (MutArr m (Unboxed sh elm)) Source #

unsafeIndex :: Unboxed sh elm -> sh -> elm Source #

transformShape :: Index sh' => (LimitType sh -> LimitType sh') -> Unboxed sh elm -> Unboxed sh' elm Source #

(Index sh, Unbox elm) => MPrimArrayOps Unboxed sh elm Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

upperBoundM :: MutArr m (Unboxed sh elm) -> LimitType sh Source #

fromListM :: PrimMonad m => LimitType sh -> [elm] -> m (MutArr m (Unboxed sh elm)) Source #

newM :: PrimMonad m => LimitType sh -> m (MutArr m (Unboxed sh elm)) Source #

newWithM :: PrimMonad m => LimitType sh -> elm -> m (MutArr m (Unboxed sh elm)) Source #

readM :: PrimMonad m => MutArr m (Unboxed sh elm) -> sh -> m elm Source #

writeM :: PrimMonad m => MutArr m (Unboxed sh elm) -> sh -> elm -> m () Source #

(Index sh, Unbox e, Unbox e') => PrimArrayMap Unboxed sh e e' Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

map :: (e -> e') -> Unboxed sh e -> Unboxed sh e' Source #

(Eq (LimitType sh), Eq e, Unbox e) => Eq (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

(==) :: Unboxed sh e -> Unboxed sh e -> Bool #

(/=) :: Unboxed sh e -> Unboxed sh e -> Bool #

(Data sh, Data (LimitType sh), Data e, Unbox e) => Data (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Unboxed sh e -> c (Unboxed sh e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Unboxed sh e) #

toConstr :: Unboxed sh e -> Constr #

dataTypeOf :: Unboxed sh e -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Unboxed sh e)) #

dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (Unboxed sh e)) #

gmapT :: (forall b. Data b => b -> b) -> Unboxed sh e -> Unboxed sh e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Unboxed sh e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Unboxed sh e -> r #

gmapQ :: (forall d. Data d => d -> u) -> Unboxed sh e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Unboxed sh e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Unboxed sh e -> m (Unboxed sh e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Unboxed sh e -> m (Unboxed sh e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Unboxed sh e -> m (Unboxed sh e) #

(Read (LimitType sh), Read e, Unbox e) => Read (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

(Show (LimitType sh), Show e, Unbox e) => Show (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

showsPrec :: Int -> Unboxed sh e -> ShowS #

show :: Unboxed sh e -> String #

showList :: [Unboxed sh e] -> ShowS #

Generic (MutArr m (Unboxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Associated Types

type Rep (MutArr m (Unboxed sh e)) :: Type -> Type #

Methods

from :: MutArr m (Unboxed sh e) -> Rep (MutArr m (Unboxed sh e)) x #

to :: Rep (MutArr m (Unboxed sh e)) x -> MutArr m (Unboxed sh e) #

(Generic (LimitType sh), Generic e, Unbox e) => Generic (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Associated Types

type Rep (Unboxed sh e) :: Type -> Type #

Methods

from :: Unboxed sh e -> Rep (Unboxed sh e) x #

to :: Rep (Unboxed sh e) x -> Unboxed sh e #

(Hashable (LimitType sh), Hashable e, Hashable (Vector e), Unbox e, Generic (LimitType sh), Generic e) => Hashable (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

hashWithSalt :: Int -> Unboxed sh e -> Int #

hash :: Unboxed sh e -> Int #

(ToJSON (LimitType sh), ToJSON e, Unbox e, Generic (LimitType sh), Generic e) => ToJSON (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

toJSON :: Unboxed sh e -> Value #

toEncoding :: Unboxed sh e -> Encoding #

toJSONList :: [Unboxed sh e] -> Value #

toEncodingList :: [Unboxed sh e] -> Encoding #

(FromJSON (LimitType sh), FromJSON e, Unbox e, Generic (LimitType sh), Generic e) => FromJSON (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

parseJSON :: Value -> Parser (Unboxed sh e) #

parseJSONList :: Value -> Parser [Unboxed sh e] #

(Binary (LimitType sh), Binary e, Unbox e, Generic (LimitType sh), Generic e) => Binary (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

put :: Unboxed sh e -> Put #

get :: Get (Unboxed sh e) #

putList :: [Unboxed sh e] -> Put #

(Serialize (LimitType sh), Serialize e, Unbox e, Generic (LimitType sh), Generic e) => Serialize (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

put :: Putter (Unboxed sh e) #

get :: Get (Unboxed sh e) #

NFData (LimitType sh) => NFData (MutArr m (Unboxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

rnf :: MutArr m (Unboxed sh e) -> () #

NFData (LimitType sh) => NFData (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

rnf :: Unboxed sh e -> () #

data MutArr m (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

data MutArr m (Unboxed sh e) = MUnboxed !(LimitType sh) !(MVector (PrimState m) e)
type Rep (MutArr m (Unboxed sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

type Rep (MutArr m (Unboxed sh e)) = D1 (MetaData "MutArr" "Data.PrimitiveArray.Dense" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "MUnboxed" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (LimitType sh)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MVector (PrimState m) e))))
type Rep (Unboxed sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

type Rep (Unboxed sh e) = D1 (MetaData "Unboxed" "Data.PrimitiveArray.Dense" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "Unboxed" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (LimitType sh)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector e))))

data C Source #

Phantom type for Complement indices.

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: Monad m => LimitType (z :. PInt C p) -> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

streamDown :: Monad m => LimitType (z :. PInt C p) -> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

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

Defined in Data.PrimitiveArray.Index.Point

IndexStream z => IndexStream (z :. Subword C) Source #

Subword C (complement)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

data O Source #

Phantom type for Outside indices.

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

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

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

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: Monad m => LimitType (z :. PInt O p) -> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

streamDown :: Monad m => LimitType (z :. PInt O p) -> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

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

Defined in Data.PrimitiveArray.Index.Point

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

data I Source #

Phantom type for Inside indices.

Instances
IndexStream z => IndexStream (z :. Boundary k2 I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

streamUp :: Monad m => LimitType (z :. Boundary k2 I) -> LimitType (z :. Boundary k2 I) -> Stream m (z :. Boundary k2 I) Source #

streamDown :: Monad m => LimitType (z :. Boundary k2 I) -> LimitType (z :. Boundary k2 I) -> Stream m (z :. Boundary k2 I) Source #

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

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

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

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

streamDown :: Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

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

Defined in Data.PrimitiveArray.Index.Point

IndexStream z => IndexStream (z :. Subword I) Source #

Subword I (inside)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

IndexStream (Z :. Boundary k2 I) => IndexStream (Boundary k2 I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

newtype Boundary boundaryType ioc Source #

Certain sets have an interface, a particular element with special meaning. In this module, certain `meanings' are already provided. These include a First element and a Last element. We phantom-type these to reduce programming overhead.

Constructors

Boundary 

Fields

Instances
Vector Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

MVector MVector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

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

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

streamUp :: Monad m => LimitType (z :. Boundary k2 I) -> LimitType (z :. Boundary k2 I) -> Stream m (z :. Boundary k2 I) Source #

streamDown :: Monad m => LimitType (z :. Boundary k2 I) -> LimitType (z :. Boundary k2 I) -> Stream m (z :. Boundary k2 I) Source #

Eq (Boundary boundaryType ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

(==) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

(/=) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

Num (Boundary boundaryType ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

(+) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Boundary boundaryType ioc #

(-) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Boundary boundaryType ioc #

(*) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Boundary boundaryType ioc #

negate :: Boundary boundaryType ioc -> Boundary boundaryType ioc #

abs :: Boundary boundaryType ioc -> Boundary boundaryType ioc #

signum :: Boundary boundaryType ioc -> Boundary boundaryType ioc #

fromInteger :: Integer -> Boundary boundaryType ioc #

Ord (Boundary boundaryType ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

compare :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Ordering #

(<) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

(<=) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

(>) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

(>=) :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Bool #

max :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Boundary boundaryType ioc #

min :: Boundary boundaryType ioc -> Boundary boundaryType ioc -> Boundary boundaryType ioc #

Show (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

showsPrec :: Int -> Boundary i t -> ShowS #

show :: Boundary i t -> String #

showList :: [Boundary i t] -> ShowS #

Generic (Boundary boundaryType ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Associated Types

type Rep (Boundary boundaryType ioc) :: Type -> Type #

Methods

from :: Boundary boundaryType ioc -> Rep (Boundary boundaryType ioc) x #

to :: Rep (Boundary boundaryType ioc) x -> Boundary boundaryType ioc #

Hashable (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

hashWithSalt :: Int -> Boundary i t -> Int #

hash :: Boundary i t -> Int #

ToJSON (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

FromJSON (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Binary (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

put :: Boundary i t -> Put #

get :: Get (Boundary i t) #

putList :: [Boundary i t] -> Put #

Serialize (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

put :: Putter (Boundary i t) #

get :: Get (Boundary i t) #

NFData (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Methods

rnf :: Boundary i t -> () #

Unbox (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

IndexStream (Z :. Boundary k2 I) => IndexStream (Boundary k2 I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Index (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

Associated Types

data LimitType (Boundary i t) :: Type Source #

data MVector s (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

type Rep (Boundary boundaryType ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

type Rep (Boundary boundaryType ioc) = D1 (MetaData "Boundary" "Data.PrimitiveArray.Index.BitSetClasses" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "Boundary" PrefixI True) (S1 (MetaSel (Just "getBoundary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

data LimitType (Boundary i t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSetClasses

class ApplyMask s where Source #

Assuming a bitset on bits [0 .. highbit], we can apply a mask that stretches out those bits over [0 .. higherBit] with highbit <= higherBit. Any active interfaces are correctly set as well.

Methods

applyMask :: Mask s -> s -> s Source #

data Fixed t Source #

Fixed allows us to fix some or all bits of a bitset, thereby providing succ/pred operations which are only partially free.

The mask is lazy, this allows us to have undefined for l and h.

f = getFixedMask .&. getFixed are the fixed bits. n = getFixed .&. complement getFixedMask are the free bits. to = complement getFixed is the to move mask n' = popShiftR to n yields the population after the move p = popPermutation undefined n' yields the new population permutation p' = popShiftL to p yields the population moved back final = p' .|. f

Constructors

Fixed 

Fields

type family Mask s :: * Source #

Masks are used quite often for different types of bitsets. We liberate them as a type family.

class SetPredSucc s where Source #

Successor and Predecessor for sets. Designed as a class to accomodate sets with interfaces and without interfaces with one function.

The functions are not written recursively, as we currently only have three cases, and we do not want to "reset" while generating successors and predecessors.

Note that sets have a partial order. Within the group of element with the same popCount, we use popPermutation which has the same stepping order for both, setSucc and setPred.

Methods

setSucc :: Int -> Int -> s -> Maybe s Source #

Set successor. The first argument is the lower set limit, the second the upper set limit, the third the current set.

setPred :: Int -> Int -> s -> Maybe s Source #

Set predecessor. The first argument is the lower set limit, the second the upper set limit, the third the current set.

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

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 #

data Any Source #

Declare the interface to match anything.

TODO needed? want to use later in ADPfusion

data Last Source #

Declare the interface to be the end of a path.

data First Source #

Declare the interface to be the start of a path.

streamUpBndMk :: Monad m => b -> p -> a -> m (a, b) Source #

streamUpBndStep :: Monad m => p -> Int -> (a, Int) -> m (Step (a, Int) (a :. Boundary boundaryType ioc)) Source #

streamDownBndMk :: Monad m => p -> b -> a -> m (a, b) Source #

streamDownBndStep :: Monad m => Int -> p -> (a, Int) -> m (Step (a, Int) (a :. Boundary boundaryType ioc)) Source #

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

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

NFData (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Methods

rnf :: 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

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.BitSet0

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

Defined in Data.PrimitiveArray.Index.BitSet0

Index (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

Associated Types

data LimitType (BitSet t) :: Type 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 #

data MVector s (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

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.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "BitSet" PrefixI True) (S1 (MetaSel (Just "_bitSet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

data LimitType (BitSet t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet0

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

data BitSet1 i ioc Source #

The bitset with one interface or boundary.

Constructors

BitSet1 

Fields

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

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

Defined in Data.PrimitiveArray.Index.BitSet1

Methods

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

streamDown :: 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 :: Monad m => LimitType (z :. BitSet1 i I) -> LimitType (z :. BitSet1 i I) -> Stream m (z :. BitSet1 i I) Source #

streamDown :: 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 :: Monad m => LimitType (BitSet1 i t) -> LimitType (BitSet1 i t) -> Stream m (BitSet1 i t) Source #

streamDown :: 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) :: Type Source #

Methods

linearIndex :: LimitType (BitSet1 bnd ioc) -> BitSet1 bnd ioc -> Int 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 #

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 #

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

Defined in Data.PrimitiveArray.Index.BitSet1

data 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.9.0.0-7o4e78MXLzPCxIvR95QAvs" 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))))
data Vector (BitSet1 i ioc) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.BitSet1

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

Defined in Data.PrimitiveArray.Index.BitSet1

data LimitType (BitSet1 bnd ioc) = LtNumBits1 Int

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

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

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
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 :: Monad m => LimitType (z :. PInt C p) -> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

streamDown :: 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 :: Monad m => LimitType (z :. PInt O p) -> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

streamDown :: 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 :: Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

streamDown :: 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 :: (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 #

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

NFData (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

rnf :: 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 :: Monad m => LimitType (PInt ioc p) -> LimitType (PInt ioc p) -> Stream m (PInt ioc p) Source #

streamDown :: 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) :: Type Source #

data MVector s (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

data 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.9.0.0-7o4e78MXLzPCxIvR95QAvs" 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.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "PInt" PrefixI True) (S1 (MetaSel (Just "getPInt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

data Vector (PInt t p) = V_PInt (Vector Int)
data LimitType (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

data LimitType (PInt t p) = LtPInt Int

newtype PointR t Source #

A point in a right-linear grammars.

Constructors

PointR 

Fields

Instances
Eq (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

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 #

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.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "PointR" PrefixI True) (S1 (MetaSel (Just "fromPointR") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype PointL t Source #

A point in a left-linear grammar. The syntactic symbol is in left-most position.

Constructors

PointL 

Fields

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

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

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

NFData (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

rnf :: PointL t -> () #

Unbox (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

Index (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

data LimitType (PointL t) :: Type Source #

data MVector s (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

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.9.0.0-7o4e78MXLzPCxIvR95QAvs" 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.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "PointL" PrefixI True) (S1 (MetaSel (Just "fromPointL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

data LimitType (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

data SP z Source #

Constructors

SP !z !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
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] #

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

NFData (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

rnf :: 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

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

IndexStream z => IndexStream (z :. Subword I) Source #

Subword I (inside)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

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

Defined in Data.PrimitiveArray.Index.Subword

Index (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

data LimitType (Subword t) :: Type Source #

data MVector s (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

data 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.9.0.0-7o4e78MXLzPCxIvR95QAvs" 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.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "Subword" PrefixI True) (S1 (MetaSel (Just "fromSubword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int :. Int))))
data Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

data 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.

data Unit t Source #

Constructors

Unit 
Instances
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 #

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

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 #

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

Defined in Data.PrimitiveArray.Index.Unit

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

Eq (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

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

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

Ord (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

compare :: Unit t -> Unit t -> Ordering #

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

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

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

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

max :: Unit t -> Unit t -> Unit t #

min :: Unit t -> Unit t -> Unit t #

Read (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Show (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

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

show :: Unit t -> String #

showList :: [Unit t] -> ShowS #

Generic (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Associated Types

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

Methods

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

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

Arbitrary (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

arbitrary :: Gen (Unit t) #

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

Hashable (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

hashWithSalt :: Int -> Unit t -> Int #

hash :: Unit t -> Int #

ToJSON (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

ToJSONKey (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

FromJSON (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

FromJSONKey (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Binary (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

put :: Unit t -> Put #

get :: Get (Unit t) #

putList :: [Unit t] -> Put #

Serialize (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

put :: Putter (Unit t) #

get :: Get (Unit t) #

NFData (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

rnf :: Unit t -> () #

Unbox (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

IndexStream z => IndexStream (z :. Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Methods

streamUp :: Monad m => LimitType (z :. Unit t) -> LimitType (z :. Unit t) -> Stream m (z :. Unit t) Source #

streamDown :: Monad m => LimitType (z :. Unit t) -> LimitType (z :. Unit t) -> Stream m (z :. Unit t) Source #

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

Defined in Data.PrimitiveArray.Index.Unit

Methods

streamUp :: Monad m => LimitType (Unit t) -> LimitType (Unit t) -> Stream m (Unit t) Source #

streamDown :: Monad m => LimitType (Unit t) -> LimitType (Unit t) -> Stream m (Unit t) Source #

Index (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

Associated Types

data LimitType (Unit t) :: Type Source #

data MVector s (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

data MVector s (Unit t) = MV_Unit (MVector s ())
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.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "LtUnit" PrefixI False) (U1 :: Type -> Type))
type Rep (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

type Rep (Unit t) = D1 (MetaData "Unit" "Data.PrimitiveArray.Index.Unit" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" False) (C1 (MetaCons "Unit" PrefixI False) (U1 :: Type -> Type))
data Vector (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

data Vector (Unit t) = V_Unit (Vector ())
data LimitType (Unit t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Unit

data LimitType (Unit t) = LtUnit

(!) :: (Index sh, Unbox p, Show sh, Show (LimitType sh)) => Unboxed sh p -> sh -> p Source #

Bounds-checked version of indexing.

First, we check via inBounds, second we check if the linear index is outside of the allocated area.