Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data PrimArray a = PrimArray ByteArray#
- 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
- foldl' :: Prim a => (b -> a -> b) -> b -> PrimArray a -> b
- foldr :: Prim a => (a -> b -> b) -> b -> PrimArray a -> b
- length :: Prim a => PrimArray a -> Int
- writeN :: (MonadIO m, Prim a) => Int -> Fold m a (PrimArray a)
- write :: (MonadIO m, Prim a) => Fold m a (PrimArray a)
- toStreamD :: (Prim a, Monad m) => PrimArray a -> Stream m a
- toStreamDRev :: (Prim a, Monad m) => PrimArray a -> Stream m a
- toStream :: (Prim a, Monad m, IsStream t) => PrimArray a -> t m a
- toStreamRev :: (Prim a, Monad m, IsStream t) => PrimArray a -> t m a
- read :: (Prim a, Monad m) => Unfold m (PrimArray a) a
- readSlice :: (Prim a, Monad m) => Int -> Int -> Unfold m (PrimArray a) a
- fromListN :: Prim a => Int -> [a] -> PrimArray a
- fromList :: Prim a => [a] -> PrimArray a
- fromStreamDN :: (MonadIO m, Prim a) => Int -> Stream m a -> m (PrimArray a)
- fromStreamD :: (MonadIO m, Prim a) => Stream m a -> m (PrimArray a)
- fromStreamN :: (MonadIO m, Prim a) => Int -> SerialT m a -> m (PrimArray a)
- fromStream :: (MonadIO m, Prim a) => SerialT m a -> m (PrimArray a)
- streamFold :: (Prim a, Monad m) => (SerialT m a -> m b) -> PrimArray a -> m b
- fold :: (Prim a, Monad m) => Fold m a b -> PrimArray a -> m b
Documentation
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
(Eq a, Prim a) => Eq (PrimArray a) Source # | Since: 0.6.4.0 |
(Ord a, Prim a) => Ord (PrimArray a) Source # | Lexicographic ordering. Subject to change between major versions. Since: 0.6.4.0 |
Defined in Streamly.Internal.Data.Prim.Array.Types | |
(Show a, Prim a) => Show (PrimArray a) Source # | Since: 0.6.4.0 |
Prim a => NFData (PrimArray a) Source # | |
Defined in Streamly.Internal.Data.Prim.Array |
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.