| Copyright | (c) Alexey Kuleshevich 2020 |
|---|---|
| License | BSD3 |
| Maintainer | Alexey Kuleshevich <alexey@kuleshevi.ch> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Prim.Array
Description
Synopsis
- newtype Size = Size {}
- data BArray e = BArray (Array# e)
- isSameBArray :: BArray a -> BArray a -> Bool
- sizeOfBArray :: forall e. BArray e -> Size
- indexBArray :: forall e. BArray e -> Int -> e
- copyBArray :: forall e m s. MonadPrim s m => BArray e -> Int -> BMArray e s -> Int -> Size -> m ()
- cloneBArray :: forall e. BArray e -> Int -> Size -> BArray e
- thawBArray :: forall e m s. MonadPrim s m => BArray e -> m (BMArray e s)
- thawCopyBArray :: forall e m s. MonadPrim s m => BArray e -> Int -> Size -> m (BMArray e s)
- toListBArray :: forall e. BArray e -> [e]
- fromListBArray :: forall e. [e] -> BArray e
- fromListBArrayN :: forall e. HasCallStack => Size -> [e] -> BArray e
- fromBaseBArray :: Array ix e -> BArray e
- toBaseBArray :: BArray e -> Array Int e
- data BMArray e s = BMArray (MutableArray# s e)
- getSizeOfBMArray :: forall e m s. MonadPrim s m => BMArray e s -> m Size
- readBMArray :: forall e m s. MonadPrim s m => BMArray e s -> Int -> m e
- writeBMArray :: forall e m s. MonadPrim s m => BMArray e s -> Int -> e -> m ()
- writeLazyBMArray :: forall e m s. MonadPrim s m => BMArray e s -> Int -> e -> m ()
- writeDeepBMArray :: forall e m s. (MonadPrim s m, NFData e) => BMArray e s -> Int -> e -> m ()
- isSameBMArray :: forall a s. BMArray a s -> BMArray a s -> Bool
- newBMArray :: forall e m s. MonadPrim s m => Size -> e -> m (BMArray e s)
- newLazyBMArray :: forall e m s. MonadPrim s m => Size -> e -> m (BMArray e s)
- newRawBMArray :: forall e m s. (HasCallStack, MonadPrim s m) => Size -> m (BMArray e s)
- makeBMArray :: forall e m s. MonadPrim s m => Size -> (Int -> m e) -> m (BMArray e s)
- moveBMArray :: forall e m s. MonadPrim s m => BMArray e s -> Int -> BMArray e s -> Int -> Size -> m ()
- cloneBMArray :: forall e m s. MonadPrim s m => BMArray e s -> Int -> Size -> m (BMArray e s)
- shrinkBMArray :: forall e m s. MonadPrim s m => BMArray e s -> Size -> m ()
- resizeBMArray :: forall e m s. MonadPrim s m => BMArray e s -> Size -> e -> m (BMArray e s)
- resizeRawBMArray :: forall e m s. MonadPrim s m => BMArray e s -> Size -> m (BMArray e s)
- freezeBMArray :: forall e m s. MonadPrim s m => BMArray e s -> m (BArray e)
- freezeCopyBMArray :: forall e m s. MonadPrim s m => BMArray e s -> Int -> Size -> m (BArray e)
- data SBArray e = SBArray (SmallArray# e)
- isSameSBArray :: SBArray a -> SBArray a -> Bool
- sizeOfSBArray :: forall e. SBArray e -> Size
- indexSBArray :: forall e. SBArray e -> Int -> e
- copySBArray :: forall e m s. MonadPrim s m => SBArray e -> Int -> SBMArray e s -> Int -> Size -> m ()
- cloneSBArray :: forall e. SBArray e -> Int -> Size -> SBArray e
- thawSBArray :: forall e m s. MonadPrim s m => SBArray e -> m (SBMArray e s)
- thawCopySBArray :: forall e m s. MonadPrim s m => SBArray e -> Int -> Size -> m (SBMArray e s)
- toListSBArray :: forall e. SBArray e -> [e]
- fromListSBArray :: forall e. [e] -> SBArray e
- fromListSBArrayN :: forall e. HasCallStack => Size -> [e] -> SBArray e
- data SBMArray e s = SBMArray (SmallMutableArray# s e)
- isSameSBMArray :: forall a s. SBMArray a s -> SBMArray a s -> Bool
- getSizeOfSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> m Size
- readSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> Int -> m e
- writeSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> Int -> e -> m ()
- writeLazySBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> Int -> e -> m ()
- writeDeepSBMArray :: forall e m s. (MonadPrim s m, NFData e) => SBMArray e s -> Int -> e -> m ()
- newSBMArray :: forall e m s. MonadPrim s m => Size -> e -> m (SBMArray e s)
- newLazySBMArray :: forall e m s. MonadPrim s m => Size -> e -> m (SBMArray e s)
- newRawSBMArray :: forall e m s. (HasCallStack, MonadPrim s m) => Size -> m (SBMArray e s)
- makeSBMArray :: forall e m s. MonadPrim s m => Size -> (Int -> m e) -> m (SBMArray e s)
- moveSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> Int -> SBMArray e s -> Int -> Size -> m ()
- cloneSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> Int -> Size -> m (SBMArray e s)
- shrinkSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> Size -> m ()
- resizeSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> Size -> e -> m (SBMArray e s)
- resizeRawSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> Size -> m (SBMArray e s)
- freezeSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> m (SBArray e)
- freezeCopySBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> Int -> Size -> m (SBArray e)
- data UArray e = UArray ByteArray#
- isSameUArray :: forall a b. UArray a -> UArray b -> Bool
- isPinnedUArray :: forall e. UArray e -> Bool
- sizeOfUArray :: forall e. Prim e => UArray e -> Size
- indexUArray :: forall e. Prim e => UArray e -> Int -> e
- copyUArray :: forall e m s. (Prim e, MonadPrim s m) => UArray e -> Int -> UMArray e s -> Int -> Size -> m ()
- thawUArray :: forall e m s. MonadPrim s m => UArray e -> m (UMArray e s)
- toListUArray :: forall e. Prim e => UArray e -> [e]
- fromListUArray :: forall e. Prim e => [e] -> UArray e
- fromListUArrayN :: forall e. Prim e => Size -> [e] -> UArray e
- fromBaseUArray :: (Prim e, IArray UArray e) => UArray ix e -> UArray e
- toBaseUArray :: (Prim e, IArray UArray e) => UArray e -> UArray Int e
- data UMArray e s = UMArray (MutableByteArray# s)
- isSameUMArray :: forall a b s. UMArray a s -> UMArray b s -> Bool
- isPinnedUMArray :: forall e s. UMArray e s -> Bool
- getSizeOfUMArray :: forall e m s. (Prim e, MonadPrim s m) => UMArray e s -> m Size
- readUMArray :: forall e m s. (Prim e, MonadPrim s m) => UMArray e s -> Int -> m e
- writeUMArray :: forall e m s. (Prim e, MonadPrim s m) => UMArray e s -> Int -> e -> m ()
- newUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> e -> m (UMArray e s)
- newRawUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> m (UMArray e s)
- makeUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> (Int -> m e) -> m (UMArray e s)
- newPinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> e -> m (UMArray e s)
- newRawPinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> m (UMArray e s)
- makePinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> (Int -> m e) -> m (UMArray e s)
- newAlignedPinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> e -> m (UMArray e s)
- newRawAlignedPinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> m (UMArray e s)
- makeAlignedPinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> (Int -> m e) -> m (UMArray e s)
- moveUMArray :: forall e m s. (Prim e, MonadPrim s m) => UMArray e s -> Int -> UMArray e s -> Int -> Size -> m ()
- setUMArray :: forall e m s. (Prim e, MonadPrim s m) => UMArray e s -> Int -> Size -> e -> m ()
- shrinkUMArray :: forall e m s. (MonadPrim s m, Prim e) => UMArray e s -> Size -> m ()
- resizeUMArray :: forall e m s. (MonadPrim s m, Prim e) => UMArray e s -> Size -> m (UMArray e s)
- freezeUMArray :: forall e m s. MonadPrim s m => UMArray e s -> m (UArray e)
- uninitialized :: HasCallStack => String -> String -> a
- makeMutWith :: Monad m => (Size -> m b) -> (b -> Int -> a -> m ()) -> Size -> (Int -> m a) -> m b
- fromListMutWith :: Monad m => (Size -> m b) -> (b -> Int -> a -> m ()) -> Size -> [a] -> m b
- foldrWithFB :: (a e -> Size) -> (a e -> Int -> e) -> (e -> b -> b) -> b -> a e -> b
- eqWith :: Eq e => (a e -> a e -> Bool) -> (a e -> Size) -> (a e -> Int -> e) -> a e -> a e -> Bool
- compareWith :: Ord e => (a e -> a e -> Bool) -> (a e -> Size) -> (a e -> Int -> e) -> a e -> a e -> Ordering
- appendWith :: (forall s. Size -> ST s (ma e s)) -> (forall s. a e -> Int -> ma e s -> Int -> Size -> ST s ()) -> (forall s. ma e s -> ST s (a e)) -> (a e -> Size) -> a e -> a e -> a e
- concatWith :: (forall s. Size -> ST s (ma e s)) -> (forall s. a e -> Int -> ma e s -> Int -> Size -> ST s ()) -> (forall s. ma e s -> ST s (a e)) -> (a e -> Size) -> [a e] -> a e
Documentation
Minimal interface, wrappers around primops
Indexing and Size type
As in the rest of the library majority of the functions are unsafe.
no fusion
Boxed vs unboxed concept
Mutable vs Immutable
Note more features in primal-memory and primal-mutable
Instances
Boxed Array
A boxed array is essentially a contiguous chunk of memory that holds
pointers to actual elements that are being stored somewhere else on the heap. Therefore
it is more efficient to use UArray if the element being stored has a Prim instance
or can have created for it, because this avoids an extra level of indirection. However
this is not always possible and for this reason we have boxed arrays.
Immutable
Immutable array with boxed elements.
Since: 0.3.0
Instances
| Functor BArray Source # | Since: 0.3.0 |
| Foldable BArray Source # | Since: 0.3.0 |
Defined in Data.Prim.Array Methods fold :: Monoid m => BArray m -> m # foldMap :: Monoid m => (a -> m) -> BArray a -> m # foldMap' :: Monoid m => (a -> m) -> BArray a -> m # foldr :: (a -> b -> b) -> b -> BArray a -> b # foldr' :: (a -> b -> b) -> b -> BArray a -> b # foldl :: (b -> a -> b) -> b -> BArray a -> b # foldl' :: (b -> a -> b) -> b -> BArray a -> b # foldr1 :: (a -> a -> a) -> BArray a -> a # foldl1 :: (a -> a -> a) -> BArray a -> a # elem :: Eq a => a -> BArray a -> Bool # maximum :: Ord a => BArray a -> a # minimum :: Ord a => BArray a -> a # | |
| Eq1 BArray Source # | |
| Ord1 BArray Source # | |
Defined in Data.Prim.Array | |
| Show1 BArray Source # | |
| IsList (BArray e) Source # | |
| Eq e => Eq (BArray e) Source # | |
| Ord e => Ord (BArray e) Source # | |
Defined in Data.Prim.Array | |
| Show e => Show (BArray e) Source # | |
| e ~ Char => IsString (BArray e) Source # | |
Defined in Data.Prim.Array Methods fromString :: String -> BArray e # | |
| Semigroup (BArray e) Source # | |
| Monoid (BArray e) Source # | |
| NFData e => NFData (BArray e) Source # | |
Defined in Data.Prim.Array | |
| type Item (BArray e) Source # | |
Defined in Data.Prim.Array | |
isSameBArray :: BArray a -> BArray a -> Bool Source #
Compare pointers for two immutable arrays and see if they refer to the exact same one.
Since: 0.3.0
sizeOfBArray :: forall e. BArray e -> Size Source #
O(1) - Get the number of elements in an immutable array
Documentation for utilized primop: sizeofArray#.
Since: 0.3.0
Arguments
| :: forall e. BArray e | array - Array where to lookup an element from |
| -> Int | ix - Position of the element within the Precoditions: 0 <= ix ix < unSize (sizeOfBArray array) |
| -> e |
O(1) - Index an element in the immutable boxed array.
Documentation for utilized primop: indexArray#.
- Unsafe
- Bounds are not checked. When a precondition for
ixargument is violated the result is either unpredictable output or failure with a segfault.
Examples
>>>import Data.Prim.Array>>>let a = fromListBArray [[0 .. i] | i <- [0 .. 10 :: Int]]>>>indexBArray a 1[0,1]>>>indexBArray a 5[0,1,2,3,4,5]
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BArray e | srcArray - Source immutable array Precondition: srcMutArray <- thawBArray srcArray srcMutArray /= dstMutArray |
| -> Int | srcStartIx - Offset into the source immutable array where copy should start from Preconditions: 0 <= srcStartIx srcStartIx < unSize (sizeOfBArray srcArray) |
| -> BMArray e s | dstMutArray - Destination mutable array |
| -> Int | dstStartIx - Offset into the destination mutable array where the copy should start at Preconditions: 0 <= dstStartIx dstSize <- getSizeOfBMArray dstMutArray dstStartIx < unSize dstSize |
| -> Size | sz - Number of elements to copy over Preconditions: 0 <= sz srcStartIx + unSize sz < unSize (sizeOfBArray srcArray) dstSize <- getSizeOfBMArray dstMutArray dstStartIx + unSize sz < unSize dstSize |
| -> m () |
O(sz) - Copy a subsection of an immutable array into a subsection of a mutable array. Source and destination arrays must not be the same array in different states.
Documentation for utilized primop: copyArray#.
- Unsafe
- When any of the preconditions for
srcStartIx,dstStartIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault.
Since: 0.3.0
Arguments
| :: forall e. BArray e | srcArray - Immutable source array |
| -> Int | startIx - Location within Preconditions: 0 <= startIx startIx < unSize (sizeOfBArray srcArray) |
| -> Size | sz - Size of the returned immutable array. Also this is the number of elements that will be copied over into the destionation array starting at the beginning. Preconditions: 0 <= sz startIx + unSize sz < unSize (sizeOfBArray srcArray) Should be less then the actual available memory |
| -> BArray e |
O(sz) - Make an exact copy of a subsection of a pure immutable array.
- Unsafe
- When any of the preconditions for
startIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault. Failure with out of memory is also possibility when the @sz is too large.
Documentation for utilized primop: cloneArray#.
Examples
>>>let a = fromListBArray ['a'..'z']>>>aBArray "abcdefghijklmnopqrstuvwxyz">>>cloneBArray a 23 3BArray "xyz"
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BArray e | array - Source immutable array that will be thawed |
| -> m (BMArray e s) |
O(1) - Convert a pure immutable boxed array into a mutable boxed array. Use
freezeBMArray in order to go in the opposite direction.
Documentation for utilized primop: unsafeThawArray#.
- Unsafe
- This function makes it possible to break referential transparency, because any
subsequent destructive operation to the mutable boxed array will also be reflected in
the source immutable array as well. See
thawCopyBArraythat avoids this problem with a fresh allocation and data copy.
Examples
>>>ma <- thawBArray $ fromListBArray [1 .. 5 :: Integer]>>>writeBMArray ma 1 10>>>freezeBMArray maBArray [1,10,3,4,5]
Be careful not to retain a reference to the pure immutable source array after the thawed version gets mutated.
>>>let a = fromListBArray [1 .. 5 :: Integer]>>>ma' <- thawBArray a>>>writeBMArray ma' 0 100000>>>aBArray [100000,2,3,4,5]
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BArray e | srcArray - Immutable source array |
| -> Int | startIx - Location within Preconditions: 0 <= startIx startIx < unSize (sizeOfBArray srcArray) |
| -> Size | sz - Size of the returned mutable array. Also this is the number of elements that will be copied over into the destionation array starting at the beginning. Preconditions: 0 <= sz startIx + unSize sz < unSize (sizeOfBArray srcArray) Should be less then the actual available memory |
| -> m (BMArray e s) | dstMutArray - Newly created destination mutable boxed array |
O(sz) - Create a new mutable array with size sz and copy that number of elements
from source immutable srcArray starting at an offset startIx into the newly created
dstMutArray. This function can help avoid an issue with referential transparency that
is inherent to thawBArray.
- Unsafe
- When any of the preconditions for
startIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault. Failure with out of memory is also a possibility when the @sz is too large.
Documentation for utilized primop: thawArray#.
Examples
>>>let a = fromListBArray [1 .. 5 :: Int]>>>ma <- thawCopyBArray a 1 3>>>writeBMArray ma 1 10>>>freezeBMArray maBArray [2,10,4]>>>aBArray [1,2,3,4,5]
Since: 0.3.0
toListBArray :: forall e. BArray e -> [e] Source #
Convert a pure boxed array into a list. It should work fine with GHC built-in list fusion.
Since: 0.1.0
fromListBArray :: forall e. [e] -> BArray e Source #
O(length list) - Convert a list into an immutable boxed array. It is more efficient to use
fromListBArrayN when the number of elements is known ahead of time. The reason for this
is that it is necessary to iterate the whole list twice: once to count how many elements
there is in order to create large enough array that can fit them; and the second time to
load the actual elements. Naturally, infinite lists will grind the program to a halt.
Example
>>>fromListBArray "Hello Haskell"BArray "Hello Haskell"
Since: 0.3.0
Arguments
| :: forall e. HasCallStack | |
| => Size | sz - Expected number of elements in the |
| -> [e] | list - A list to bew loaded into the array |
| -> BArray e |
O(min(length list, sz)) - Same as fromListBArray, except that it will allocate an
array exactly of n size, as such it will not convert any portion of the list that
doesn't fit into the newly created array.
- Partial
- When length of supplied list is in fact smaller then the expected size
sz, thunks withUndefinedElementexception throwing function will be placed in the tail portion of the array. - Unsafe
- When a precondition
szis violated this function can result in critical failure with out of memory orHeapOverflowasync exception.
Examples
>>>fromListBArrayN 3 [1 :: Int, 2, 3]BArray [1,2,3]>>>fromListBArrayN 3 [1 :: Int ..]BArray [1,2,3]
Since: 0.1.0
fromBaseBArray :: Array ix e -> BArray e Source #
O(1) - cast a boxed immutable Array that is wired with GHC to BArray from primal.
>>>import Data.Array.IArray as IA>>>let arr = IA.listArray (10, 15) [30 .. 35] :: IA.Array Int Integer>>>arrarray (10,15) [(10,30),(11,31),(12,32),(13,33),(14,34),(15,35)]>>>fromBaseBArray arrBArray [30,31,32,33,34,35]
Since: 0.3.0
Mutable
Mutable array with boxed elements.
Since: 0.3.0
Constructors
| BMArray (MutableArray# s e) |
getSizeOfBMArray :: forall e m s. MonadPrim s m => BMArray e s -> m Size Source #
O(1) - Get the size of a mutable boxed array
Documentation for utilized primop: sizeofMutableArray#.
Example
>>>ma <- newBMArray 1024 "Element of each cell">>>getSizeOfBMArray maSize {unSize = 1024}
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BMArray e s | srcMutArray - Array to read an element from |
| -> Int | ix - Index that refers to an element we need within the the Precoditions: 0 <= ix ix < unSize (sizeOfMBArray srcMutArray) |
| -> m e |
O(1) - Read an element from a mutable boxed array at the supplied index.
Documentation for utilized primop: readArray#.
- Unsafe
- Violation of
ixpreconditions can result in undefined behavior or a failure with a segfault
Example
>>>ma <- makeBMArray 10 (pure . ("Element ix: " ++) . show)>>>readBMArray ma 5"Element ix: 5"
Since: 0.1.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BMArray e s | dstMutArray - An array to have the element written to |
| -> Int | ix - Index within the the Precoditions: 0 <= ix ix < unSize (sizeOfMBArray srcArray) |
| -> e | elt - Element to be written into |
| -> m () |
O(1) - Write an element elt into the mutable boxed array dstMutArray at the
supplied index ix. The actual element will be evaluated to WHNF prior to mutation.
- Unsafe
- Violation of
ixpreconditions can result in heap corruption or a failure with a segfault
Examples
>>>ma <- newBMArray 4 (Nothing :: Maybe Integer)>>>writeBMArray ma 2 (Just 2)>>>freezeBMArray maBArray [Nothing,Nothing,Just 2,Nothing]
It is important to note that an element is evaluated prior to being written into a cell, so it will not overwrite the value of an array's cell if it evaluates to an exception:
>>>import Control.Prim.Exception>>>writeBMArray ma 2 (impureThrow DivideByZero)*** Exception: divide by zero>>>freezeBMArray maBArray [Nothing,Nothing,Just 2,Nothing]
However, it is evaluated only to Weak Head Normal Form (WHNF), so it is still possible to write something that eventually evaluates to bottom.
>>>writeBMArray ma 3 (Just (7 `div` 0 ))>>>freezeBMArray maBArray [Nothing,Nothing,Just 2,Just *** Exception: divide by zero>>>readBMArray ma 3Just *** Exception: divide by zero
Either deepseq or writeDeepBMArray can be used to alleviate that.
Since: 0.3.0
writeLazyBMArray :: forall e m s. MonadPrim s m => BMArray e s -> Int -> e -> m () Source #
O(1) - Same as writeBMArray but allows to write a thunk into an array instead of an
evaluated element. Careful with memory leaks and thunks that evaluate to exceptions.
Documentation for utilized primop: writeArray#.
- Unsafe
- Same reasons as
writeBMArray
Since: 0.3.0
writeDeepBMArray :: forall e m s. (MonadPrim s m, NFData e) => BMArray e s -> Int -> e -> m () Source #
O(1) - Same as writeBMArray, except it ensures that the value being written is
fully evaluated, i.e. to Normal Form (NF).
- Unsafe
- Same reasons as
writeBMArray
Since: 0.3.0
isSameBMArray :: forall a s. BMArray a s -> BMArray a s -> Bool Source #
Compare pointers for two mutable arrays and see if they refer to the exact same one.
Documentation for utilized primop: sameMutableArray#.
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => Size | sz - Size of the array Preconditions: 0 <= sz Should be below some upper limit that is dictated by the operating system and the total amount of available memory |
| -> e | elt - Value to use for all array cells |
| -> m (BMArray e s) |
Create a mutable boxed array where each element is set to the supplied initial value
elt, which is evaluated before array allocation happens. See newLazyBMArray for
an ability to initialize with a thunk.
- Unsafe size
- Violation of precondition for the
szargument can result in the current thread being killed withHeapOverflowasynchronous exception or death of the whole process with some unchecked exception from RTS.
Examples
>>>newBMArray 10 'A' >>= freezeBMArrayBArray "AAAAAAAAAA"
Since: 0.3.0
newLazyBMArray :: forall e m s. MonadPrim s m => Size -> e -> m (BMArray e s) Source #
Same as newBMArray, except initial element is allowed to be a thunk.
Documentation for utilized primop: newArray#.
- Unsafe
- Same reasons as
newBMArray
Since: 0.3.0
newRawBMArray :: forall e m s. (HasCallStack, MonadPrim s m) => Size -> m (BMArray e s) Source #
Create new mutable array, where each element is initilized to a thunk that throws an
error when evaluated. This is useful when there is a plan to later iterate over the whole
array and write values into each cell in some index aware fashion. Consider makeBMArray
as an alternative.
- Partial
- All array cells are initialized with thunks that throw
UndefinedElementexception when evaluated - Unsafe
- Same reasons as
newBMArray
Examples
>>>import Data.Prim>>>let xs = "Hello Haskell">>>ma <- newRawBMArray (Size (length xs)) :: IO (BMArray Char RW)>>>mapM_ (\(i, x) -> writeBMArray ma i x) (zip [0..] xs)>>>freezeBMArray maBArray "Hello Haskell"
Since: 0.3.0
makeBMArray :: forall e m s. MonadPrim s m => Size -> (Int -> m e) -> m (BMArray e s) Source #
Create new mutable boxed array of the supplied size and fill it with a monadic action that is applied to indices of each array cell.
- Unsafe
- Same reasons as
newBMArray
Examples
>>>ma <- makeBMArray 5 $ \i -> (toEnum (i + 97) :: Char) <$ putStrLn ("Handling index: " ++ show i)Handling index: 0 Handling index: 1 Handling index: 2 Handling index: 3 Handling index: 4>>>freezeBMArray maBArray "abcde"
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BMArray e s | srcMutArray - Source mutable array |
| -> Int | srcStartIx - Offset into the source mutable array where copy should start from Preconditions: 0 <= srcStartIx srcSize <- getSizeOfBMArray srcMutArray srcStartIx < unSize srcSize |
| -> BMArray e s | dstMutArray - Destination mutable array |
| -> Int | dstStartIx - Offset into the destination mutable array where copy should start to Preconditions: 0 <= dstStartIx dstSize <- getSizeOfBMArray dstMutArray dstStartIx < unSize dstSize |
| -> Size | sz - Number of elements to copy over Preconditions: 0 <= sz srcSize <- getSizeOfBMArray srcMutArray srcStartIx + unSize sz < unSize srcSize dstSize <- getSizeOfBMArray dstMutArray dstStartIx + unSize sz < unSize dstSize |
| -> m () |
O(sz) - Copy a subsection of a mutable array into a subsection of another or the same
mutable array. Therefore, unlike copyBArray, memory ia allowed to overlap between source
and destination.
Documentation for utilized primop: copyMutableArray#.
- Unsafe
- When any of the preconditions for
srcStartIx,dstStartIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault.
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BMArray e s | srcArray - Source mutable array |
| -> Int | startIx - Location within Preconditions: 0 <= startIx startIx < unSize (sizeOfBArray srcArray) |
| -> Size | sz - Size of the returned mutable array. Also this is the number of elements that will be copied over into the destionation array starting at the beginning. Preconditions: 0 <= sz startIx + unSize sz < unSize (sizeOfBArray srcArray) Should be less then actual available memory |
| -> m (BMArray e s) |
O(sz) - Allocate a new mutable array of size sz and copy that number of the
elements over from the srcArray starting at index ix. Similar to cloneBArray,
except it works on mutable arrays.
Documentation for utilized primop: cloneMutableArray#.
- Unsafe
- When any of the preconditions for
startIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault. Failure with out of memory is also a possibility when the @sz is too large.
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BMArray e s | mutArray - Mutable unboxed array to be shrunk |
| -> Size | sz - New size for the array in number of elements Preconditions: 0 <= sz curSize <- getSizeOfBMArray mutArray sz <= curSize |
| -> m () |
O(1) - Reduce the size of a mutable boxed array.
Documentation for utilized primop: shrinkMutableArray#.
- Unsafe
- - Violation of preconditions for
szleads to undefined behavior
- 3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BMArray e s | srcMutArray - Mutable boxed array to be shrunk |
| -> Size | sz - New size for the array in number of elements Preconditions: 0 <= sz Should be below some upper limit that is dictated by the operating system and the total amount of available memory |
| -> e | elt - Element to write into extra space at the end when growing the array. |
| -> m (BMArray e s) | dstMutArray - produces a resized version of srcMutArray. |
O(1) - Either grow or shrink the size of a mutable unboxed array. Shrinking happens
in-place without new array creation and data copy, while growing the array is
implemented with creating new array and copy of the data over from the source array
srcMutArray. This has a consequence that produced array dstMutArray might refer to
the same srcMutArray or to a totally new array, which can be checked with
isSameBMArray.
Documentation on the utilized primop: resizeMutableArray#.
- Unsafe
- - Same reasons as in
newRawBMArray.
- 3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BMArray e s | srcMutArray - Mutable boxed array to be shrunk |
| -> Size | sz - New size for the array in number of elements Preconditions: 0 <= sz Should be below some upper limit that is dictated by the operating system and the total amount of available memory |
| -> m (BMArray e s) | dstMutArray - produces a resized version of srcMutArray. |
O(1) - Same as resizeBMArray, except when growing the array empty space at the
end is filled with bottom.
- Partial
- - When size
szis larger then the size ofsrcMutArraythendstMutArraywill have cells at the end initialized with thunks that throwUndefinedElementexception. - Unsafe
- - Same reasons as in
newBMArray.
- 3.0
freezeBMArray :: forall e m s. MonadPrim s m => BMArray e s -> m (BArray e) Source #
O(1) - Convert a mutable boxed array into an immutable one. Use thawBArray in order
to go in the opposite direction.
Documentation for utilized primop: unsafeFreezeArray#.
- Unsafe
- This function makes it possible to break referential transparency, because any
subsequent destructive operation to the source mutable boxed array will also be reflected
in the resulting immutable array. See
freezeCopyBMArraythat avoids this problem with fresh allocation.
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => BMArray e s | srcArray - Source mutable array |
| -> Int | startIx - Location within Preconditions: 0 <= startIx startIx < unSize (sizeOfBArray srcArray) |
| -> Size | sz - Size of the returned immutable array. Also this is the number of elements that will be copied over into the destionation array starting at the beginning. Preconditions: 0 <= sz startIx + unSize sz < unSize (sizeOfBArray srcArray) Should be less then actual available memory |
| -> m (BArray e) |
O(sz) - Similar to freezeBMArray, except it creates a new array with the copy of a
subsection of a mutable array before converting it into an immutable.
Documentation for utilized primop: freezeArray#.
- Unsafe
- When any of the preconditions for
startIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault or out of memory exception.
Since: 0.3.0
Small Boxed Array
Immutable
Small boxed immutable array
Constructors
| SBArray (SmallArray# e) |
Instances
isSameSBArray :: SBArray a -> SBArray a -> Bool Source #
Compare pointers for two immutable arrays and see if they refer to the exact same one.
Since: 0.3.0
sizeOfSBArray :: forall e. SBArray e -> Size Source #
O(1) - Get the number of elements in an immutable array
Documentation for utilized primop: sizeofSmallArray#.
Since: 0.3.0
Arguments
| :: forall e. SBArray e | array - Array where to lookup an element from |
| -> Int | ix - Position of the element within the Precoditions: 0 <= ix ix < unSize (sizeOfSBArray array) |
| -> e |
O(1) - Index an element in the immutable small boxed array.
Documentation for utilized primop: indexSmallArray#.
- Unsafe
- Bounds are not checked. When a precondition for
ixargument is violated the result is either unpredictable output or failure with a segfault.
Examples
>>>import Data.Prim.Array>>>let a = fromListSBArray [[0 .. i] | i <- [0 .. 10 :: Int]]>>>indexSBArray a 1[0,1]>>>indexSBArray a 5[0,1,2,3,4,5]
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBArray e | srcArray - Source immutable array Precondition: srcMutArray <- thawSBArray srcArray srcMutArray /= dstMutArray |
| -> Int | srcStartIx - Offset into the source immutable array where copy should start from Preconditions: 0 <= srcStartIx srcStartIx < unSize (sizeOfSBArray srcArray) |
| -> SBMArray e s | dstMutArray - Destination mutable array |
| -> Int | dstStartIx - Offset into the destination mutable array where the copy should start at Preconditions: 0 <= dstStartIx dstSize <- getSizeOfSBMArray dstMutArray dstStartIx < unSize dstSize |
| -> Size | sz - Number of elements to copy over Preconditions: 0 <= sz srcStartIx + unSize sz < unSize (sizeOfSBArray srcArray) dstSize <- getSizeOfSBMArray dstMutArray dstStartIx + unSize sz < unSize dstSize |
| -> m () |
O(sz) - Copy a subsection of an immutable array into a subsection of a mutable array. Source and destination arrays must not be the same array in different states.
Documentation for utilized primop: copySmallArray#.
- Unsafe
- When any of the preconditions for
srcStartIx,dstStartIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault.
Since: 0.3.0
Arguments
| :: forall e. SBArray e | srcArray - Immutable source array |
| -> Int | startIx - Location within Preconditions: 0 <= startIx startIx < unSize (sizeOfSBArray srcArray) |
| -> Size | sz - Size of the returned immutable array. Also this is the number of elements that will be copied over into the destionation array starting at the beginning. Preconditions: 0 <= sz startIx + unSize sz < unSize (sizeOfSBArray srcArray) Should be less then the actual available memory |
| -> SBArray e |
O(sz) - Make an exact copy of a subsection of a pure immutable array.
- Unsafe
- When any of the preconditions for
startIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault. Failure with out of memory is also a possibility when the @sz is too large.
Documentation for utilized primop: cloneSmallArray#.
Examples
>>>let a = fromListSBArray ['a'..'z']>>>aSBArray "abcdefghijklmnopqrstuvwxyz">>>cloneSBArray a 23 3SBArray "xyz"
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBArray e | array - Source immutable array that will be thawed |
| -> m (SBMArray e s) |
O(1) - Convert a pure immutable boxed array into a mutable boxed array. Use
freezeSBMArray in order to go in the opposite direction.
Documentation for utilized primop: unsafeThawSmallArray#.
- Unsafe
- This function makes it possible to break referential transparency, because any
subsequent destructive operation to the mutable boxed array will also be reflected in
the source immutable array as well. See
thawCopySBArraythat avoids this problem with a fresh allocation and data copy.
Examples
>>>ma <- thawSBArray $ fromListSBArray [1 .. 5 :: Integer]>>>writeSBMArray ma 1 10>>>freezeSBMArray maSBArray [1,10,3,4,5]
Be careful not to retain a reference to the pure immutable source array after the thawed version gets mutated.
>>>let a = fromListSBArray [1 .. 5 :: Integer]>>>ma' <- thawSBArray a>>>writeSBMArray ma' 0 100000>>>aSBArray [100000,2,3,4,5]
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBArray e | srcArray - Immutable source array |
| -> Int | startIx - Location within Preconditions: 0 <= startIx startIx < unSize (sizeOfSBArray srcArray) |
| -> Size | sz - Size of the returned mutable array. Also this is the number of elements that will be copied over into the destionation array starting at the beginning. Preconditions: 0 <= sz startIx + unSize sz < unSize (sizeOfSBArray srcArray) Should be less then the actual available memory |
| -> m (SBMArray e s) | dstMutArray - Newly created destination mutable boxed array |
O(sz) - Create a new mutable array with size sz and copy that number of elements
from source immutable srcArray starting at an offset startIx into the newly created
dstMutArray. This function can help avoid an issue with referential transparency that
is inherent to thawSBArray.
- Unsafe
- When any of the preconditions for
startIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault. Failure with out of memory is also a possibility when the @sz is too large.
Documentation for utilized primop: thawSmallArray#.
Examples
>>>let a = fromListSBArray [1 .. 5 :: Int]>>>ma <- thawCopySBArray a 1 3>>>writeSBMArray ma 1 10>>>freezeSBMArray maSBArray [2,10,4]>>>aSBArray [1,2,3,4,5]
Since: 0.3.0
toListSBArray :: forall e. SBArray e -> [e] Source #
Convert a pure boxed array into a list. It should work fine with GHC built-in list fusion.
Since: 0.1.0
fromListSBArray :: forall e. [e] -> SBArray e Source #
O(length list) - Convert a list into an immutable boxed array. It is more efficient to use
fromListSBArrayN when the number of elements is known ahead of time. The reason for this
is that it is necessary to iterate the whole list twice: once to count how many elements
there is in order to create large enough array that can fit them; and the second time to
load the actual elements. Naturally, infinite lists will grind the program to a halt.
Example
>>>fromListSBArray "Hello Haskell"SBArray "Hello Haskell"
Since: 0.3.0
Arguments
| :: forall e. HasCallStack | |
| => Size | sz - Expected number of elements in the |
| -> [e] | list - A list to bew loaded into the array |
| -> SBArray e |
O(min(length list, sz)) - Same as fromListSBArray, except that it will allocate
an array exactly of n size, as such it will not convert any portion of the list that
doesn't fit into the newly created array.
- Partial
- When length of supplied list is in fact smaller then the expected size
sz, thunks withUndefinedElementexception throwing function will be placed in the tail portion of the array. - Unsafe
- When a precondition
szis violated this function can result in critical failure with out of memory orHeapOverflowasync exception.
Examples
>>>fromListSBArrayN 3 [1 :: Int, 2, 3]SBArray [1,2,3]>>>fromListSBArrayN 3 [1 :: Int ..]SBArray [1,2,3]
Since: 0.1.0
Mutable
Small boxed mutable array
Constructors
| SBMArray (SmallMutableArray# s e) |
isSameSBMArray :: forall a s. SBMArray a s -> SBMArray a s -> Bool Source #
Compare pointers for two mutable arrays and see if they refer to the exact same one.
Documentation for utilized primop: sameSmallMutableArray#.
Since: 0.3.0
getSizeOfSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> m Size Source #
O(1) - Get the size of a mutable boxed array
Documentation for utilized primop: getSizeofSmallMutableArray# for ghc-8.10 and newer
and fallback to sizeofMutableArray# for older versions.
Example
>>>ma <- newSBMArray 1024 "Element of each cell">>>getSizeOfSBMArray maSize {unSize = 1024}
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBMArray e s | srcMutArray - Array to read an element from |
| -> Int | ix - Index that refers to an element we need within the the Precoditions: 0 <= ix ix < unSize (sizeOfMSBArray srcMutArray) |
| -> m e |
O(1) - Read an element from a mutable small boxed array at the supplied index.
Documentation for utilized primop: readSmallArray#.
- Unsafe
- Violation of
ixpreconditions can result in undefined behavior or a failure with a segfault
Example
>>>ma <- makeSBMArray 10 (pure . ("Element ix: " ++) . show)>>>readSBMArray ma 5"Element ix: 5"
Since: 0.1.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBMArray e s | dstMutArray - An array to have the element written to |
| -> Int | ix - Index within the the Precoditions: 0 <= ix ix < unSize (sizeOfMSBArray srcArray) |
| -> e | elt - Element to be written into |
| -> m () |
O(1) - Write an element elt into the mutable small boxed array dstMutArray at
the supplied index ix. The actual element will be evaluated to WHNF prior to
mutation.
- Unsafe
- Violation of
ixpreconditions can result in heap corruption or a failure with a segfault
Examples
>>>ma <- newSBMArray 4 (Nothing :: Maybe Integer)>>>writeSBMArray ma 2 (Just 2)>>>freezeSBMArray maSBArray [Nothing,Nothing,Just 2,Nothing]
It is important to note that an element is evaluated prior to being written into a cell, so it will not overwrite the value of an array's cell if it evaluates to an exception:
>>>import Control.Prim.Exception>>>writeSBMArray ma 2 (impureThrow DivideByZero)*** Exception: divide by zero>>>freezeSBMArray maSBArray [Nothing,Nothing,Just 2,Nothing]
However, it is evaluated only to Weak Head Normal Form (WHNF), so it is still possible to write something that eventually evaluates to bottom.
>>>writeSBMArray ma 3 (Just (7 `div` 0 ))>>>freezeSBMArray maSBArray [Nothing,Nothing,Just 2,Just *** Exception: divide by zero
Either deepseq or writeDeepSBMArray can be used to alleviate that.
Since: 0.3.0
writeLazySBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> Int -> e -> m () Source #
O(1) - Same as writeSBMArray but allows to write a thunk into an array instead of an
evaluated element. Careful with memory leaks and thunks that evaluate to exceptions.
Documentation for utilized primop: writeSmallArray#.
- Unsafe
- Same reasons as
writeSBMArray
Since: 0.3.0
writeDeepSBMArray :: forall e m s. (MonadPrim s m, NFData e) => SBMArray e s -> Int -> e -> m () Source #
O(1) - Same as writeSBMArray, except it ensures that the value being written is
fully evaluated, i.e. to Normal Form (NF).
- Unsafe
- Same reasons as
writeSBMArray
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => Size | sz - Size of the array Preconditions: 0 <= sz Should be below some upper limit that is dictated by the operating system and the total amount of available memory |
| -> e | elt - Value to use for all array cells |
| -> m (SBMArray e s) |
Create a mutable boxed array where each element is set to the supplied initial value
elt, which is evaluated before array allocation happens. See newLazySBMArray for
an ability to initialize with a thunk.
- Unsafe size
- Violation of precondition for the
szargument can result in the current thread being killed withHeapOverflowasynchronous exception or death of the whole process with some unchecked exception from RTS.
Examples
>>>newSBMArray 10 'A' >>= freezeSBMArraySBArray "AAAAAAAAAA"
Since: 0.3.0
newLazySBMArray :: forall e m s. MonadPrim s m => Size -> e -> m (SBMArray e s) Source #
Same as newSBMArray, except initial element is allowed to be a thunk.
Documentation for utilized primop: newSmallArray#.
- Unsafe
- Same reasons as
newSBMArray
Since: 0.3.0
newRawSBMArray :: forall e m s. (HasCallStack, MonadPrim s m) => Size -> m (SBMArray e s) Source #
Create new mutable array, where each element is initilized to a thunk that throws an
error when evaluated. This is useful when there is a plan to later iterate over the whole
array and write values into each cell in some index aware fashion. Consider makeSBMArray
as an alternative.
- Partial
- All array cells are initialized with thunks that throw
UndefinedElementexception. - Unsafe
- Same reasons as
newSBMArray
Examples
>>>import Data.Prim>>>let xs = "Hello Haskell">>>ma <- newRawSBMArray (Size (length xs)) :: IO (SBMArray Char RW)>>>mapM_ (\(i, x) -> writeSBMArray ma i x) (zip [0..] xs)>>>freezeSBMArray maSBArray "Hello Haskell"
Since: 0.3.0
makeSBMArray :: forall e m s. MonadPrim s m => Size -> (Int -> m e) -> m (SBMArray e s) Source #
Create new mutable boxed array of the supplied size and fill it with a monadic action that is applied to indices of each array cell.
- Unsafe
- Same reasons as
newSBMArray
Examples
>>>ma <- makeSBMArray 5 $ \i -> (toEnum (i + 97) :: Char) <$ putStrLn ("Handling index: " ++ show i)Handling index: 0 Handling index: 1 Handling index: 2 Handling index: 3 Handling index: 4>>>freezeSBMArray maSBArray "abcde"
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBMArray e s | srcMutArray - Source mutable array |
| -> Int | srcStartIx - Offset into the source mutable array where copy should start from Preconditions: 0 <= srcStartIx srcSize <- getSizeOfSBMArray srcMutArray srcStartIx < unSize srcSize |
| -> SBMArray e s | dstMutArray - Destination mutable array |
| -> Int | dstStartIx - Offset into the destination mutable array where copy should start to Preconditions: 0 <= dstStartIx dstSize <- getSizeOfSBMArray dstMutArray dstStartIx < unSize dstSize |
| -> Size | sz - Number of elements to copy over Preconditions: 0 <= sz srcSize <- getSizeOfSBMArray srcMutArray srcStartIx + unSize sz < unSize srcSize dstSize <- getSizeOfSBMArray dstMutArray dstStartIx + unSize sz < unSize dstSize |
| -> m () |
O(sz) - Copy a subsection of a mutable array into a subsection of another or the same
mutable array. Therefore, unlike copySBArray, memory ia allowed to overlap between source
and destination.
Documentation for utilized primop: copySmallMutableArray#.
- Unsafe
- When any of the preconditions for
srcStartIx,dstStartIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault.
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBMArray e s | srcArray - Source mutable array |
| -> Int | startIx - Location within Preconditions: 0 <= startIx startIx < unSize (sizeOfSBArray srcArray) |
| -> Size | sz - Size of the returned mutable array. Also this is the number of elements that will be copied over into the destionation array starting at the beginning. Preconditions: 0 <= sz startIx + unSize sz < unSize (sizeOfSBArray srcArray) Should be less then actual available memory |
| -> m (SBMArray e s) |
O(sz) - Allocate a new small boxed mutable array of size sz and copy that number
of the elements over from the srcArray starting at index ix. Similar to
cloneSBArray, except that it works on mutable arrays.
Documentation for utilized primop: cloneSmallMutableArray#.
- Unsafe
- When any of the preconditions for
startIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault. Failure with out of memory is also a possibility when the @sz is too large.
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBMArray e s | mutArray - Mutable unboxed array to be shrunk |
| -> Size | sz - New size for the array in number of elements Preconditions: 0 <= sz curSize <- getSizeOfSBMArray mutArray sz <= curSize |
| -> m () |
O(1) - Reduce the size of a mutable small boxed array.
Documentation for utilized primop: shrinkSmallMutableArray#.
- Unsafe
- - Violation of preconditions for
szleads to undefined behavior
- 3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBMArray e s | srcMutArray - Mutable boxed array to be shrunk |
| -> Size | sz - New size for the array in number of elements Preconditions: 0 <= sz Should be below some upper limit that is dictated by the operating system and the total amount of available memory |
| -> e | elt - Element to write into extra space at the end when growing the array. |
| -> m (SBMArray e s) | dstMutArray - produces a resized version of srcMutArray. |
O(1) - Either grow or shrink the size of a mutable unboxed array. Shrinking happens
in-place without new array creation and data copy, while growing the array is
implemented with creating new array and copy of the data over from the source array
srcMutArray. This has a consequence that produced array dstMutArray might refer to
the same srcMutArray or to a totally new array, which can be checked with
isSameSBMArray.
Documentation on the utilized primop: resizeSmallMutableArray#.
- Unsafe
- - Same reasons as in
newRawSBMArray.
- 3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBMArray e s | srcMutArray - Mutable boxed array to be shrunk |
| -> Size | sz - New size for the array in number of elements Preconditions: 0 <= sz Should be below some upper limit that is dictated by the operating system and the total amount of available memory |
| -> m (SBMArray e s) | dstMutArray - produces a resized version of srcMutArray. |
O(1) - Same as resizeSBMArray, except when growing the array empty space at the
end is filled with bottom.
- Partial
- - When size
szis larger then the size ofsrcMutArraythendstMutArraywill have cells at the end initialized with thunks that throwUndefinedElementexception. - Unsafe
- - Same reasons as in
newSBMArray.
- 3.0
freezeSBMArray :: forall e m s. MonadPrim s m => SBMArray e s -> m (SBArray e) Source #
O(1) - Convert a mutable boxed array into an immutable one. Use thawSBArray in order
to go in the opposite direction.
Documentation for utilized primop: unsafeFreezeSmallArray#.
- Unsafe
- This function makes it possible to break referential transparency, because any
subsequent destructive operation to the source mutable boxed array will also be reflected
in the resulting immutable array. See
freezeCopySBMArraythat avoids this problem with fresh allocation.
Since: 0.3.0
Arguments
| :: forall e m s. MonadPrim s m | |
| => SBMArray e s | srcArray - Source mutable array |
| -> Int | startIx - Location within Preconditions: 0 <= startIx startIx < unSize (sizeOfSBArray srcArray) |
| -> Size | sz - Size of the returned immutable array. Also this is the number of elements that will be copied over into the destionation array starting at the beginning. Preconditions: 0 <= sz startIx + unSize sz < unSize (sizeOfSBArray srcArray) Should be less then actual available memory |
| -> m (SBArray e) |
O(sz) - Similar to freezeSBMArray, except it creates a new array with the copy of a
subsection of a mutable array before converting it into an immutable.
Documentation for utilized primop: freezeSmallArray#.
- Unsafe
- When any of the preconditions for
startIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor more likely a failure with a segfault or out of memory exception.
Since: 0.3.0
Unboxed Array
Immutable
Constructors
| UArray ByteArray# |
Instances
| Prim e => IsList (UArray e) Source # | |
| (Prim e, Eq e) => Eq (UArray e) Source # | |
| (Prim e, Ord e) => Ord (UArray e) Source # | |
Defined in Data.Prim.Array | |
| (Prim e, Show e) => Show (UArray e) Source # | |
| e ~ Char => IsString (UArray e) Source # | |
Defined in Data.Prim.Array Methods fromString :: String -> UArray e # | |
| Prim e => Semigroup (UArray e) Source # | |
| Prim e => Monoid (UArray e) Source # | |
| NFData (UArray e) Source # | O(1) - |
Defined in Data.Prim.Array | |
| type Item (UArray e) Source # | |
Defined in Data.Prim.Array | |
isSameUArray :: forall a b. UArray a -> UArray b -> Bool Source #
O(1) - Compare pointers for two immutable arrays and see if they refer to the exact same one.
Documentation for utilized primop: isSameByteArray#.
Since: 0.3.0
isPinnedUArray :: forall e. UArray e -> Bool Source #
O(1) - Check if memory for immutable unboxed array was allocated as pinned.
Documentation for utilized primop: isByteArrayPinned#.
Since: 0.3.0
sizeOfUArray :: forall e. Prim e => UArray e -> Size Source #
O(1) - Get the size of an immutable array in number of elements.
Documentation for utilized primop: sizeofByteArray#.
Since: 0.3.0
Arguments
| :: forall e. Prim e | |
| => UArray e | array - Array where to lookup an element from |
| -> Int | ix - Position of the element within the Precoditions: 0 <= ix ix < unSize (sizeOfUArray array) |
| -> e |
O(1) - Index an element of a pure unboxed array.
Documentation for utilized primop: indexByteArray#.
- Unsafe
- Bounds are not checked. When a precondition for
ixargument is violated the result is either unpredictable output or failure with a segfault.
Examples
>>>let a = fromListUArray ([Left pi, Right 123] :: [Either Double Int])>>>indexUArray a 0Left 3.141592653589793>>>indexUArray a 1Right 123
Since: 0.3.0
Arguments
| :: forall e m s. (Prim e, MonadPrim s m) | |
| => UArray e | srcArray - Source immutable array Precondition: srcMutArray <- thawUArray srcArray srcMutArray /= dstMutArray |
| -> Int | srcStartIx - Offset into the source immutable array where copy should start from Preconditions: 0 <= srcStartIx srcStartIx < unSize (sizeOfUArray srcArray) |
| -> UMArray e s | dstMutArray - Destination mutable array |
| -> Int | dstStartIx - Offset into the destination mutable array where the copy should start at Preconditions: 0 <= dstStartIx dstSize <- getSizeOfMUArray dstMutArray dstStartIx < unSize dstSize |
| -> Size | sz - Number of elements to copy over Preconditions: 0 <= sz srcStartIx + unSize sz < unSize (sizeOfUArray srcArray) dstSize <- getSizeOfMUArray dstMutArray dstStartIx + unSize sz < unSize dstSize |
| -> m () |
O(sz) - Copy a subsection of an immutable array into a subsection of another mutable array. Source and destination arrays must not be the same array in different states.
Documentation for utilized primop: copyByteArray#.
- Unsafe
- When any of the preconditions for
srcStartIx,dstStartIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor failure with a segfault.
Since: 0.3.0
thawUArray :: forall e m s. MonadPrim s m => UArray e -> m (UMArray e s) Source #
O(1) - Convert a pure immutable unboxed array into a mutable unboxed array. Use
freezeUMArray in order to go in the opposite direction.
Documentation for utilized primop: unsafeThawByteArray#.
- Unsafe
- This function makes it possible to break referential transparency, because any subsequent destructive operation to the mutable unboxed array will also be reflected in the source immutable array as well.
Examples
>>>ma <- thawUArray $ fromListUArray [1 .. 5 :: Int]>>>writeUMArray ma 1 10>>>freezeUMArray maUArray [1,10,3,4,5]
Be careful not to retain a reference to the pure immutable source array after the thawed version gets mutated.
>>>let a = fromListUArray [1 .. 5 :: Int]>>>ma' <- thawUArray a>>>writeUMArray ma' 0 100000>>>aUArray [100000,2,3,4,5]
Since: 0.3.0
toListUArray :: forall e. Prim e => UArray e -> [e] Source #
O(n) - Convert a pure boxed array into a list. It should work fine with GHC built-in list fusion.
Since: 0.1.0
fromListUArray :: forall e. Prim e => [e] -> UArray e Source #
O(length list) - Convert a list into an immutable boxed array. It is more efficient to use
fromListUArrayN when the number of elements is known ahead of time. The reason for this
is that it is necessary to iterate the whole list twice: once to count how many elements
there is in order to create large enough array that can fit them; and the second time to
load the actual elements. Naturally, infinite lists will grind the program to a halt.
Example
>>>fromListUArray "Hello Haskell"UArray "Hello Haskell"
Since: 0.3.0
Arguments
| :: forall e. Prim e | |
| => Size | sz - Expected number of elements in the |
| -> [e] | list - A list to bew loaded into the array |
| -> UArray e |
O(min(length list, sz)) - Same as fromListUArray, except it will allocate an array exactly of n size, as
such it will not convert any portion of the list that doesn't fit into the newly
created array.
- Partial
- When length of supplied list is in fact smaller then the expected size
sz, thunks withUndefinedElementexception throwing function will be placed in the tail portion of the array. - Unsafe
- When a precondition
szis violated this function can result in critical failure with out of memory orHeapOverflowasync exception.
Examples
>>>fromListUArrayN 3 [1 :: Int, 2, 3]UArray [1,2,3]>>>fromListUArrayN 3 [1 :: Int ..]UArray [1,2,3]
Since: 0.1.0
fromBaseUArray :: (Prim e, IArray UArray e) => UArray ix e -> UArray e Source #
O(1) - cast an unboxed UArray that is wired with GHC to UArray from primal.
>>>import Data.Array.IArray as IA>>>import Data.Array.Unboxed as UA>>>let uarr = IA.listArray (10, 15) [30 .. 35] :: UA.UArray Int Word>>>uarrarray (10,15) [(10,30),(11,31),(12,32),(13,33),(14,34),(15,35)]>>>fromBaseUArray uarrUArray [30,31,32,33,34,35]
Since: 0.3.0
Mutable
Constructors
| UMArray (MutableByteArray# s) |
isSameUMArray :: forall a b s. UMArray a s -> UMArray b s -> Bool Source #
O(1) - Compare pointers for two mutable arrays and see if they refer to the exact same one.
Documentation for utilized primop: sameMutableByteArray#.
Since: 0.3.0
isPinnedUMArray :: forall e s. UMArray e s -> Bool Source #
O(1) - Check if memory for mutable unboxed array was allocated as pinned.
Documentation for utilized primop: isMutableByteArrayPinned#.
Since: 0.3.0
getSizeOfUMArray :: forall e m s. (Prim e, MonadPrim s m) => UMArray e s -> m Size Source #
O(1) - Get the size of a mutable unboxed array
Documentation for utilized primop: getSizeofMutableByteArray#.
Example
>>>ma <- thawUArray $ fromListUArray ['a' .. 'z']>>>getSizeOfUMArray maSize {unSize = 26}
Since: 0.3.0
Arguments
| :: forall e m s. (Prim e, MonadPrim s m) | |
| => UMArray e s | srcMutArray - Array to read an element from |
| -> Int | ix - Index for the element we need within the the Precoditions: 0 <= ix srcSize <- getSizeOfMUArray srcMutArray ix < unSize srcSize |
| -> m e |
O(1) - Read an element from a mutable unboxed array at the supplied index.
Documentation for utilized primop: readMutableByteArray#.
- Unsafe
- Violation of
ixpreconditions can result in value that doesn't belong tosrcMutArrayor a failure with a segfault
Examples
>>>ma <- thawUArray $ fromListUArray "Hi!">>>readUMArray ma 2'!'
Since: 0.3.0
writeUMArray :: forall e m s. (Prim e, MonadPrim s m) => UMArray e s -> Int -> e -> m () Source #
O(1) - Write an element into an unboxed mutable array at a supplied index.
Documentation for utilized primop: writeMutableByteArray#.
- Unsafe
- Violation of
ixpreconditions can result in heap corruption or a failure with a segfault
Examples
>>>import Data.Prim>>>ma <- newRawUMArray 4 :: IO (UMArray (Maybe Int) RW)>>>mapM_ (\i -> writeUMArray ma i Nothing) [0, 1, 3]>>>writeUMArray ma 2 (Just 2)>>>freezeUMArray maUArray [Nothing,Nothing,Just 2,Nothing]
Since: 0.3.0
Arguments
| :: forall e m s. (Prim e, MonadPrim s m) | |
| => Size | sz - Size of the array in number of elements. Preconditions: 0 <= sz Susceptible to integer overflow: 0 <= toByteCount (Count (unSize n) :: Count e) Should be below some upper limit that is dictated by the operating system and the total amount of available memory |
| -> e | |
| -> m (UMArray e s) |
O(sz) - Allocate new mutable unboxed array. Similar to newRawUMArray, except all
elements are initialized to the supplied initial value. This is equivalent to
makeUMArray sz (const (pure a)) but often will be more efficient.
- Unsafe
- When any of preconditions for
szargument is violated the outcome is unpredictable. One possible outcome is termination withHeapOverflowasync exception.
Examples
>>>import Data.Prim>>>let xs = "Hello">>>ma <- newUMArray (Size (length xs) + 8) '!' :: IO (UMArray Char RW)>>>mapM_ (\(i, x) -> writeUMArray ma i x) (zip [0..] xs)>>>freezeUMArray maUArray "Hello!!!!!!!!"
Since: 0.3.0
Arguments
| :: forall e m s. (Prim e, MonadPrim s m) | |
| => Size | sz - Size of the array in number of elements. Preconditions: 0 <= sz Susceptible to integer overflow: 0 <= toByteCount (Count (unSize n) :: Count e) Should be below some upper limit that is dictated by the operating system and the total amount of available memory |
| -> m (UMArray e s) |
O(1) - Allocate new mutable unboxed array. None of the elements are initialized so expect it to contain some random garbage.
Documentation for utilized primop: newByteArray#.
- Unsafe
- When any of preconditions for
szargument is violated the outcome is unpredictable. One possible outcome is termination withHeapOverflowasync exception. In a pure setting, such as when executed withinrunST, if each cell in new array is not overwritten it can lead to violation of referential transparency, because contents of newly allocated unboxed array is non-determinstic.
Examples
>>>import Data.Prim>>>let xs = "Hello Haskell">>>ma <- newRawUMArray (Size (length xs)) :: IO (UMArray Char RW)>>>mapM_ (\(i, x) -> writeUMArray ma i x) (zip [0..] xs)>>>freezeUMArray maUArray "Hello Haskell"
Since: 0.3.0
makeUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> (Int -> m e) -> m (UMArray e s) Source #
Create new mutable unboxed array of the supplied size and fill it with a monadic action that is applied to indices of each array cell.
- Unsafe
- Same reasons as
newUMArray
Examples
>>>ma <- makeUMArray 5 $ \i -> (toEnum (i + 97) :: Char) <$ putStrLn ("Handling index: " ++ show i)Handling index: 0 Handling index: 1 Handling index: 2 Handling index: 3 Handling index: 4>>>freezeUMArray maUArray "abcde"
Since: 0.3.0
newPinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> e -> m (UMArray e s) Source #
Same newUMArray, but allocate memory as pinned. See newRawPinnedUMArray for more info.
- Unsafe
- - Same reasons as
newUMArray.
Since: 0.3.0
newRawPinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> m (UMArray e s) Source #
O(1) - Same as newRawUMArray except allocate new mutable unboxed array as pinned
Documentation for utilized primop: newPinnedByteArray#.
- Unsafe
- Same reasons as in
newRawUMArray.
Since: 0.3.0
makePinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> (Int -> m e) -> m (UMArray e s) Source #
newAlignedPinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> e -> m (UMArray e s) Source #
Same newUMArray, but allocate memory as pinned and aligned. See
newRawAlignedPinnedUMArray for more info.
- Unsafe
- - Same reasons as
newUMArray.
Since: 0.3.0
newRawAlignedPinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> m (UMArray e s) Source #
O(1) - Same as newRawPinnedUMArray except allocate new mutable unboxed array as
pinned and aligned according to the Prim instance for the type of element e
Documentation for utilized primop: newAlignedPinnedByteArray#.
- Unsafe
- Same reasons as in
newRawUMArray.
Since: 0.3.0
makeAlignedPinnedUMArray :: forall e m s. (Prim e, MonadPrim s m) => Size -> (Int -> m e) -> m (UMArray e s) Source #
Same as makeUMArray, but allocate memory as pinned and aligned.
- Unsafe
- Same reasons as
newUMArray
Since: 0.3.0
Arguments
| :: forall e m s. (Prim e, MonadPrim s m) | |
| => UMArray e s | srcMutArray - Source mutable array |
| -> Int | srcStartIx - Offset into the source mutable array where copy should start from Preconditions: 0 <= srcStartIx srcSize <- getSizeOfMUArray srcMutArray srcStartIx < unSize srcSize |
| -> UMArray e s | dstMutArray - Destination mutable array |
| -> Int | dstStartIx - Offset into the destination mutable array where copy should start to Preconditions: 0 <= dstStartIx dstSize <- getSizeOfMUArray dstMutArray dstStartIx < unSize dstSize |
| -> Size | sz - Number of elements to copy over Preconditions: 0 <= sz srcSize <- getSizeOfMUArray srcMutArray srcStartIx + unSize sz < unSize srcSize dstSize <- getSizeOfMUArray dstMutArray dstStartIx + unSize sz < unSize dstSize |
| -> m () |
O(sz) - Copy a subsection of a mutable array into a subsection of another or the same
mutable array. Therefore, unlike copyBArray, memory ia allowed to overlap between
source and destination.
Documentation for utilized primop: copyMutableByteArray#.
- Unsafe
- When any of the preconditions for
srcStartIx,dstStartIxorszis violated this function can result in a copy of some data that doesn't belong tosrcArrayor failure with a segfault.
Since: 0.3.0
Arguments
| :: forall e m s. (Prim e, MonadPrim s m) | |
| => UMArray e s | dstMutArray - Mutable array |
| -> Int | dstStartIx - Offset into the mutable array Preconditions: 0 <= dstStartIx dstSize <- getSizeOfMUArray dstMutArray dstStartIx < unSize dstSize |
| -> Size | n - Number of elements to overwrite Preconditions: 0 <= n dstSize <- getSizeOfMUArray dstMutArray dstStartIx + unSize n < unSize dstSize |
| -> e | elt - Value to overwrite the cells with in the specified block |
| -> m () |
O(n) - Write the same element into the dstMutArray mutable array n times starting
at dstStartIx offset.
- Unsafe
Since: 0.3.0
Arguments
| :: forall e m s. (MonadPrim s m, Prim e) | |
| => UMArray e s | mutArray - Mutable unboxed array to be shrunk |
| -> Size | sz - New size for the array in number of elements Preconditions: 0 <= sz curSize <- getSizeOfUMArray mutArray sz <= curSize |
| -> m () |
O(1) - Reduce the size of a mutable unboxed array.
Documentation for utilized primop: shrinkMutableByteArray#.
- Unsafe
- - Violation of preconditions for
szleads to undefined behavior
- 3.0
Arguments
| :: forall e m s. (MonadPrim s m, Prim e) | |
| => UMArray e s | srcMutArray - Mutable unboxed array to be shrunk |
| -> Size | sz - New size for the array in number of elements Preconditions: 0 <= sz Susceptible to integer overflow: 0 <= toByteCount (Count (unSize n) :: Count e) Should be below some upper limit that is dictated by the operating system and the total amount of available memory |
| -> m (UMArray e s) | dstMutArray - produces a resized version of srcMutArray. |
O(1) - Either grow or shrink the size of a mutable unboxed array. Shrinking happens
without new allocation and data copy, while growing the array is implemented with
allocation of new unpinned array and copy of the data over from the source array
srcMutArray. This has a consequence that produced array dstMutArray might refer to
the same srcMutArray or to a totally new array, which can be checked with
isSameUMArray.
Documentation on the utilized primop: resizeMutableByteArray#.
- Unsafe
- - Same reasons as in
newRawUMArray. When sizeszis larger then the size ofsrcMutArraythendstMutArraywill contain uninitialized memory at its end, hence a potential problem for referential transparency.
- 3.0
freezeUMArray :: forall e m s. MonadPrim s m => UMArray e s -> m (UArray e) Source #
O(1) - Convert a mutable unboxed array into an immutable one. Use thawUArray in order
to go in the opposite direction.
Documentation on the utilized primop: unsafeFreezeByteArray#.
- Unsafe
- This function makes it possible to break referential transparency, because any
subsequent destructive operation to the source mutable boxed array will also be reflected
in the resulting immutable array. See
freezeCopyBMArraythat avoids this problem with fresh allocation.
Since: 0.3.0
Helper functions
Arguments
| :: HasCallStack | |
| => String | Module name |
| -> String | Function name |
| -> a |
Default "raw" element for boxed arrays.
Arguments
| :: Monad m | |
| => (Size -> m b) | Function for array creation |
| -> (b -> Int -> a -> m ()) | Function for writing elements |
| -> Size | Size for the created array |
| -> (Int -> m a) | Function for generating elements from array index |
| -> m b |
Helper for generating mutable arrays
Since: 0.3.0
Arguments
| :: Monad m | |
| => (Size -> m b) | Function for array creation |
| -> (b -> Int -> a -> m ()) | Function for writing elements |
| -> Size | Size for the created array |
| -> [a] | Function for generating elements from array index |
| -> m b |
Convert a list to a mutable array
Arguments
| :: (a e -> Size) | Function that produces the size of an array |
| -> (a e -> Int -> e) | Indexing function |
| -> (e -> b -> b) | Folding functions |
| -> b | Initial accumulator |
| -> a e | Array to fold over |
| -> b |
Right fold that is strict on the element. The key feature of this function is that it
can be used to convert an array to a list by integrating with list fusion using build.
Since: 0.3.0
Arguments
| :: Eq e | |
| => (a e -> a e -> Bool) | Pointer equality |
| -> (a e -> Size) | Get the size of array |
| -> (a e -> Int -> e) | Index an element of an array |
| -> a e | First array |
| -> a e | Second array |
| -> Bool |
Check for equality of two arrays
Since: 0.3.0
Arguments
| :: Ord e | |
| => (a e -> a e -> Bool) | Pointer equality |
| -> (a e -> Size) | Get the size of array |
| -> (a e -> Int -> e) | Index an element of an array |
| -> a e | First array |
| -> a e | Second array |
| -> Ordering |
Compare two arrays using supplied functions
Since: 0.3.0