Copyright | (c) Alexey Kuleshevich 2018-2020 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- unsafeMakeLoadArray :: Comp -> Sz ix -> Maybe e -> (forall m. Monad m => Scheduler m () -> Int -> (Int -> e -> m ()) -> m ()) -> Array DL ix e
- unsafeMakeLoadArrayAdjusted :: Comp -> Sz ix -> Maybe e -> (forall m. Monad m => Scheduler m () -> (Int -> e -> m ()) -> m ()) -> Array DL ix e
- newtype Sz ix = SafeSz ix
- newtype Stride ix = SafeStride ix
- unsafeIndex :: Source r ix e => Array r ix e -> ix -> e
- unsafeLinearIndex :: Source r ix e => Array r ix e -> Int -> e
- unsafeLinearIndexM :: Manifest r ix e => Array r ix e -> Int -> e
- unsafeBackpermute :: (Source r' ix' e, Index ix) => Sz ix -> (ix -> ix') -> Array r' ix' e -> Array D ix e
- unsafeResize :: (Resize r ix, Index ix') => Sz ix' -> Array r ix e -> Array r ix' e
- unsafeExtract :: Extract r ix e => ix -> Sz ix -> Array r ix e -> Array (R r) ix e
- unsafeTransform :: (Source r' ix' e', Index ix) => (Sz ix' -> (Sz ix, a)) -> (a -> (ix' -> e') -> ix -> e) -> Array r' ix' e' -> Array D ix e
- unsafeTransform2 :: (Source r1 ix1 e1, Source r2 ix2 e2, Index ix) => (Sz ix1 -> Sz ix2 -> (Sz ix, a)) -> (a -> (ix1 -> e1) -> (ix2 -> e2) -> ix -> e) -> Array r1 ix1 e1 -> Array r2 ix2 e2 -> Array D ix e
- unsafeSlice :: (Slice r ix e, MonadThrow m) => Array r ix e -> ix -> Sz ix -> Dim -> m (Elt r ix e)
- unsafeOuterSlice :: OuterSlice r ix e => Array r ix e -> Int -> Elt r ix e
- unsafeInnerSlice :: InnerSlice r ix e => Array r ix e -> (Sz (Lower ix), Sz Int) -> Int -> Elt r ix e
- unsafeLinearSlice :: Source r ix e => Ix1 -> Sz1 -> Array r ix e -> Array r Ix1 e
- unsafeThaw :: (Mutable r ix e, PrimMonad m) => Array r ix e -> m (MArray (PrimState m) r ix e)
- unsafeFreeze :: (Mutable r ix e, PrimMonad m) => Comp -> MArray (PrimState m) r ix e -> m (Array r ix e)
- unsafeNew :: (Mutable r ix e, PrimMonad m) => Sz ix -> m (MArray (PrimState m) r ix e)
- unsafeCreateArray :: forall r ix e a m b. (Mutable r ix e, PrimMonad m, MonadUnliftIO m) => Comp -> Sz ix -> (Scheduler m a -> MArray (PrimState m) r ix e -> m b) -> m ([a], Array r ix e)
- unsafeCreateArray_ :: forall r ix e a m b. (Mutable r ix e, PrimMonad m, MonadUnliftIO m) => Comp -> Sz ix -> (Scheduler m a -> MArray (PrimState m) r ix e -> m b) -> m (Array r ix e)
- unsafeCreateArrayS :: forall r ix e a m. (Mutable r ix e, PrimMonad m) => Sz ix -> (MArray (PrimState m) r ix e -> m a) -> m (a, Array r ix e)
- unsafeRead :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> m e
- unsafeLinearRead :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> m e
- unsafeWrite :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> e -> m ()
- unsafeLinearWrite :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> e -> m ()
- unsafeModify :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m e) -> ix -> m e
- unsafeLinearModify :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m e) -> Int -> m e
- unsafeSwap :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> ix -> m (e, e)
- unsafeLinearSwap :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> Int -> m (e, e)
- unsafeLinearSet :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Ix1 -> Sz1 -> e -> m ()
- unsafeLinearCopy :: (Mutable r ix e, Mutable r ix' e, PrimMonad m) => MArray (PrimState m) r ix' e -> Ix1 -> MArray (PrimState m) r ix e -> Ix1 -> Sz1 -> m ()
- unsafeArrayLinearCopy :: (Mutable r ix e, Mutable r ix' e, PrimMonad m) => Array r ix' e -> Ix1 -> MArray (PrimState m) r ix e -> Ix1 -> Sz1 -> m ()
- unsafeLinearShrink :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Sz ix -> m (MArray (PrimState m) r ix e)
- unsafeLinearGrow :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Sz ix -> m (MArray (PrimState m) r ix e)
- unsafeWithPtr :: (MonadUnliftIO m, Storable a) => Array S ix a -> (Ptr a -> m b) -> m b
- unsafeArrayToForeignPtr :: Storable e => Array S ix e -> (ForeignPtr e, Int)
- unsafeMArrayToForeignPtr :: Storable e => MArray s S ix e -> (ForeignPtr e, Int)
- unsafeArrayFromForeignPtr :: Storable e => Comp -> ForeignPtr e -> Int -> Sz1 -> Array S Ix1 e
- unsafeArrayFromForeignPtr0 :: Storable e => Comp -> ForeignPtr e -> Sz1 -> Array S Ix1 e
- unsafeMArrayFromForeignPtr :: Storable e => ForeignPtr e -> Int -> Sz1 -> MArray s S Ix1 e
- unsafeMArrayFromForeignPtr0 :: Storable e => ForeignPtr e -> Sz1 -> MArray s S Ix1 e
- unsafeAtomicReadIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> m Int
- unsafeAtomicWriteIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m ()
- unsafeAtomicModifyIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> (Int -> Int) -> m Int
- unsafeAtomicAddIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeAtomicSubIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeAtomicAndIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeAtomicNandIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeAtomicOrIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeAtomicXorIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeCasIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> Int -> m Int
- unsafeBoxedArray :: Array e -> Array B Ix1 e
- unsafeNormalBoxedArray :: Array B ix e -> Array N ix e
- unsafeFromBoxedVector :: Vector a -> Array B Ix1 a
- unsafeUnstablePartitionRegionM :: forall r e m. (Mutable r Ix1 e, PrimMonad m) => MArray (PrimState m) r Ix1 e -> (e -> Bool) -> Ix1 -> Ix1 -> m Ix1
- unsafeHead :: Source r Ix1 e => Vector r e -> e
- unsafeLast :: Source r Ix1 e => Vector r e -> e
- unsafeIndexM :: (Source r Ix1 e, Monad m) => Vector r e -> Ix1 -> m e
- unsafeHeadM :: Monad m => Source r Ix1 e => Vector r e -> m e
- unsafeLastM :: Monad m => Source r Ix1 e => Vector r e -> m e
- unsafeInit :: Source r Ix1 e => Vector r e -> Vector r e
- unsafeTail :: Source r Ix1 e => Vector r e -> Vector r e
- unsafeTake :: Source r Ix1 e => Sz1 -> Vector r e -> Vector r e
- unsafeDrop :: Source r Ix1 e => Sz1 -> Vector r e -> Vector r e
- unsafeUnfoldrN :: Sz1 -> (s -> Maybe (e, s)) -> s -> Vector DS e
- unsafeUnfoldrNM :: Monad m => Sz1 -> (s -> m (Maybe (e, s))) -> s -> m (Vector DS e)
- unsafeFromListN :: Sz1 -> [e] -> Vector DS e
- makeUnsafeStencil :: Index ix => Sz ix -> ix -> (ix -> (ix -> e) -> a) -> Stencil ix e a
- unsafeMapStencil :: Manifest r ix e => Border e -> Sz ix -> ix -> (ix -> (ix -> e) -> a) -> Array r ix e -> Array DW ix a
- mapStencilUnsafe :: Manifest r ix e => Border e -> Sz ix -> ix -> ((ix -> e) -> a) -> Array r ix e -> Array DW ix a
- forStencilUnsafe :: (Source r ix e, Manifest r ix e) => Array r ix e -> Sz ix -> ix -> ((ix -> Maybe e) -> a) -> Array DW ix a
Creation
:: Comp | Computation strategy to use. Directly affects the scheduler that gets created for the loading function. |
-> Sz ix | Size of the array |
-> Maybe e | An element to use for initialization of the mutable array that will be created in the future |
-> (forall m. Monad m => Scheduler m () -> Int -> (Int -> e -> m ()) -> m ()) | This function accepts:
|
-> Array DL ix e |
Specify how an array can be loaded/computed through creation of a DL
array. Unlike
makeLoadArrayS
or makeLoadArray
this function is unsafe, since there is no
guarantee that all elements will be initialized and the supplied element writing
function does not perform any bounds checking.
Since: 0.3.1
unsafeMakeLoadArrayAdjusted :: Comp -> Sz ix -> Maybe e -> (forall m. Monad m => Scheduler m () -> (Int -> e -> m ()) -> m ()) -> Array DL ix e Source #
Same as unsafeMakeLoadArray
, except will ensure that starting index is correctly
adjusted. Which means the writing function gets one less argument.
Since: 0.5.2
Indexing
Sz
provides type safety guarantees preventing mixup with index, which is used for looking into
array cells, from the size, that describes total number of elements along each dimension in the
array. Moreover the Sz
constructor will prevent creation of invalid sizes with negative numbers.
Since: 0.3.0
SafeSz ix | Safe size constructor. It is unsafe to use it without making sure that it does not contain
negative components. Use Since: 0.3.0 |
Stride provides a way to ignore elements of an array if an index is divisible by a
corresponding value in a stride. So, for a Stride (i :. j)
only elements with indices will be
kept around:
( 0 :. 0) ( 0 :. j) ( 0 :. 2j) ( 0 :. 3j) ... ( i :. 0) ( i :. j) ( i :. 2j) ( i :. 3j) ... (2i :. 0) (2i :. j) (2i :. 2j) (2i :. 3j) ... ...
Only positive strides make sense, so Stride
pattern synonym constructor will prevent a user
from creating a stride with negative or zero values, thus promoting safety of the library.
Examples:
- Default and minimal stride of
will have no affect and all elements will kept.Stride
(pureIndex
1) - If stride is
, then every 2nd element (i.e. with index 1, 3, 5, ..) will be skipped and only elemnts with indices divisible by 2 will be kept around.Stride
2 - In case of two dimensions, if what you want is to keep all rows divisible by 5, but keep every
column intact then you'd use
Stride (5 :. 1)
.
Since: 0.2.1
SafeStride ix |
unsafeIndex :: Source r ix e => Array r ix e -> ix -> e Source #
Lookup element in the array. No bounds check is performed and access of arbitrary memory is possible when invalid index is supplied.
Since: 0.1.0
unsafeLinearIndex :: Source r ix e => Array r ix e -> Int -> e Source #
Lookup element in the array using flat index in a row-major fashion. No bounds check is performed
Since: 0.1.0
Manipulations
unsafeBackpermute :: (Source r' ix' e, Index ix) => Sz ix -> (ix -> ix') -> Array r' ix' e -> Array D ix e Source #
unsafeResize :: (Resize r ix, Index ix') => Sz ix' -> Array r ix e -> Array r ix' e Source #
O(1) - Change the size of an array. Total number of elements should be the same, but it is not validated.
unsafeExtract :: Extract r ix e => ix -> Sz ix -> Array r ix e -> Array (R r) ix e Source #
O(1) - Extract a portion of an array. Staring index and new size are not validated.
unsafeTransform :: (Source r' ix' e', Index ix) => (Sz ix' -> (Sz ix, a)) -> (a -> (ix' -> e') -> ix -> e) -> Array r' ix' e' -> Array D ix e Source #
Same transform'
, except no bounds checking is performed, thus making it faster,
but unsafe.
Since: 0.3.0
unsafeTransform2 :: (Source r1 ix1 e1, Source r2 ix2 e2, Index ix) => (Sz ix1 -> Sz ix2 -> (Sz ix, a)) -> (a -> (ix1 -> e1) -> (ix2 -> e2) -> ix -> e) -> Array r1 ix1 e1 -> Array r2 ix2 e2 -> Array D ix e Source #
Same transform2'
, except no bounds checking is performed, thus making it faster,
but unsafe.
Since: 0.3.0
Slicing
unsafeSlice :: (Slice r ix e, MonadThrow m) => Array r ix e -> ix -> Sz ix -> Dim -> m (Elt r ix e) Source #
unsafeOuterSlice :: OuterSlice r ix e => Array r ix e -> Int -> Elt r ix e Source #
O(1) - Take a slice out of an array from the outside
unsafeInnerSlice :: InnerSlice r ix e => Array r ix e -> (Sz (Lower ix), Sz Int) -> Int -> Elt r ix e Source #
unsafeLinearSlice :: Source r ix e => Ix1 -> Sz1 -> Array r ix e -> Array r Ix1 e Source #
O(1) - Source arrays also give us ability to look at their linear slices in constant time
Since: 0.5.0
Mutable interface
unsafeThaw :: (Mutable r ix e, PrimMonad m) => Array r ix e -> m (MArray (PrimState m) r ix e) Source #
Convert immutable array into a mutable array without copy.
Since: 0.1.0
unsafeFreeze :: (Mutable r ix e, PrimMonad m) => Comp -> MArray (PrimState m) r ix e -> m (Array r ix e) Source #
Convert mutable array into an immutable array without copy.
Since: 0.1.0
unsafeNew :: (Mutable r ix e, PrimMonad m) => Sz ix -> m (MArray (PrimState m) r ix e) Source #
Create new mutable array, leaving it's elements uninitialized. Size isn't validated either.
Since: 0.1.0
:: (Mutable r ix e, PrimMonad m, MonadUnliftIO m) | |
=> Comp | Computation strategy to use after |
-> Sz ix | Size of the newly created array |
-> (Scheduler m a -> MArray (PrimState m) r ix e -> m b) | An action that should fill all elements of the brand new mutable array |
-> m ([a], Array r ix e) |
Same as createArray
, but memory will not be initialized
and for unboxed types might contain garbage.
Since: 0.5.0
:: (Mutable r ix e, PrimMonad m, MonadUnliftIO m) | |
=> Comp | Computation strategy to use after |
-> Sz ix | Size of the newly created array |
-> (Scheduler m a -> MArray (PrimState m) r ix e -> m b) | An action that should fill all elements of the brand new mutable array |
-> m (Array r ix e) |
Same as createArray_
, but memory will not be initialized
and for unboxed types might contain garbage.
Since: 0.5.0
:: (Mutable r ix e, PrimMonad m) | |
=> Sz ix | Size of the newly created array |
-> (MArray (PrimState m) r ix e -> m a) | An action that should fill all elements of the brand new mutable array |
-> m (a, Array r ix e) |
Same as createArrayS
, but memory will not be initialized
and for unboxed types might contain garbage.
Since: 0.5.0
Read
unsafeRead :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> m e Source #
Read an array element
Since: 0.1.0
unsafeLinearRead :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> m e Source #
Read an element at linear row-major index
Since: 0.1.0
Write
unsafeWrite :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> e -> m () Source #
Write an element into array
Since: 0.1.0
unsafeLinearWrite :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> e -> m () Source #
Write an element into mutable array with linear row-major index
Since: 0.1.0
Modify
unsafeModify :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m e) -> ix -> m e Source #
Modify an element in the array with a monadic action. Returns the previous value.
Since: 0.4.0
unsafeLinearModify :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m e) -> Int -> m e Source #
Modify an element in the array with a monadic action. Returns the previous value.
Since: 0.4.0
Swap
unsafeSwap :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> ix -> m (e, e) Source #
Swap two elements in a mutable array under the supplied indices. Returns the previous values.
Since: 0.4.0
unsafeLinearSwap :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> Int -> m (e, e) Source #
Swap two elements in a mutable array under the supplied linear indices. Returns the previous values.
Since: 0.4.0
Range modification
unsafeLinearSet :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Ix1 -> Sz1 -> e -> m () Source #
Set all cells in the mutable array within the range to a specified value.
Since: 0.3.0
:: (Mutable r ix e, Mutable r ix' e, PrimMonad m) | |
=> MArray (PrimState m) r ix' e | Source mutable array |
-> Ix1 | Starting index at source array |
-> MArray (PrimState m) r ix e | Target mutable array |
-> Ix1 | Starting index at target array |
-> Sz1 | Number of elements to copy |
-> m () |
Copy part of one mutable array into another
Since: 0.3.6
unsafeArrayLinearCopy Source #
:: (Mutable r ix e, Mutable r ix' e, PrimMonad m) | |
=> Array r ix' e | Source pure array |
-> Ix1 | Starting index at source array |
-> MArray (PrimState m) r ix e | Target mutable array |
-> Ix1 | Starting index at target array |
-> Sz1 | Number of elements to copy |
-> m () |
Copy a part of a pure array into a mutable array
Since: 0.3.6
Resizing
unsafeLinearShrink :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Sz ix -> m (MArray (PrimState m) r ix e) Source #
Linearly reduce the size of an array. Total number of elements should be smaller or equal. There is no guarantee that the original array is left unchanged, so it should no longer be used.
Since: 0.3.6
unsafeLinearGrow :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Sz ix -> m (MArray (PrimState m) r ix e) Source #
Linearly increase the size of an array. Total number of elements should be larger or equal. There is no guarantee that the original array is left unchanged, so it should no longer be used.
Since: 0.3.6
Pointer access
unsafeWithPtr :: (MonadUnliftIO m, Storable a) => Array S ix a -> (Ptr a -> m b) -> m b Source #
A pointer to the beginning of the storable array. It is unsafe since, if mutated, it can break referential transparency.
Since: 0.1.3
unsafeArrayToForeignPtr :: Storable e => Array S ix e -> (ForeignPtr e, Int) Source #
O(1) - Yield the underlying ForeignPtr
together with its length.
Since: 0.3.0
unsafeMArrayToForeignPtr :: Storable e => MArray s S ix e -> (ForeignPtr e, Int) Source #
O(1) - Yield the underlying ForeignPtr
together with its length.
Since: 0.3.0
unsafeArrayFromForeignPtr :: Storable e => Comp -> ForeignPtr e -> Int -> Sz1 -> Array S Ix1 e Source #
O(1) - Wrap a ForeignPtr
, an offset and it's size into a pure storable array.
Since: 0.3.0
unsafeArrayFromForeignPtr0 :: Storable e => Comp -> ForeignPtr e -> Sz1 -> Array S Ix1 e Source #
O(1) - Wrap a ForeignPtr
and it's size into a pure storable array.
Since: 0.3.0
unsafeMArrayFromForeignPtr :: Storable e => ForeignPtr e -> Int -> Sz1 -> MArray s S Ix1 e Source #
O(1) - Wrap a ForeignPtr
, an offset and it's size into a mutable storable array. It is
still safe to modify the pointer, unless the array gets frozen prior to modification.
Since: 0.3.0
unsafeMArrayFromForeignPtr0 :: Storable e => ForeignPtr e -> Sz1 -> MArray s S Ix1 e Source #
O(1) - Wrap a ForeignPtr
and it's size into a mutable storable array. It is still safe to
modify the pointer, unless the array gets frozen prior to modification.
Since: 0.3.0
Atomic Operations
unsafeAtomicReadIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> m Int Source #
Atomically read an Int
element from the array
Since: 0.3.0
unsafeAtomicWriteIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m () Source #
Atomically write an Int
element int the array
Since: 0.3.0
unsafeAtomicModifyIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> (Int -> Int) -> m Int Source #
Atomically modify an Int
element of the array. Returns the old value.
Since: 0.3.0
unsafeAtomicAddIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically add to an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeAtomicSubIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically subtract from an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeAtomicAndIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically AND an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeAtomicNandIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically NAND an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeAtomicOrIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically OR an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeAtomicXorIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically XOR an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeCasIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> Int -> m Int Source #
Atomically CAS an Int
in the array. Returns the old value.
Since: 0.3.0
Other operations
unsafeBoxedArray :: Array e -> Array B Ix1 e Source #
O(n) - Cast a boxed array. It is unsafe because it violates the invariant that all
elements of N
array are in NF.
Since: 0.5.0
unsafeNormalBoxedArray :: Array B ix e -> Array N ix e Source #
O(n) - Cast a boxed array. It is unsafe because it violates the invariant that all
elements of N
array are in NF.
Since: 0.5.0
unsafeFromBoxedVector :: Vector a -> Array B Ix1 a Source #
O(n) - Cast a boxed vector without touching any elements. It is unsafe because it
violates the invariant that all elements of B
array are in WHNF.
Since: 0.5.0
unsafeUnstablePartitionRegionM Source #
:: (Mutable r Ix1 e, PrimMonad m) | |
=> MArray (PrimState m) r Ix1 e | |
-> (e -> Bool) | |
-> Ix1 | Start index of the region |
-> Ix1 | End index of the region |
-> m Ix1 |
Partition a segment of a vector. Starting and ending indices are unchecked.
Since: 0.3.2
Vector
Accessors
Indexing
Monadic Indexing
Slicing
Unbounded streams
:: Sz1 |
|
-> (s -> Maybe (e, s)) | Unfolding function. Stops when |
-> s | Inititial element. |
-> Vector DS e |
O(n) - Right unfolding function with at most n
number of elements.
Unsafe - This function is unsafe because it will allocate enough space in memory for
n
elements ahead of time, regardless of when unfolding function returns a
Nothing
. Supplying n
that is too big will result in an asynchronous
HeapOverflow
exception.
Since: 0.5.1
unsafeUnfoldrNM :: Monad m => Sz1 -> (s -> m (Maybe (e, s))) -> s -> m (Vector DS e) Source #
O(n) - Same as unsafeUnfoldrN
, but with monadic generating function.
Unsafe - This function is unsafe because it will allocate enough space in memory for
n
elements ahead of time, regardless of when unfolding function returns a
Nothing
. Supplying n
that is too big will result in an asynchronous
HeapOverflow
exception.
Since: 0.5.1
unsafeFromListN :: Sz1 -> [e] -> Vector DS e Source #
O(n) - Convert a list of a known length to a delayed stream vector.
Unsafe - This function is unsafe because it will allocate enough space in memory for
n
elements ahead of time, regardless of the actual size of the list. Supplying n
that is too big will result in an asynchronous HeapOverflow
exception.
Since: 0.5.1
Stencil
:: Index ix | |
=> Sz ix | Size of the stencil |
-> ix | Center of the stencil |
-> (ix -> (ix -> e) -> a) | Stencil function. |
-> Stencil ix e a |
Similar to makeStencil
, but there are no guarantees that the
stencil will not read out of bounds memory. This stencil is also a bit more powerful in sense it
gets an extra peice of information, namely the exact index for the element it is constructing.
Since: 0.3.0
unsafeMapStencil :: Manifest r ix e => Border e -> Sz ix -> ix -> (ix -> (ix -> e) -> a) -> Array r ix e -> Array DW ix a Source #
This is an unsafe version of mapStencil
, that does no
take Stencil
as argument, as such it does no stencil validation. There is no
performance difference between the two, but the unsafe version has an advantage of not
requiring to deal with Value
wrapper and has access to the actual index with the
array.
Since: 0.5.0
Deprecated
mapStencilUnsafe :: Manifest r ix e => Border e -> Sz ix -> ix -> ((ix -> e) -> a) -> Array r ix e -> Array DW ix a Source #
Deprecated: In favor of unsafeMapStencil
:: (Source r ix e, Manifest r ix e) | |
=> Array r ix e | |
-> Sz ix | Size of the stencil |
-> ix | Center of the stencil |
-> ((ix -> Maybe e) -> a) | Stencil function that receives a "get" function as it's argument that can retrieve values of cells in the source array with respect to the center of the stencil. Stencil function must return a value that will be assigned to the cell in the result array. Offset supplied to the "get" function cannot go outside the boundaries of the stencil. |
-> Array DW ix a |
Deprecated: In favor of unsafeMapStencil
Just as mapStencilUnsafe
this is an unsafe version of the stencil
mapping. Arguments are in slightly different order and the indexing function returns
Nothing
for elements outside the border.
Since: 0.1.7