Copyright | (c) Dong Han 2017 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Unified unboxed and boxed array operations using type family.
All operations are NOT bound checked, if you need checked operations please use Z.Data.Array.Checked. It exports exactly same APIs so that you can switch between without pain.
Some mnemonics:
newArr
,newArrWith
return mutable array,readArr
,writeArr
works on them,setArr
fill elements with offset and length.indexArr
works on immutable one, useindexArr'
to avoid indexing thunk.- The order of arguements of
copyArr
,copyMutableArr
andmoveArr
are always target and its offset come first, and source and source offset follow, copying length comes last.
Synopsis
- class Arr (arr :: * -> *) a where
- type MArr arr = (mar :: * -> * -> *) | mar -> arr
- newArr :: (PrimMonad m, PrimState m ~ s) => Int -> m (MArr arr s a)
- newArrWith :: (PrimMonad m, PrimState m ~ s) => Int -> a -> m (MArr arr s a)
- readArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> m a
- writeArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> a -> m ()
- setArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> Int -> a -> m ()
- indexArr :: arr a -> Int -> a
- indexArr' :: arr a -> Int -> (# a #)
- indexArrM :: Monad m => arr a -> Int -> m a
- freezeArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> Int -> m (arr a)
- thawArr :: (PrimMonad m, PrimState m ~ s) => arr a -> Int -> Int -> m (MArr arr s a)
- unsafeFreezeArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> m (arr a)
- unsafeThawArr :: (PrimMonad m, PrimState m ~ s) => arr a -> m (MArr arr s a)
- copyArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> arr a -> Int -> Int -> m ()
- copyMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> MArr arr s a -> Int -> Int -> m ()
- moveArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> MArr arr s a -> Int -> Int -> m ()
- cloneArr :: arr a -> Int -> Int -> arr a
- cloneMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> Int -> m (MArr arr s a)
- resizeMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> m (MArr arr s a)
- shrinkMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> m ()
- sameMutableArr :: MArr arr s a -> MArr arr s a -> Bool
- sizeofArr :: arr a -> Int
- sizeofMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> m Int
- sameArr :: arr a -> arr a -> Bool
- data RealWorld
- data Array a = Array {}
- data MutableArray s a = MutableArray {
- marray# :: MutableArray# s a
- data SmallArray a = SmallArray (SmallArray# a)
- data SmallMutableArray s a = SmallMutableArray (SmallMutableArray# s a)
- uninitialized :: a
- data PrimArray a = PrimArray ByteArray#
- data MutablePrimArray s a = MutablePrimArray (MutableByteArray# s)
- class Prim a where
- sizeOf# :: a -> Int#
- alignment# :: a -> Int#
- indexByteArray# :: ByteArray# -> Int# -> a
- readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
- writeByteArray# :: MutableByteArray# s -> Int# -> a -> State# s -> State# s
- setByteArray# :: MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s
- indexOffAddr# :: Addr# -> Int# -> a
- readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, a #)
- writeOffAddr# :: Addr# -> Int# -> a -> State# s -> State# s
- setOffAddr# :: Addr# -> Int# -> Int# -> a -> State# s -> State# s
- newPinnedPrimArray :: (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a)
- newAlignedPinnedPrimArray :: (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a)
- copyPrimArrayToPtr :: (PrimMonad m, Prim a) => Ptr a -> PrimArray a -> Int -> Int -> m ()
- copyMutablePrimArrayToPtr :: (PrimMonad m, Prim a) => Ptr a -> MutablePrimArray (PrimState m) a -> Int -> Int -> m ()
- copyPtrToMutablePrimArray :: (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> Ptr a -> Int -> m ()
- primArrayContents :: PrimArray a -> Ptr a
- mutablePrimArrayContents :: MutablePrimArray s a -> Ptr a
- withPrimArrayContents :: PrimArray a -> (Ptr a -> IO b) -> IO b
- withMutablePrimArrayContents :: MutablePrimArray RealWorld a -> (Ptr a -> IO b) -> IO b
- isPrimArrayPinned :: PrimArray a -> Bool
- isMutablePrimArrayPinned :: MutablePrimArray s a -> Bool
- data UnliftedArray a = UnliftedArray ArrayArray#
- data MutableUnliftedArray s a = MutableUnliftedArray (MutableArrayArray# s)
- class PrimUnlifted a where
- writeUnliftedArray# :: MutableArrayArray# s -> Int# -> a -> State# s -> State# s
- readUnliftedArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, a #)
- indexUnliftedArray# :: ArrayArray# -> Int# -> a
- data ArrayException
- class Cast source destination
- castArray :: (Arr arr a, Cast a b) => arr a -> arr b
- castMutableArray :: (Arr arr a, Cast a b) => MArr arr s a -> MArr arr s b
- sizeOf :: Prim a => a -> Int
Arr typeclass
class Arr (arr :: * -> *) a where Source #
A typeclass to unify box & unboxed, mutable & immutable array operations.
Most of these functions simply wrap their primitive counterpart, if there's no primitive ones, we polyfilled using other operations to get the same semantics.
One exception is that shrinkMutableArr
only perform closure resizing on PrimArray
because
current RTS support only that, shrinkMutableArr
will do nothing on other array type.
It's reasonable to trust GHC with specializing & inlining these polymorphric functions. They are used across this package and perform identical to their monomophric counterpart.
newArr :: (PrimMonad m, PrimState m ~ s) => Int -> m (MArr arr s a) Source #
Make a new array with given size.
For boxed array, all elements are uninitialized
which shall not be accessed.
For primitive array, elements are just random garbage.
newArrWith :: (PrimMonad m, PrimState m ~ s) => Int -> a -> m (MArr arr s a) Source #
Make a new array and fill it with an initial value.
readArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> m a Source #
Index mutable array in a primitive monad.
writeArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> a -> m () Source #
Write mutable array in a primitive monad.
setArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> Int -> a -> m () Source #
Fill mutable array with a given value.
indexArr :: arr a -> Int -> a Source #
Index immutable array, which is a pure operation. This operation often
result in an indexing thunk for lifted arrays, use 'indexArr'' or indexArrM
if that's not desired.
indexArr' :: arr a -> Int -> (# a #) Source #
Index immutable array, pattern match on the unboxed unit tuple to force indexing (without forcing the element).
indexArrM :: Monad m => arr a -> Int -> m a Source #
Index immutable array in a primitive monad, this helps in situations that you want your indexing result is not a thunk referencing whole array.
freezeArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> Int -> m (arr a) Source #
Safely freeze mutable array by make a immutable copy of its slice.
thawArr :: (PrimMonad m, PrimState m ~ s) => arr a -> Int -> Int -> m (MArr arr s a) Source #
Safely thaw immutable array by make a mutable copy of its slice.
unsafeFreezeArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> m (arr a) Source #
In place freeze a mutable array, the original mutable array can not be used anymore.
unsafeThawArr :: (PrimMonad m, PrimState m ~ s) => arr a -> m (MArr arr s a) Source #
In place thaw a immutable array, the original immutable array can not be used anymore.
:: (PrimMonad m, PrimState m ~ s) | |
=> MArr arr s a | target |
-> Int | target offset |
-> arr a | source |
-> Int | source offset |
-> Int | source length |
-> m () |
Copy a slice of immutable array to mutable array at given offset.
:: (PrimMonad m, PrimState m ~ s) | |
=> MArr arr s a | target |
-> Int | target offset |
-> MArr arr s a | source |
-> Int | source offset |
-> Int | source length |
-> m () |
Copy a slice of mutable array to mutable array at given offset. The two mutable arrays shall no be the same one.
:: (PrimMonad m, PrimState m ~ s) | |
=> MArr arr s a | target |
-> Int | target offset |
-> MArr arr s a | source |
-> Int | source offset |
-> Int | source length |
-> m () |
Copy a slice of mutable array to mutable array at given offset. The two mutable arrays may be the same one.
cloneArr :: arr a -> Int -> Int -> arr a Source #
Create immutable copy.
cloneMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> Int -> m (MArr arr s a) Source #
Create mutable copy.
resizeMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> m (MArr arr s a) Source #
Resize mutable array to given size.
shrinkMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> m () Source #
Shrink mutable array to given size. This operation only works on primitive arrays.
For some array types, this is a no-op, e.g. sizeOfMutableArr
will not change.
sameMutableArr :: MArr arr s a -> MArr arr s a -> Bool Source #
Is two mutable array are reference equal.
sizeofArr :: arr a -> Int Source #
Size of immutable array.
sizeofMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr arr s a -> m Int Source #
Size of mutable array.
sameArr :: arr a -> arr a -> Bool Source #
Is two immutable array are referencing the same one.
Note that sameArr
's result may change depending on compiler's optimizations, for example
let arr = runST ... in arr
may return false if compiler decides to
inline it.sameArr
arr
See https://ghc.haskell.org/trac/ghc/ticket/13908 for more background.
Instances
RealWorld
is deeply magical. It is primitive, but it is not
unlifted (hence ptrArg
). We never manipulate values of type
RealWorld
; it's only used in the type system, to parameterise State#
.
Boxed array type
Boxed arrays
Instances
Monad Array | |
Functor Array | |
MonadFix Array | |
Defined in Data.Primitive.Array | |
MonadFail Array | |
Defined in Data.Primitive.Array | |
Applicative Array | |
Foldable Array | |
Defined in Data.Primitive.Array fold :: Monoid m => Array m -> m # foldMap :: Monoid m => (a -> m) -> Array a -> m # foldMap' :: Monoid m => (a -> m) -> Array a -> m # foldr :: (a -> b -> b) -> b -> Array a -> b # foldr' :: (a -> b -> b) -> b -> Array a -> b # foldl :: (b -> a -> b) -> b -> Array a -> b # foldl' :: (b -> a -> b) -> b -> Array a -> b # foldr1 :: (a -> a -> a) -> Array a -> a # foldl1 :: (a -> a -> a) -> Array a -> a # elem :: Eq a => a -> Array a -> Bool # maximum :: Ord a => Array a -> a # minimum :: Ord a => Array a -> a # | |
Traversable Array | |
Eq1 Array | Since: primitive-0.6.4.0 |
Ord1 Array | Since: primitive-0.6.4.0 |
Defined in Data.Primitive.Array | |
Read1 Array | Since: primitive-0.6.4.0 |
Defined in Data.Primitive.Array | |
Show1 Array | Since: primitive-0.6.4.0 |
MonadZip Array | |
Alternative Array | |
MonadPlus Array | |
NFData1 Array | |
Defined in Data.Primitive.Array | |
Arr Array a Source # | |
Defined in Z.Data.Array newArr :: (PrimMonad m, PrimState m ~ s) => Int -> m (MArr Array s a) Source # newArrWith :: (PrimMonad m, PrimState m ~ s) => Int -> a -> m (MArr Array s a) Source # readArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> Int -> m a Source # writeArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> Int -> a -> m () Source # setArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> Int -> Int -> a -> m () Source # indexArr :: Array a -> Int -> a Source # indexArr' :: Array a -> Int -> (# a #) Source # indexArrM :: Monad m => Array a -> Int -> m a Source # freezeArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> Int -> Int -> m (Array a) Source # thawArr :: (PrimMonad m, PrimState m ~ s) => Array a -> Int -> Int -> m (MArr Array s a) Source # unsafeFreezeArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> m (Array a) Source # unsafeThawArr :: (PrimMonad m, PrimState m ~ s) => Array a -> m (MArr Array s a) Source # copyArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> Int -> Array a -> Int -> Int -> m () Source # copyMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> Int -> MArr Array s a -> Int -> Int -> m () Source # moveArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> Int -> MArr Array s a -> Int -> Int -> m () Source # cloneArr :: Array a -> Int -> Int -> Array a Source # cloneMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> Int -> Int -> m (MArr Array s a) Source # resizeMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> Int -> m (MArr Array s a) Source # shrinkMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> Int -> m () Source # sameMutableArr :: MArr Array s a -> MArr Array s a -> Bool Source # sizeofArr :: Array a -> Int Source # sizeofMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr Array s a -> m Int Source # | |
Vec Array a Source # | |
IsList (Array a) | |
Eq a => Eq (Array a) | |
Data a => Data (Array a) | |
Defined in Data.Primitive.Array gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Array a -> c (Array a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array a) # toConstr :: Array a -> Constr # dataTypeOf :: Array a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Array a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array a)) # gmapT :: (forall b. Data b => b -> b) -> Array a -> Array a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array a -> r # gmapQ :: (forall d. Data d => d -> u) -> Array a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Array a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # | |
Ord a => Ord (Array a) | Lexicographic ordering. Subject to change between major versions. |
Read a => Read (Array a) | |
Show a => Show (Array a) | |
Semigroup (Array a) | Since: primitive-0.6.3.0 |
Monoid (Array a) | |
NFData a => NFData (Array a) | |
Defined in Data.Primitive.Array | |
Print a => Print (Array a) Source # | |
Defined in Z.Data.Text.Print | |
JSON a => JSON (Array a) Source # | |
type MArr Array Source # | |
Defined in Z.Data.Array | |
type IArray Array Source # | |
Defined in Z.Data.Vector.Base | |
type Item (Array a) | |
Defined in Data.Primitive.Array |
data MutableArray s a #
Mutable boxed arrays associated with a primitive state token.
MutableArray | |
|
Instances
Eq (MutableArray s a) | |
Defined in Data.Primitive.Array (==) :: MutableArray s a -> MutableArray s a -> Bool # (/=) :: MutableArray s a -> MutableArray s a -> Bool # | |
(Typeable s, Typeable a) => Data (MutableArray s a) | |
Defined in Data.Primitive.Array gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MutableArray s a -> c (MutableArray s a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MutableArray s a) # toConstr :: MutableArray s a -> Constr # dataTypeOf :: MutableArray s a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MutableArray s a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MutableArray s a)) # gmapT :: (forall b. Data b => b -> b) -> MutableArray s a -> MutableArray s a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MutableArray s a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MutableArray s a -> r # gmapQ :: (forall d. Data d => d -> u) -> MutableArray s a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MutableArray s a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # |
data SmallArray a #
Instances
data SmallMutableArray s a #
Instances
Eq (SmallMutableArray s a) | |
Defined in Data.Primitive.SmallArray (==) :: SmallMutableArray s a -> SmallMutableArray s a -> Bool # (/=) :: SmallMutableArray s a -> SmallMutableArray s a -> Bool # | |
(Typeable s, Typeable a) => Data (SmallMutableArray s a) | |
Defined in Data.Primitive.SmallArray gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SmallMutableArray s a -> c (SmallMutableArray s a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SmallMutableArray s a) # toConstr :: SmallMutableArray s a -> Constr # dataTypeOf :: SmallMutableArray s a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SmallMutableArray s a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SmallMutableArray s a)) # gmapT :: (forall b. Data b => b -> b) -> SmallMutableArray s a -> SmallMutableArray s a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SmallMutableArray s a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SmallMutableArray s a -> r # gmapQ :: (forall d. Data d => d -> u) -> SmallMutableArray s a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SmallMutableArray s a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # |
uninitialized :: a Source #
Bottom value (throw (
)
for initialize new boxed array(UndefinedElement
uninitialized
)Array
, SmallArray
..).
Primitive array type
Arrays of unboxed elements. This accepts types like Double
, Char
,
Int
, and Word
, as well as their fixed-length variants (Word8
,
Word16
, etc.). Since the elements are unboxed, a PrimArray
is strict
in its elements. This differs from the behavior of Array
, which is lazy
in its elements.
Instances
data MutablePrimArray s a #
Mutable primitive arrays associated with a primitive state token.
These can be written to and read from in a monadic context that supports
sequencing such as IO
or ST
. Typically, a mutable primitive array will
be built and then convert to an immutable primitive array using
unsafeFreezePrimArray
. However, it is also acceptable to simply discard
a mutable primitive array since it lives in managed memory and will be
garbage collected when no longer referenced.
Instances
Eq (MutablePrimArray s a) | |
Defined in Data.Primitive.PrimArray (==) :: MutablePrimArray s a -> MutablePrimArray s a -> Bool # (/=) :: MutablePrimArray s a -> MutablePrimArray s a -> Bool # | |
NFData (MutablePrimArray s a) | |
Defined in Data.Primitive.PrimArray rnf :: MutablePrimArray s a -> () # | |
PrimUnlifted (MutablePrimArray s a) Source # | |
Defined in Z.Data.Array.UnliftedArray writeUnliftedArray# :: MutableArrayArray# s0 -> Int# -> MutablePrimArray s a -> State# s0 -> State# s0 Source # readUnliftedArray# :: MutableArrayArray# s0 -> Int# -> State# s0 -> (# State# s0, MutablePrimArray s a #) Source # indexUnliftedArray# :: ArrayArray# -> Int# -> MutablePrimArray s a Source # |
Class of types supporting primitive array operations. This includes
interfacing with GC-managed memory (functions suffixed with ByteArray#
)
and interfacing with unmanaged memory (functions suffixed with Addr#
).
Endianness is platform-dependent.
Size of values of type a
. The argument is not used.
alignment# :: a -> Int# #
Alignment of values of type a
. The argument is not used.
indexByteArray# :: ByteArray# -> Int# -> a #
Read a value from the array. The offset is in elements of type
a
rather than in bytes.
readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) #
Read a value from the mutable array. The offset is in elements of type
a
rather than in bytes.
writeByteArray# :: MutableByteArray# s -> Int# -> a -> State# s -> State# s #
Write a value to the mutable array. The offset is in elements of type
a
rather than in bytes.
setByteArray# :: MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s #
Fill a slice of the mutable array with a value. The offset and length
of the chunk are in elements of type a
rather than in bytes.
indexOffAddr# :: Addr# -> Int# -> a #
Read a value from a memory position given by an address and an offset.
The memory block the address refers to must be immutable. The offset is in
elements of type a
rather than in bytes.
readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, a #) #
Read a value from a memory position given by an address and an offset.
The offset is in elements of type a
rather than in bytes.
writeOffAddr# :: Addr# -> Int# -> a -> State# s -> State# s #
Write a value to a memory position given by an address and an offset.
The offset is in elements of type a
rather than in bytes.
setOffAddr# :: Addr# -> Int# -> Int# -> a -> State# s -> State# s #
Fill a memory block given by an address, an offset and a length.
The offset and length are in elements of type a
rather than in bytes.
Instances
Array operations
newPinnedPrimArray :: (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) #
Create a pinned primitive array of the specified size in elements. The garbage collector is guaranteed not to move it.
Since: primitive-0.7.1.0
newAlignedPinnedPrimArray :: (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) #
Create a pinned primitive array of the specified size in elements and
with the alignment given by its Prim
instance. The garbage collector is
guaranteed not to move it.
Since: primitive-0.7.0.0
:: (PrimMonad m, Prim a) | |
=> Ptr a | destination pointer |
-> PrimArray a | source array |
-> Int | offset into source array |
-> Int | number of prims to copy |
-> m () |
Copy a slice of an immutable primitive array to an address.
The offset and length are given in elements of type a
.
This function assumes that the Prim
instance of a
agrees with the Storable
instance. This function is only
available when building with GHC 7.8 or newer.
Note: this function does not do bounds or overlap checking.
:: (PrimMonad m, Prim a) | |
=> Ptr a | destination pointer |
-> MutablePrimArray (PrimState m) a | source array |
-> Int | offset into source array |
-> Int | number of prims to copy |
-> m () |
Copy a slice of an immutable primitive array to an address.
The offset and length are given in elements of type a
.
This function assumes that the Prim
instance of a
agrees with the Storable
instance. This function is only
available when building with GHC 7.8 or newer.
Note: this function does not do bounds or overlap checking.
:: (PrimMonad m, Prim a) | |
=> MutablePrimArray (PrimState m) a | destination array |
-> Int | destination offset |
-> Ptr a | source pointer |
-> Int | number of elements |
-> m () |
Copy from a pointer to a mutable primitive array.
The offset and length are given in elements of type a
.
This function is only available when building with GHC 7.8
or newer.
primArrayContents :: PrimArray a -> Ptr a #
Yield a pointer to the array's data. This operation is only safe on
pinned prim arrays allocated by newPinnedByteArray
or
newAlignedPinnedByteArray
.
Since: primitive-0.7.1.0
mutablePrimArrayContents :: MutablePrimArray s a -> Ptr a #
Yield a pointer to the array's data. This operation is only safe on
pinned byte arrays allocated by newPinnedByteArray
or
newAlignedPinnedByteArray
.
Since: primitive-0.7.1.0
withPrimArrayContents :: PrimArray a -> (Ptr a -> IO b) -> IO b Source #
Yield a pointer to the array's data and do computation with it.
This operation is only safe on pinned primitive arrays allocated by newPinnedPrimArray
or
newAlignedPinnedPrimArray
.
Don't pass a forever loop to this function, see #14346.
withMutablePrimArrayContents :: MutablePrimArray RealWorld a -> (Ptr a -> IO b) -> IO b Source #
Yield a pointer to the array's data and do computation with it.
This operation is only safe on pinned primitive arrays allocated by newPinnedPrimArray
or
newAlignedPinnedPrimArray
.
Don't pass a forever loop to this function, see #14346.
isPrimArrayPinned :: PrimArray a -> Bool #
Check whether or not the byte array is pinned. Pinned primitive arrays cannot
be moved by the garbage collector. It is safe to use primArrayContents
on such byte arrays. This function is only available when compiling with
GHC 8.2 or newer.
Since: primitive-0.7.1.0
isMutablePrimArrayPinned :: MutablePrimArray s a -> Bool #
Check whether or not the mutable primitive array is pinned. This function is only available when compiling with GHC 8.2 or newer.
Since: primitive-0.7.1.0
Unlifted array type
data UnliftedArray a Source #
Array holding PrimUnlifted
values.
Instances
data MutableUnliftedArray s a Source #
Mutable array holding PrimUnlifted
values.
class PrimUnlifted a where Source #
Types with TYPE
UnliftedRep
, which can be stored / retrieved in ArrayArray#
.
writeUnliftedArray# :: MutableArrayArray# s -> Int# -> a -> State# s -> State# s Source #
readUnliftedArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, a #) Source #
indexUnliftedArray# :: ArrayArray# -> Int# -> a Source #
Instances
The ArrayException
type
data ArrayException #
Exceptions generated by array operations
IndexOutOfBounds String | An attempt was made to index an array outside its declared bounds. |
UndefinedElement String | An attempt was made to evaluate an element of an array that had not been initialized. |
Instances
Eq ArrayException | Since: base-4.2.0.0 |
Defined in GHC.IO.Exception (==) :: ArrayException -> ArrayException -> Bool # (/=) :: ArrayException -> ArrayException -> Bool # | |
Ord ArrayException | Since: base-4.2.0.0 |
Defined in GHC.IO.Exception compare :: ArrayException -> ArrayException -> Ordering # (<) :: ArrayException -> ArrayException -> Bool # (<=) :: ArrayException -> ArrayException -> Bool # (>) :: ArrayException -> ArrayException -> Bool # (>=) :: ArrayException -> ArrayException -> Bool # max :: ArrayException -> ArrayException -> ArrayException # min :: ArrayException -> ArrayException -> ArrayException # | |
Show ArrayException | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception showsPrec :: Int -> ArrayException -> ShowS # show :: ArrayException -> String # showList :: [ArrayException] -> ShowS # | |
Exception ArrayException | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception |
Cast between primitive arrays
class Cast source destination Source #
Cast
between primitive types of the same size.
Instances
Cast Double Int64 Source # | |
Cast Double Word64 Source # | |
Cast Float Int32 Source # | |
Cast Float Word32 Source # | |
Cast Int Word Source # | |
Cast Int8 Word8 Source # | |
Cast Int16 Word16 Source # | |
Cast Int32 Float Source # | |
Cast Int32 Word32 Source # | |
Cast Int64 Double Source # | |
Cast Int64 Word64 Source # | |
Cast Word Int Source # | |
Cast Word8 Int8 Source # | |
Cast Word16 Int16 Source # | |
Cast Word32 Float Source # | |
Cast Word32 Int32 Source # | |
Cast Word64 Double Source # | |
Cast Word64 Int64 Source # | |
Coercible a b => Cast a b Source # | |
Defined in Z.Data.Array.Cast |
castMutableArray :: (Arr arr a, Cast a b) => MArr arr s a -> MArr arr s b Source #
Cast between mutable arrays