massiv-0.3.5.0: Massiv (Массив) is an Array Library.

Copyright(c) Alexey Kuleshevich 2018-2019
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Massiv.Array.Unsafe

Contents

Description

 
Synopsis

Creation

unsafeMakeLoadArray :: Comp -> Sz ix -> Maybe e -> (forall m. Monad m => Scheduler m () -> Int -> (Int -> e -> m ()) -> m ()) -> Array DL ix e Source #

Specify how an array can be loaded/computed through creation of a DL array. Unlike makeLoadArrayS this function is unsafe since there is no guarantee that all elements will be initialized and in case of parallel scheduler there is a possibility of non-determinism.

Since: 0.3.1

Indexing

newtype Sz ix Source #

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

Constructors

SafeSz ix

Safe size constructor. It is unsafe to use it without making sure that it does not contain negative components. Use Sz pattern instead.

Since: 0.3.0

Instances
Eq ix => Eq (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

(==) :: Sz ix -> Sz ix -> Bool #

(/=) :: Sz ix -> Sz ix -> Bool #

(Num ix, Index ix) => Num (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

(+) :: Sz ix -> Sz ix -> Sz ix #

(-) :: Sz ix -> Sz ix -> Sz ix #

(*) :: Sz ix -> Sz ix -> Sz ix #

negate :: Sz ix -> Sz ix #

abs :: Sz ix -> Sz ix #

signum :: Sz ix -> Sz ix #

fromInteger :: Integer -> Sz ix #

Ord ix => Ord (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

compare :: Sz ix -> Sz ix -> Ordering #

(<) :: Sz ix -> Sz ix -> Bool #

(<=) :: Sz ix -> Sz ix -> Bool #

(>) :: Sz ix -> Sz ix -> Bool #

(>=) :: Sz ix -> Sz ix -> Bool #

max :: Sz ix -> Sz ix -> Sz ix #

min :: Sz ix -> Sz ix -> Sz ix #

Index ix => Show (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

showsPrec :: Int -> Sz ix -> ShowS #

show :: Sz ix -> String #

showList :: [Sz ix] -> ShowS #

NFData ix => NFData (Sz ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Internal

Methods

rnf :: Sz ix -> () #

newtype Stride ix Source #

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:

Expand
  • Default and minimal stride of Stride (pureIndex 1) will have no affect and all elements will kept.
  • If stride is Stride 2, 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.
  • 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).

Constructors

SafeStride ix 
Instances
Eq ix => Eq (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

(==) :: Stride ix -> Stride ix -> Bool #

(/=) :: Stride ix -> Stride ix -> Bool #

Ord ix => Ord (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

compare :: Stride ix -> Stride ix -> Ordering #

(<) :: Stride ix -> Stride ix -> Bool #

(<=) :: Stride ix -> Stride ix -> Bool #

(>) :: Stride ix -> Stride ix -> Bool #

(>=) :: Stride ix -> Stride ix -> Bool #

max :: Stride ix -> Stride ix -> Stride ix #

min :: Stride ix -> Stride ix -> Stride ix #

Index ix => Show (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

showsPrec :: Int -> Stride ix -> ShowS #

show :: Stride ix -> String #

showList :: [Stride ix] -> ShowS #

NFData ix => NFData (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

rnf :: Stride 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.

unsafeLinearIndex :: Source r ix e => Array r ix e -> Int -> e Source #

Lookup element in the array using flat index in a row-major fasion. No bounds check is performed

unsafeLinearIndexM :: Manifest r ix e => Array r ix e -> Int -> e Source #

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 (EltRepr r ix) 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

Deprecated

unsafeTraverse :: (Source r ix' e', Index ix) => Sz ix -> ((ix' -> e') -> ix -> e) -> Array r ix' e' -> Array D ix e Source #

Deprecated: In favor of more general unsafeTransform'

unsafeTraverse2 :: (Source r1 ix1 e1, Source r2 ix2 e2, Index ix) => Sz ix -> ((ix1 -> e1) -> (ix2 -> e2) -> ix -> e) -> Array r1 ix1 e1 -> Array r2 ix2 e2 -> Array D ix e Source #

Deprecated: In favor of more general unsafeTransform2'

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 #

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

unsafeRead :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> m e Source #

Read an array element

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

unsafeWrite :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> e -> m () Source #

Write an element into array

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

unsafeLinearSet :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> Int -> e -> m () Source #

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

unsafeUnstablePartitionRegionM Source #

Arguments

:: (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