License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
An unboxed array of primitive types
All the cells in the array are in one chunk of contiguous memory.
Synopsis
- data UArray ty = UArray !(Offset ty) !(CountOf ty) !(UArrayBackend ty)
- class Eq ty => PrimType ty where
- type PrimSize ty :: Nat
- primSizeInBytes :: Proxy ty -> CountOf Word8
- primShiftToBytes :: Proxy ty -> Int
- primBaUIndex :: ByteArray# -> Offset ty -> ty
- primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> prim ty
- primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> ty -> prim ()
- primAddrIndex :: Addr# -> Offset ty -> ty
- primAddrRead :: PrimMonad prim => Addr# -> Offset ty -> prim ty
- primAddrWrite :: PrimMonad prim => Addr# -> Offset ty -> ty -> prim ()
- copy :: PrimType ty => UArray ty -> UArray ty
- unsafeCopyAtRO :: forall prim ty. (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> UArray ty -> Offset ty -> CountOf ty -> prim ()
- recast :: forall a b. (PrimType a, PrimType b) => UArray a -> UArray b
- unsafeRecast :: (PrimType a, PrimType b) => UArray a -> UArray b
- length :: UArray ty -> CountOf ty
- freeze :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> prim (UArray ty)
- unsafeFreeze :: PrimMonad prim => MUArray ty (PrimState prim) -> prim (UArray ty)
- thaw :: (PrimMonad prim, PrimType ty) => UArray ty -> prim (MUArray ty (PrimState prim))
- unsafeThaw :: (PrimType ty, PrimMonad prim) => UArray ty -> prim (MUArray ty (PrimState prim))
- vFromListN :: forall ty. PrimType ty => CountOf ty -> [ty] -> UArray ty
- new :: (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MUArray ty (PrimState prim))
- create :: forall ty. PrimType ty => CountOf ty -> (Offset ty -> ty) -> UArray ty
- createFromIO :: PrimType ty => CountOf ty -> (Ptr ty -> IO (CountOf ty)) -> IO (UArray ty)
- createFromPtr :: PrimType ty => Ptr ty -> CountOf ty -> IO (UArray ty)
- sub :: PrimType ty => UArray ty -> Offset ty -> Offset ty -> UArray ty
- copyToPtr :: forall ty prim. (PrimType ty, PrimMonad prim) => UArray ty -> Ptr ty -> prim ()
- withPtr :: forall ty prim a. (PrimMonad prim, PrimType ty) => UArray ty -> (Ptr ty -> prim a) -> prim a
- withMutablePtr :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a
- unsafeFreezeShrink :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> CountOf ty -> prim (UArray ty)
- freezeShrink :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> CountOf ty -> prim (UArray ty)
- fromBlock :: PrimType ty => Block ty -> UArray ty
- toBlock :: PrimType ty => UArray ty -> Block ty
- update :: PrimType ty => UArray ty -> [(Offset ty, ty)] -> UArray ty
- unsafeUpdate :: PrimType ty => UArray ty -> [(Offset ty, ty)] -> UArray ty
- unsafeIndex :: forall ty. PrimType ty => UArray ty -> Offset ty -> ty
- unsafeIndexer :: (PrimMonad prim, PrimType ty) => UArray ty -> ((Offset ty -> ty) -> prim a) -> prim a
- unsafeDewrap :: (Block ty -> Offset ty -> a) -> (Ptr ty -> Offset ty -> ST s a) -> UArray ty -> a
- unsafeRead :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> prim ty
- unsafeWrite :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> ty -> prim ()
- equalMemcmp :: PrimType ty => UArray ty -> UArray ty -> Bool
- singleton :: PrimType ty => ty -> UArray ty
- replicate :: PrimType ty => CountOf ty -> ty -> UArray ty
- map :: (PrimType a, PrimType b) => (a -> b) -> UArray a -> UArray b
- mapIndex :: (PrimType a, PrimType b) => (Offset b -> a -> b) -> UArray a -> UArray b
- findIndex :: PrimType ty => ty -> UArray ty -> Maybe (Offset ty)
- revFindIndex :: PrimType ty => ty -> UArray ty -> Maybe (Offset ty)
- index :: PrimType ty => UArray ty -> Offset ty -> ty
- null :: UArray ty -> Bool
- take :: CountOf ty -> UArray ty -> UArray ty
- unsafeTake :: CountOf ty -> UArray ty -> UArray ty
- drop :: CountOf ty -> UArray ty -> UArray ty
- unsafeDrop :: CountOf ty -> UArray ty -> UArray ty
- splitAt :: CountOf ty -> UArray ty -> (UArray ty, UArray ty)
- revDrop :: CountOf ty -> UArray ty -> UArray ty
- revTake :: CountOf ty -> UArray ty -> UArray ty
- revSplitAt :: CountOf ty -> UArray ty -> (UArray ty, UArray ty)
- splitOn :: PrimType ty => (ty -> Bool) -> UArray ty -> [UArray ty]
- break :: forall ty. PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty)
- breakEnd :: forall ty. PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty)
- breakElem :: PrimType ty => ty -> UArray ty -> (UArray ty, UArray ty)
- breakLine :: UArray Word8 -> Either Bool (UArray Word8, UArray Word8)
- elem :: PrimType ty => ty -> UArray ty -> Bool
- indices :: PrimType ty => UArray ty -> UArray ty -> [Offset ty]
- intersperse :: forall ty. PrimType ty => ty -> UArray ty -> UArray ty
- span :: PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty)
- spanEnd :: PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty)
- cons :: PrimType ty => ty -> UArray ty -> UArray ty
- snoc :: PrimType ty => UArray ty -> ty -> UArray ty
- uncons :: PrimType ty => UArray ty -> Maybe (ty, UArray ty)
- unsnoc :: PrimType ty => UArray ty -> Maybe (UArray ty, ty)
- find :: PrimType ty => (ty -> Bool) -> UArray ty -> Maybe ty
- sortBy :: forall ty. PrimType ty => (ty -> ty -> Ordering) -> UArray ty -> UArray ty
- filter :: forall ty. PrimType ty => (ty -> Bool) -> UArray ty -> UArray ty
- reverse :: forall ty. PrimType ty => UArray ty -> UArray ty
- replace :: PrimType ty => UArray ty -> UArray ty -> UArray ty -> UArray ty
- foldr :: PrimType ty => (ty -> a -> a) -> a -> UArray ty -> a
- foldl' :: PrimType ty => (a -> ty -> a) -> a -> UArray ty -> a
- foldr1 :: PrimType ty => (ty -> ty -> ty) -> NonEmpty (UArray ty) -> ty
- foldl1' :: PrimType ty => (ty -> ty -> ty) -> NonEmpty (UArray ty) -> ty
- all :: PrimType ty => (ty -> Bool) -> UArray ty -> Bool
- any :: PrimType ty => (ty -> Bool) -> UArray ty -> Bool
- isPrefixOf :: PrimType ty => UArray ty -> UArray ty -> Bool
- isSuffixOf :: PrimType ty => UArray ty -> UArray ty -> Bool
- foreignMem :: PrimType ty => FinalPtr ty -> CountOf ty -> UArray ty
- fromForeignPtr :: PrimType ty => (ForeignPtr ty, Int, Int) -> UArray ty
- builderAppend :: (PrimType ty, PrimMonad state) => ty -> Builder (UArray ty) (MUArray ty) ty state err ()
- builderBuild :: (PrimType ty, PrimMonad m) => Int -> Builder (UArray ty) (MUArray ty) ty m err () -> m (Either err (UArray ty))
- builderBuild_ :: (PrimType ty, PrimMonad m) => Int -> Builder (UArray ty) (MUArray ty) ty m () () -> m (UArray ty)
- toHexadecimal :: PrimType ty => UArray ty -> UArray Word8
- toBase64Internal :: PrimType ty => Addr# -> UArray ty -> Bool -> UArray Word8
Documentation
An array of type built on top of GHC primitive.
The elements need to have fixed sized and the representation is a packed contiguous array in memory that can easily be passed to foreign interface
Instances
From AsciiString (UArray Word8) Source # | |
Defined in Basement.From | |
From String (UArray Word8) Source # | |
Data ty => Data (UArray ty) Source # | |
Defined in Basement.UArray.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UArray ty -> c (UArray ty) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (UArray ty) # toConstr :: UArray ty -> Constr # dataTypeOf :: UArray ty -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (UArray ty)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (UArray ty)) # gmapT :: (forall b. Data b => b -> b) -> UArray ty -> UArray ty # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UArray ty -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UArray ty -> r # gmapQ :: (forall d. Data d => d -> u) -> UArray ty -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UArray ty -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) # | |
PrimType ty => Monoid (UArray ty) Source # | |
PrimType ty => Semigroup (UArray ty) Source # | |
PrimType ty => IsList (UArray ty) Source # | |
(PrimType ty, Show ty) => Show (UArray ty) Source # | |
NormalForm (UArray ty) Source # | |
Defined in Basement.UArray.Base toNormalForm :: UArray ty -> () Source # | |
(PrimType ty, Eq ty) => Eq (UArray ty) Source # | |
(PrimType ty, Ord ty) => Ord (UArray ty) Source # | |
Defined in Basement.UArray.Base | |
TryFrom (UArray Word8) String Source # | |
PrimType ty => From (Block ty) (UArray ty) Source # | |
PrimType ty => From (Array ty) (UArray ty) Source # | |
PrimType ty => From (UArray ty) (Block ty) Source # | |
PrimType ty => From (UArray ty) (Array ty) Source # | |
(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (UArray ty) (BlockN n ty) Source # | |
(NatWithinBound Int n, PrimType ty) => From (BlockN n ty) (UArray ty) Source # | |
type Item (UArray ty) Source # | |
Defined in Basement.UArray.Base |
class Eq ty => PrimType ty where Source #
Represent the accessor for types that can be stored in the UArray and MUArray.
Types need to be a instance of storable and have fixed sized.
primSizeInBytes :: Proxy ty -> CountOf Word8 Source #
get the size in bytes of a ty element
primShiftToBytes :: Proxy ty -> Int Source #
get the shift size
primBaUIndex :: ByteArray# -> Offset ty -> ty Source #
return the element stored at a specific index
:: PrimMonad prim | |
=> MutableByteArray# (PrimState prim) | mutable array to read from |
-> Offset ty | index of the element to retrieve |
-> prim ty | the element returned |
Read an element at an index in a mutable array
:: PrimMonad prim | |
=> MutableByteArray# (PrimState prim) | mutable array to modify |
-> Offset ty | index of the element to modify |
-> ty | the new value to store |
-> prim () |
Write an element to a specific cell in a mutable array.
primAddrIndex :: Addr# -> Offset ty -> ty Source #
Read from Address, without a state. the value read should be considered a constant for all pratical purpose, otherwise bad thing will happens.
primAddrRead :: PrimMonad prim => Addr# -> Offset ty -> prim ty Source #
Read a value from Addr in a specific primitive monad
primAddrWrite :: PrimMonad prim => Addr# -> Offset ty -> ty -> prim () Source #
Write a value to Addr in a specific primitive monad
Instances
methods
copy :: PrimType ty => UArray ty -> UArray ty Source #
Copy every cells of an existing array to a new array
:: forall prim ty. (PrimMonad prim, PrimType ty) | |
=> MUArray ty (PrimState prim) | destination array |
-> Offset ty | offset at destination |
-> UArray ty | source array |
-> Offset ty | offset at source |
-> CountOf ty | number of elements to copy |
-> prim () |
Copy n
sequential elements from the specified offset in a source array
to the specified position in a destination array.
This function does not check bounds. Accessing invalid memory can return unpredictable and invalid values.
internal methods
recast :: forall a b. (PrimType a, PrimType b) => UArray a -> UArray b Source #
Recast an array of type a to an array of b
a and b need to have the same size otherwise this raise an async exception
unsafeRecast :: (PrimType a, PrimType b) => UArray a -> UArray b Source #
Unsafely recast an UArray containing a
to an UArray containing b
The offset and size are converted from units of a
to units of b
,
but no check are performed to make sure this is compatible.
use recast
if unsure.
freeze :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> prim (UArray ty) Source #
Freeze a MUArray into a UArray by copying all the content is a pristine new buffer
The MUArray in parameter can be still be used after the call without changing the resulting frozen data.
unsafeFreeze :: PrimMonad prim => MUArray ty (PrimState prim) -> prim (UArray ty) Source #
Freeze a mutable array into an array.
the MUArray must not be changed after freezing.
thaw :: (PrimMonad prim, PrimType ty) => UArray ty -> prim (MUArray ty (PrimState prim)) Source #
Thaw an array to a mutable array.
the array is not modified, instead a new mutable array is created and every values is copied, before returning the mutable array.
unsafeThaw :: (PrimType ty, PrimMonad prim) => UArray ty -> prim (MUArray ty (PrimState prim)) Source #
Thaw an immutable array.
The UArray must not be used after thawing.
Creation
vFromListN :: forall ty. PrimType ty => CountOf ty -> [ty] -> UArray ty Source #
Make an array from a list of elements with a size hint.
The list should be of the same size as the hint, as otherwise:
- The length of the list is smaller than the hint: the array allocated is of the size of the hint, but is sliced to only represent the valid bits
- The length of the list is bigger than the hint: The allocated array is the size of the hint, and the list is truncated to fit.
new :: (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MUArray ty (PrimState prim)) Source #
Create a new mutable array of size @n.
When memory for a new array is allocated, we decide if that memory region should be pinned (will not be copied around by GC) or unpinned (can be moved around by GC) depending on its size.
You can change the threshold value used by setting the environment variable
HS_FOUNDATION_UARRAY_UNPINNED_MAX
.
:: forall ty. PrimType ty | |
=> CountOf ty | the size of the array |
-> (Offset ty -> ty) | the function that set the value at the index |
-> UArray ty | the array created |
Create a new array of size n by settings each cells through the
function
f.
:: PrimType ty | |
=> CountOf ty | the size of the array |
-> (Ptr ty -> IO (CountOf ty)) | filling function that |
-> IO (UArray ty) |
Create a pinned array that is filled by a filler
function (typically an IO call like hGetBuf)
createFromPtr :: PrimType ty => Ptr ty -> CountOf ty -> IO (UArray ty) Source #
Freeze a chunk of memory pointed, of specific size into a new unboxed array
:: forall ty prim. (PrimType ty, PrimMonad prim) | |
=> UArray ty | the source array to copy |
-> Ptr ty | The destination address where the copy is going to start |
-> prim () |
Copy all the block content to the memory starting at the destination address
withPtr :: forall ty prim a. (PrimMonad prim, PrimType ty) => UArray ty -> (Ptr ty -> prim a) -> prim a Source #
Get a Ptr pointing to the data in the UArray.
Since a UArray is immutable, this Ptr shouldn't be to use to modify the contents
If the UArray is pinned, then its address is returned as is, however if it's unpinned, a pinned copy of the UArray is made before getting the address.
withMutablePtr :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a Source #
Create a pointer on the beginning of the mutable array
and call a function f
.
The mutable buffer can be mutated by the f
function
and the change will be reflected in the mutable array
If the mutable array is unpinned, a trampoline buffer
is created and the data is only copied when f
return.
unsafeFreezeShrink :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> CountOf ty -> prim (UArray ty) Source #
freezeShrink :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> CountOf ty -> prim (UArray ty) Source #
Just like freeze
but copy only the first n bytes
The size requested need to be smaller or equal to the length of the MUArray, otherwise a Out of Bounds exception is raised
fromBlock :: PrimType ty => Block ty -> UArray ty Source #
Create a UArray from a Block
The block is still used by the uarray
toBlock :: PrimType ty => UArray ty -> Block ty Source #
Create a Block from a UArray.
Note that because of the slice, the destination block is re-allocated and copied, unless the slice point at the whole array
accessors
update :: PrimType ty => UArray ty -> [(Offset ty, ty)] -> UArray ty Source #
update an array by creating a new array with the updates.
the operation copy the previous array, modify it in place, then freeze it.
unsafeIndex :: forall ty. PrimType ty => UArray ty -> Offset ty -> ty Source #
Return the element at a specific index from an array without bounds checking.
Reading from invalid memory can return unpredictable and invalid values.
use index
if unsure.
unsafeIndexer :: (PrimMonad prim, PrimType ty) => UArray ty -> ((Offset ty -> ty) -> prim a) -> prim a Source #
unsafeDewrap :: (Block ty -> Offset ty -> a) -> (Ptr ty -> Offset ty -> ST s a) -> UArray ty -> a Source #
unsafeRead :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> prim ty Source #
read from a cell in a mutable array without bounds checking.
Reading from invalid memory can return unpredictable and invalid values.
use read
if unsure.
unsafeWrite :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> ty -> prim () Source #
write to a cell in a mutable array without bounds checking.
Writing with invalid bounds will corrupt memory and your program will
become unreliable. use write
if unsure.
Functions
index :: PrimType ty => UArray ty -> Offset ty -> ty Source #
Return the element at a specific index from an array.
If the index @n is out of bounds, an error is raised.
take :: CountOf ty -> UArray ty -> UArray ty Source #
Take a count of elements from the array and create an array with just those elements
drop :: CountOf ty -> UArray ty -> UArray ty Source #
Drop a count of elements from the array and return the new array minus those dropped elements
splitAt :: CountOf ty -> UArray ty -> (UArray ty, UArray ty) Source #
Split an array into two, with a count of at most N elements in the first one and the remaining in the other.
revDrop :: CountOf ty -> UArray ty -> UArray ty Source #
Drop the N elements from the end of the array
revTake :: CountOf ty -> UArray ty -> UArray ty Source #
Take the N elements from the end of the array
revSplitAt :: CountOf ty -> UArray ty -> (UArray ty, UArray ty) Source #
Split an array at the N element from the end, and return the last N elements in the first part of the tuple, and whatever first elements remaining in the second
breakEnd :: forall ty. PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #
Similar to break but start the search of the breakpoint from the end
breakEnd (> 0) [1,2,3,0,0,0]
([1,2,3], [0,0,0])
breakLine :: UArray Word8 -> Either Bool (UArray Word8, UArray Word8) Source #
Similar to breakElem specialized to split on linefeed
it either returns: * Left. no line has been found, and whether the last character is a CR * Right, a line has been found with an optional CR, and it returns the array of bytes on the left of the CR/LF, and the the array of bytes on the right of the LF.
replace :: PrimType ty => UArray ty -> UArray ty -> UArray ty -> UArray ty Source #
Replace all the occurrencies of needle
with replacement
in
the haystack
string.
fromForeignPtr :: PrimType ty => (ForeignPtr ty, Int, Int) -> UArray ty Source #
Create a foreign UArray from foreign memory and given offset/size
No check are performed to make sure this is valid, so this is unsafe.
This is particularly useful when dealing with foreign memory and
ByteString
builderAppend :: (PrimType ty, PrimMonad state) => ty -> Builder (UArray ty) (MUArray ty) ty state err () Source #
builderBuild :: (PrimType ty, PrimMonad m) => Int -> Builder (UArray ty) (MUArray ty) ty m err () -> m (Either err (UArray ty)) Source #