massiv-1.0.2.0: Massiv (Массив) is an Array Library.
Copyright(c) Alexey Kuleshevich 2018-2022
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Massiv.Array.Unsafe

Description

 
Synopsis

Creation

unsafeMakeLoadArray Source #

Arguments

:: forall ix e. Index ix 
=> 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 s. Scheduler s () -> Ix1 -> (Ix1 -> e -> ST s ()) -> ST s ())

This function accepts:

  • A scheduler that can be used for parallelization of loading
  • Linear index at which this load array will start (an offset that should be added to the linear writng function)
  • Linear element writing function
-> 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 :: forall ix e. Index ix => Comp -> Sz ix -> Maybe e -> (forall s. Scheduler s () -> (Ix1 -> e -> ST s ()) -> ST s ()) -> 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

newtype Sz ix Source #

Sz is the size of the array. It describes total number of elements along each dimension in the array. It is a wrapper around an index of the same dimension, however it provides type safety preventing mixup with index. Moreover the Sz constructor and others such as Sz1, Sz2, ... that are specialized to specific dimensions, prevent creation of invalid sizes with negative values by clamping them to zero.

Examples

Expand
>>> import Data.Massiv.Array
>>> Sz (1 :> 2 :. 3)
Sz (1 :> 2 :. 3)

Sz has a Num instance, which is very convenient:

>>> Sz (1 :> 2 :. 3) + 5
Sz (6 :> 7 :. 8)

However subtraction can sometimes lead to surprising behavior, because size is not allowed to take negative values it will be clamped at 0.

>>> Sz (1 :> 2 :. 3) - 2
Sz (0 :> 0 :. 1)

Warning: It is always wrong to negate a size, thus it will result in an error. For that reason also watch out for partially applied (- sz), which is deugared into negate sz. See more info about it in #114.

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

Instances details
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 #

Calling negate is an error.

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 -> () #

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

Defined in Data.Massiv.Core.Index.Internal

Methods

randomR :: RandomGen g => (Sz ix, Sz ix) -> g -> (Sz ix, g) #

random :: RandomGen g => g -> (Sz ix, g) #

randomRs :: RandomGen g => (Sz ix, Sz ix) -> g -> [Sz ix] #

randoms :: RandomGen g => g -> [Sz ix] #

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

Defined in Data.Massiv.Core.Index.Internal

Methods

uniformM :: StatefulGen g m => g -> m (Sz ix) #

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

Defined in Data.Massiv.Core.Index.Internal

Methods

uniformRM :: StatefulGen g m => (Sz ix, Sz ix) -> g -> m (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).

Since: 0.2.1

Constructors

SafeStride ix 

Instances

Instances details
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 -> () #

(UniformRange ix, Index ix) => Random (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

randomR :: RandomGen g => (Stride ix, Stride ix) -> g -> (Stride ix, g) #

random :: RandomGen g => g -> (Stride ix, g) #

randomRs :: RandomGen g => (Stride ix, Stride ix) -> g -> [Stride ix] #

randoms :: RandomGen g => g -> [Stride ix] #

(UniformRange ix, Index ix) => Uniform (Stride ix) Source # 
Instance details

Defined in Data.Massiv.Core.Index.Stride

Methods

uniformM :: StatefulGen g m => g -> m (Stride ix) #

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

Defined in Data.Massiv.Core.Index.Stride

Methods

uniformRM :: StatefulGen g m => (Stride ix, Stride ix) -> g -> m (Stride ix) #

unsafeIndex :: (Source r e, Index ix) => 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 e, Index ix) => 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

unsafeLinearIndexM :: (Manifest r e, Index ix) => Array r ix e -> Int -> e Source #

Manipulations

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

unsafeResize :: (Size r, Index 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.

Since: 0.1.0

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

O(1) - Extract a portion of an array. Staring index and new size are not validated.

unsafeTransform :: (Index ix', Source r' 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 :: (Index ix1, Source r1 e1, Index ix2, Source r2 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 :: (Source r e, Index ix, Index (Lower ix), MonadThrow m) => Array r ix e -> ix -> Sz ix -> Dim -> m (Array D (Lower ix) e) Source #

O(1) - Take a slice out of an array from within

unsafeOuterSlice :: (Source r e, Index ix, Index (Lower ix)) => Array r ix e -> Sz (Lower ix) -> Int -> Array r (Lower ix) e Source #

O(1) - Take a slice out of an array from the outside

Since: 0.1.0

unsafeInnerSlice :: (Source r e, Index ix) => Array r ix e -> Sz (Lower ix) -> Int -> Array D (Lower ix) e Source #

O(1) - Take a slice out of an array from the inside

unsafeLinearSlice :: (Source r e, Index ix) => 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

unsafeResizeMArray :: (Manifest r e, Index ix', Index ix) => Sz ix' -> MArray s r ix e -> MArray s r ix' e Source #

O(1) - Change the size of a mutable array. The actual number of elements should stay the same.

Since: 1.0.0

unsafeLinearSliceMArray :: (Manifest r e, Index ix) => Ix1 -> Sz1 -> MArray s r ix e -> MVector s r e Source #

O(1) - Take a linear slice out of a mutable array.

Since: 1.0.0

unsafeThaw :: (Manifest r e, Index ix, 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 :: (Manifest r e, Index ix, 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 :: (Manifest r e, Index ix, 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

unsafeLoadIntoST :: (Load r ix e, Manifest r' e) => MVector s r' e -> Array r ix e -> ST s (MArray s r' ix e) Source #

Load into a supplied mutable array sequentially. Returned array does not have to be the same.

Since: 1.0.0

unsafeLoadIntoIO :: (Load r ix e, Manifest r' e) => MVector RealWorld r' e -> Array r ix e -> IO (MArray RealWorld r' ix e) Source #

Same as unsafeLoadIntoST, but respecting computation strategy.

Since: 1.0.0

unsafeLoadIntoS :: forall r r' ix e m s. (Load r ix e, Manifest r' e, MonadPrim s m) => MVector s r' e -> Array r ix e -> m (MArray s r' ix e) Source #

Load into a supplied mutable vector sequentially. Returned array is not necesserally the same vector as the one that was supplied. It will be the same only if it had enough space to load all the elements in.

Since: 0.5.7

unsafeLoadIntoM :: forall r r' ix e m. (Load r ix e, Manifest r' e, MonadIO m) => MVector RealWorld r' e -> Array r ix e -> m (MArray RealWorld r' ix e) Source #

Same as unsafeLoadIntoS, but respecting computation strategy.

Since: 0.5.7

unsafeCreateArray Source #

Arguments

:: forall r ix e a m b. (Manifest r e, Index ix, MonadUnliftIO m) 
=> Comp

Computation strategy to use after MArray gets frozen and onward.

-> Sz ix

Size of the newly created array

-> (Scheduler RealWorld a -> MArray RealWorld 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

unsafeCreateArray_ Source #

Arguments

:: forall r ix e a m b. (Manifest r e, Index ix, MonadUnliftIO m) 
=> Comp

Computation strategy to use after MArray gets frozen and onward.

-> Sz ix

Size of the newly created array

-> (Scheduler RealWorld a -> MArray RealWorld 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

unsafeCreateArrayS Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, 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 :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> m e Source #

Read an array element

Since: 0.1.0

unsafeLinearRead :: (Manifest r e, Index ix, 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 :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> e -> m () Source #

Write an element into array

Since: 0.1.0

unsafeLinearWrite :: (Manifest r e, Index ix, 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 :: (Manifest r e, Index ix, 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 :: (Manifest r e, Index ix, 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 :: (Manifest r e, Index ix, 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 :: (Manifest r e, Index ix, 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 :: (Manifest r e, Index ix, 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

unsafeLinearCopy Source #

Arguments

:: (Manifest r e, Index ix', Index ix, 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 #

Arguments

:: (Manifest r e, Index ix', Index ix, 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 :: (Manifest r e, Index ix, 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 :: (Manifest r e, Index ix, 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

unsafeMallocMArray :: forall ix e m. (Index ix, Storable e, PrimMonad m) => Sz ix -> m (MArray (PrimState m) S ix e) Source #

Allocate memory using malloc on C heap, instead of on Haskell heap. Memory is left uninitialized

Since: 0.5.9

unsafeWithPtr :: MonadUnliftIO m => Array S ix e -> (Ptr e -> 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 :: Index ix => Array S ix e -> (ForeignPtr e, Int) Source #

O(1) - Yield the underlying ForeignPtr together with its length.

Since: 0.3.0

unsafeMArrayToForeignPtr :: Index ix => 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 :: Comp -> ForeignPtr e -> Sz1 -> Vector S 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 :: 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

coerceBoxedArray :: Array BL ix e -> Array B ix e Source #

O(1) - Cast a boxed lazy array. It is unsafe because it can violate the invariant that all elements of B array are in WHNF.

Since: 0.6.0

coerceNormalBoxedArray :: Array BL ix e -> Array N ix e Source #

O(1) - Cast a boxed lazy array. It is unsafe because it can violate the invariant that all elements of N array are in NF.

Since: 0.6.0

unsafeUnstablePartitionRegionM Source #

Arguments

:: forall r e m. (Manifest r e, PrimMonad m) 
=> MVector (PrimState m) r e 
-> (e -> m 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: 1.0.0

Vector

Accessors

Indexing

unsafeHead :: Source r e => Vector r e -> e Source #

Since: 0.5.0

unsafeLast :: Source r e => Vector r e -> e Source #

Since: 0.5.0

Monadic Indexing

unsafeIndexM :: (Source r e, Monad m) => Vector r e -> Ix1 -> m e Source #

Since: 0.5.0

unsafeHeadM :: (Monad m, Source r e) => Vector r e -> m e Source #

Since: 0.5.0

unsafeLastM :: (Monad m, Source r e) => Vector r e -> m e Source #

Since: 0.5.0

Slicing

unsafeInit :: Source r e => Vector r e -> Vector r e Source #

Since: 0.5.0

unsafeTail :: Source r e => Vector r e -> Vector r e Source #

Since: 0.5.0

unsafeTake :: Source r e => Sz1 -> Vector r e -> Vector r e Source #

Since: 0.5.0

unsafeDrop :: Source r e => Sz1 -> Vector r e -> Vector r e Source #

Since: 0.5.0

Unbounded streams

unsafeUnfoldrN Source #

Arguments

:: Sz1

n - maximum number of elements that the vector will have

-> (s -> Maybe (e, s))

Unfolding function. Stops when Nothing is returned or maximum number of elements is reached.

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

makeUnsafeStencil Source #

Arguments

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

makeUnsafeConvolutionStencil :: (Index ix, Num e) => Sz ix -> ix -> ((ix -> e -> e -> e) -> e -> e) -> Stencil ix e e Source #

Same as makeConvolutionStencil, but will result in reading memory out of bounds and potential segfaults if supplied arguments are not valid.

Since: 0.6.0

makeUnsafeCorrelationStencil :: (Index ix, Num e) => Sz ix -> ix -> ((ix -> e -> e -> e) -> e -> e) -> Stencil ix e e Source #

Same as makeCorrelationStencil, but will result in reading memory out of bounds and potential segfaults if supplied arguments are not valid.

Since: 0.6.0

unsafeTransformStencil Source #

Arguments

:: (Sz ix' -> Sz ix)

Forward modifier for the size

-> (ix' -> ix)

Forward index modifier

-> (((ix' -> e) -> (ix' -> e) -> ix' -> a) -> (ix -> e) -> (ix -> e) -> ix -> a)

Inverse stencil function modifier

-> Stencil ix' e a

Original stencil.

-> Stencil ix e a 

Perform an arbitrary transformation of a stencil. This stencil modifier can be used for example to turn a vector stencil into a matrix stencil implement, or transpose a matrix stencil. It is really easy to get this wrong, so be extremely careful.

Examples

Expand

Convert a 1D stencil into a row or column 2D stencil:

>>> import Data.Massiv.Array
>>> import Data.Massiv.Array.Unsafe
>>> let arr = compute $ iterateN 3 succ 0 :: Array P Ix2 Int
>>> arr
Array P Seq (Sz (3 :. 3))
  [ [ 1, 2, 3 ]
  , [ 4, 5, 6 ]
  , [ 7, 8, 9 ]
  ]
>>> let rowStencil = unsafeTransformStencil (\(Sz n) -> Sz (1 :. n)) (0 :.) $ \ f uget getVal (i :. j) -> f (uget  . (i :.)) (getVal . (i :.)) j
>>> applyStencil noPadding (rowStencil (sumStencil (Sz1 3))) arr
Array DW Seq (Sz (3 :. 1))
  [ [ 6 ]
  , [ 15 ]
  , [ 24 ]
  ]
>>> let columnStencil = unsafeTransformStencil (\(Sz n) -> Sz (n :. 1)) (:. 0) $ \ f uget getVal (i :. j) -> f (uget . (:. j)) (getVal . (:. j)) i
>>> applyStencil noPadding (columnStencil (sumStencil (Sz1 3))) arr
Array DW Seq (Sz (1 :. 3))
  [ [ 12, 15, 18 ]
  ]

Since: 0.5.4

Constructors

data family Array r ix e :: Type Source #

The array family. Representations r describe how data is arranged or computed. All arrays have a common property that each index ix always maps to the same unique element e, even if that element does not yet exist in memory and the array has to be computed in order to get the value of that element. Data is always arranged in a nested row-major fashion. Rank of an array is specified by Dimensions ix.

Since: 0.1.0

Instances

Instances details
Monad (Array DS Ix1) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

(>>=) :: Array DS Ix1 a -> (a -> Array DS Ix1 b) -> Array DS Ix1 b #

(>>) :: Array DS Ix1 a -> Array DS Ix1 b -> Array DS Ix1 b #

return :: a -> Array DS Ix1 a #

Index ix => Functor (Array DL ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

Methods

fmap :: (a -> b) -> Array DL ix a -> Array DL ix b #

(<$) :: a -> Array DL ix b -> Array DL ix a #

Functor (Array D ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

fmap :: (a -> b) -> Array D ix a -> Array D ix b #

(<$) :: a -> Array D ix b -> Array D ix a #

Functor (Array DS Ix1) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

fmap :: (a -> b) -> Array DS Ix1 a -> Array DS Ix1 b #

(<$) :: a -> Array DS Ix1 b -> Array DS Ix1 a #

Index ix => Functor (Array B ix) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

fmap :: (a -> b) -> Array B ix a -> Array B ix b #

(<$) :: a -> Array B ix b -> Array B ix a #

Index ix => Functor (Array BL ix) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

fmap :: (a -> b) -> Array BL ix a -> Array BL ix b #

(<$) :: a -> Array BL ix b -> Array BL ix a #

Functor (Array DW ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

fmap :: (a -> b) -> Array DW ix a -> Array DW ix b #

(<$) :: a -> Array DW ix b -> Array DW ix a #

Functor (Array DI ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

fmap :: (a -> b) -> Array DI ix a -> Array DI ix b #

(<$) :: a -> Array DI ix b -> Array DI ix a #

Index ix => Applicative (Array D ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

pure :: a -> Array D ix a #

(<*>) :: Array D ix (a -> b) -> Array D ix a -> Array D ix b #

liftA2 :: (a -> b -> c) -> Array D ix a -> Array D ix b -> Array D ix c #

(*>) :: Array D ix a -> Array D ix b -> Array D ix b #

(<*) :: Array D ix a -> Array D ix b -> Array D ix a #

Applicative (Array DS Ix1) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

pure :: a -> Array DS Ix1 a #

(<*>) :: Array DS Ix1 (a -> b) -> Array DS Ix1 a -> Array DS Ix1 b #

liftA2 :: (a -> b -> c) -> Array DS Ix1 a -> Array DS Ix1 b -> Array DS Ix1 c #

(*>) :: Array DS Ix1 a -> Array DS Ix1 b -> Array DS Ix1 b #

(<*) :: Array DS Ix1 a -> Array DS Ix1 b -> Array DS Ix1 a #

Index ix => Applicative (Array DI ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

pure :: a -> Array DI ix a #

(<*>) :: Array DI ix (a -> b) -> Array DI ix a -> Array DI ix b #

liftA2 :: (a -> b -> c) -> Array DI ix a -> Array DI ix b -> Array DI ix c #

(*>) :: Array DI ix a -> Array DI ix b -> Array DI ix b #

(<*) :: Array DI ix a -> Array DI ix b -> Array DI ix a #

Index ix => Foldable (Array D ix) Source #

Row-major sequential folding over a Delayed array.

Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

fold :: Monoid m => Array D ix m -> m #

foldMap :: Monoid m => (a -> m) -> Array D ix a -> m #

foldMap' :: Monoid m => (a -> m) -> Array D ix a -> m #

foldr :: (a -> b -> b) -> b -> Array D ix a -> b #

foldr' :: (a -> b -> b) -> b -> Array D ix a -> b #

foldl :: (b -> a -> b) -> b -> Array D ix a -> b #

foldl' :: (b -> a -> b) -> b -> Array D ix a -> b #

foldr1 :: (a -> a -> a) -> Array D ix a -> a #

foldl1 :: (a -> a -> a) -> Array D ix a -> a #

toList :: Array D ix a -> [a] #

null :: Array D ix a -> Bool #

length :: Array D ix a -> Int #

elem :: Eq a => a -> Array D ix a -> Bool #

maximum :: Ord a => Array D ix a -> a #

minimum :: Ord a => Array D ix a -> a #

sum :: Num a => Array D ix a -> a #

product :: Num a => Array D ix a -> a #

Foldable (Array DS Ix1) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

fold :: Monoid m => Array DS Ix1 m -> m #

foldMap :: Monoid m => (a -> m) -> Array DS Ix1 a -> m #

foldMap' :: Monoid m => (a -> m) -> Array DS Ix1 a -> m #

foldr :: (a -> b -> b) -> b -> Array DS Ix1 a -> b #

foldr' :: (a -> b -> b) -> b -> Array DS Ix1 a -> b #

foldl :: (b -> a -> b) -> b -> Array DS Ix1 a -> b #

foldl' :: (b -> a -> b) -> b -> Array DS Ix1 a -> b #

foldr1 :: (a -> a -> a) -> Array DS Ix1 a -> a #

foldl1 :: (a -> a -> a) -> Array DS Ix1 a -> a #

toList :: Array DS Ix1 a -> [a] #

null :: Array DS Ix1 a -> Bool #

length :: Array DS Ix1 a -> Int #

elem :: Eq a => a -> Array DS Ix1 a -> Bool #

maximum :: Ord a => Array DS Ix1 a -> a #

minimum :: Ord a => Array DS Ix1 a -> a #

sum :: Num a => Array DS Ix1 a -> a #

product :: Num a => Array DS Ix1 a -> a #

Index ix => Foldable (Array B ix) Source #

Row-major sequential folding over a Boxed array.

Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

fold :: Monoid m => Array B ix m -> m #

foldMap :: Monoid m => (a -> m) -> Array B ix a -> m #

foldMap' :: Monoid m => (a -> m) -> Array B ix a -> m #

foldr :: (a -> b -> b) -> b -> Array B ix a -> b #

foldr' :: (a -> b -> b) -> b -> Array B ix a -> b #

foldl :: (b -> a -> b) -> b -> Array B ix a -> b #

foldl' :: (b -> a -> b) -> b -> Array B ix a -> b #

foldr1 :: (a -> a -> a) -> Array B ix a -> a #

foldl1 :: (a -> a -> a) -> Array B ix a -> a #

toList :: Array B ix a -> [a] #

null :: Array B ix a -> Bool #

length :: Array B ix a -> Int #

elem :: Eq a => a -> Array B ix a -> Bool #

maximum :: Ord a => Array B ix a -> a #

minimum :: Ord a => Array B ix a -> a #

sum :: Num a => Array B ix a -> a #

product :: Num a => Array B ix a -> a #

Index ix => Foldable (Array BL ix) Source #

Row-major sequential folding over a Boxed array.

Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

fold :: Monoid m => Array BL ix m -> m #

foldMap :: Monoid m => (a -> m) -> Array BL ix a -> m #

foldMap' :: Monoid m => (a -> m) -> Array BL ix a -> m #

foldr :: (a -> b -> b) -> b -> Array BL ix a -> b #

foldr' :: (a -> b -> b) -> b -> Array BL ix a -> b #

foldl :: (b -> a -> b) -> b -> Array BL ix a -> b #

foldl' :: (b -> a -> b) -> b -> Array BL ix a -> b #

foldr1 :: (a -> a -> a) -> Array BL ix a -> a #

foldl1 :: (a -> a -> a) -> Array BL ix a -> a #

toList :: Array BL ix a -> [a] #

null :: Array BL ix a -> Bool #

length :: Array BL ix a -> Int #

elem :: Eq a => a -> Array BL ix a -> Bool #

maximum :: Ord a => Array BL ix a -> a #

minimum :: Ord a => Array BL ix a -> a #

sum :: Num a => Array BL ix a -> a #

product :: Num a => Array BL ix a -> a #

Index ix => Foldable (Array DI ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

fold :: Monoid m => Array DI ix m -> m #

foldMap :: Monoid m => (a -> m) -> Array DI ix a -> m #

foldMap' :: Monoid m => (a -> m) -> Array DI ix a -> m #

foldr :: (a -> b -> b) -> b -> Array DI ix a -> b #

foldr' :: (a -> b -> b) -> b -> Array DI ix a -> b #

foldl :: (b -> a -> b) -> b -> Array DI ix a -> b #

foldl' :: (b -> a -> b) -> b -> Array DI ix a -> b #

foldr1 :: (a -> a -> a) -> Array DI ix a -> a #

foldl1 :: (a -> a -> a) -> Array DI ix a -> a #

toList :: Array DI ix a -> [a] #

null :: Array DI ix a -> Bool #

length :: Array DI ix a -> Int #

elem :: Eq a => a -> Array DI ix a -> Bool #

maximum :: Ord a => Array DI ix a -> a #

minimum :: Ord a => Array DI ix a -> a #

sum :: Num a => Array DI ix a -> a #

product :: Num a => Array DI ix a -> a #

Index ix => Traversable (Array B ix) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

traverse :: Applicative f => (a -> f b) -> Array B ix a -> f (Array B ix b) #

sequenceA :: Applicative f => Array B ix (f a) -> f (Array B ix a) #

mapM :: Monad m => (a -> m b) -> Array B ix a -> m (Array B ix b) #

sequence :: Monad m => Array B ix (m a) -> m (Array B ix a) #

Index ix => Traversable (Array BL ix) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

traverse :: Applicative f => (a -> f b) -> Array BL ix a -> f (Array BL ix b) #

sequenceA :: Applicative f => Array BL ix (f a) -> f (Array BL ix a) #

mapM :: Monad m => (a -> m b) -> Array BL ix a -> m (Array BL ix b) #

sequence :: Monad m => Array BL ix (m a) -> m (Array BL ix a) #

Coercible (Elt ix e) (ListItem ix e) => IsList (Array L ix e) Source # 
Instance details

Defined in Data.Massiv.Core.List

Associated Types

type Item (Array L ix e) #

Methods

fromList :: [Item (Array L ix e)] -> Array L ix e #

fromListN :: Int -> [Item (Array L ix e)] -> Array L ix e #

toList :: Array L ix e -> [Item (Array L ix e)] #

(Unbox e, IsList (Array L ix e), Ragged L ix e) => IsList (Array U ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Associated Types

type Item (Array U ix e) #

Methods

fromList :: [Item (Array U ix e)] -> Array U ix e #

fromListN :: Int -> [Item (Array U ix e)] -> Array U ix e #

toList :: Array U ix e -> [Item (Array U ix e)] #

(Storable e, IsList (Array L ix e), Ragged L ix e) => IsList (Array S ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Associated Types

type Item (Array S ix e) #

Methods

fromList :: [Item (Array S ix e)] -> Array S ix e #

fromListN :: Int -> [Item (Array S ix e)] -> Array S ix e #

toList :: Array S ix e -> [Item (Array S ix e)] #

(Prim e, IsList (Array L ix e), Ragged L ix e) => IsList (Array P ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Associated Types

type Item (Array P ix e) #

Methods

fromList :: [Item (Array P ix e)] -> Array P ix e #

fromListN :: Int -> [Item (Array P ix e)] -> Array P ix e #

toList :: Array P ix e -> [Item (Array P ix e)] #

IsList (Array DS Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Associated Types

type Item (Array DS Ix1 e) #

Methods

fromList :: [Item (Array DS Ix1 e)] -> Array DS Ix1 e #

fromListN :: Int -> [Item (Array DS Ix1 e)] -> Array DS Ix1 e #

toList :: Array DS Ix1 e -> [Item (Array DS Ix1 e)] #

(NFData e, IsList (Array L ix e), Ragged L ix e) => IsList (Array BN ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Associated Types

type Item (Array BN ix e) #

Methods

fromList :: [Item (Array BN ix e)] -> Array BN ix e #

fromListN :: Int -> [Item (Array BN ix e)] -> Array BN ix e #

toList :: Array BN ix e -> [Item (Array BN ix e)] #

(IsList (Array L ix e), Ragged L ix e) => IsList (Array B ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Associated Types

type Item (Array B ix e) #

Methods

fromList :: [Item (Array B ix e)] -> Array B ix e #

fromListN :: Int -> [Item (Array B ix e)] -> Array B ix e #

toList :: Array B ix e -> [Item (Array B ix e)] #

(IsList (Array L ix e), Ragged L ix e) => IsList (Array BL ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Associated Types

type Item (Array BL ix e) #

Methods

fromList :: [Item (Array BL ix e)] -> Array BL ix e #

fromListN :: Int -> [Item (Array BL ix e)] -> Array BL ix e #

toList :: Array BL ix e -> [Item (Array BL ix e)] #

(Eq e, Index ix) => Eq (Array D ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

(==) :: Array D ix e -> Array D ix e -> Bool #

(/=) :: Array D ix e -> Array D ix e -> Bool #

(Unbox e, Eq e, Index ix) => Eq (Array U ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

(==) :: Array U ix e -> Array U ix e -> Bool #

(/=) :: Array U ix e -> Array U ix e -> Bool #

(Storable e, Eq e, Index ix) => Eq (Array S ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

(==) :: Array S ix e -> Array S ix e -> Bool #

(/=) :: Array S ix e -> Array S ix e -> Bool #

(Prim e, Eq e, Index ix) => Eq (Array P ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

(==) :: Array P ix e -> Array P ix e -> Bool #

(/=) :: Array P ix e -> Array P ix e -> Bool #

(Index ix, NFData e, Eq e) => Eq (Array BN ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

(==) :: Array BN ix e -> Array BN ix e -> Bool #

(/=) :: Array BN ix e -> Array BN ix e -> Bool #

(Index ix, Eq e) => Eq (Array B ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

(==) :: Array B ix e -> Array B ix e -> Bool #

(/=) :: Array B ix e -> Array B ix e -> Bool #

(Index ix, Eq e) => Eq (Array BL ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

(==) :: Array BL ix e -> Array BL ix e -> Bool #

(/=) :: Array BL ix e -> Array BL ix e -> Bool #

(Index ix, Eq e) => Eq (Array DI ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

(==) :: Array DI ix e -> Array DI ix e -> Bool #

(/=) :: Array DI ix e -> Array DI ix e -> Bool #

(Ord e, Index ix) => Ord (Array D ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

compare :: Array D ix e -> Array D ix e -> Ordering #

(<) :: Array D ix e -> Array D ix e -> Bool #

(<=) :: Array D ix e -> Array D ix e -> Bool #

(>) :: Array D ix e -> Array D ix e -> Bool #

(>=) :: Array D ix e -> Array D ix e -> Bool #

max :: Array D ix e -> Array D ix e -> Array D ix e #

min :: Array D ix e -> Array D ix e -> Array D ix e #

(Unbox e, Ord e, Index ix) => Ord (Array U ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

compare :: Array U ix e -> Array U ix e -> Ordering #

(<) :: Array U ix e -> Array U ix e -> Bool #

(<=) :: Array U ix e -> Array U ix e -> Bool #

(>) :: Array U ix e -> Array U ix e -> Bool #

(>=) :: Array U ix e -> Array U ix e -> Bool #

max :: Array U ix e -> Array U ix e -> Array U ix e #

min :: Array U ix e -> Array U ix e -> Array U ix e #

(Storable e, Ord e, Index ix) => Ord (Array S ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

compare :: Array S ix e -> Array S ix e -> Ordering #

(<) :: Array S ix e -> Array S ix e -> Bool #

(<=) :: Array S ix e -> Array S ix e -> Bool #

(>) :: Array S ix e -> Array S ix e -> Bool #

(>=) :: Array S ix e -> Array S ix e -> Bool #

max :: Array S ix e -> Array S ix e -> Array S ix e #

min :: Array S ix e -> Array S ix e -> Array S ix e #

(Prim e, Ord e, Index ix) => Ord (Array P ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

compare :: Array P ix e -> Array P ix e -> Ordering #

(<) :: Array P ix e -> Array P ix e -> Bool #

(<=) :: Array P ix e -> Array P ix e -> Bool #

(>) :: Array P ix e -> Array P ix e -> Bool #

(>=) :: Array P ix e -> Array P ix e -> Bool #

max :: Array P ix e -> Array P ix e -> Array P ix e #

min :: Array P ix e -> Array P ix e -> Array P ix e #

(Index ix, NFData e, Ord e) => Ord (Array BN ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

compare :: Array BN ix e -> Array BN ix e -> Ordering #

(<) :: Array BN ix e -> Array BN ix e -> Bool #

(<=) :: Array BN ix e -> Array BN ix e -> Bool #

(>) :: Array BN ix e -> Array BN ix e -> Bool #

(>=) :: Array BN ix e -> Array BN ix e -> Bool #

max :: Array BN ix e -> Array BN ix e -> Array BN ix e #

min :: Array BN ix e -> Array BN ix e -> Array BN ix e #

(Index ix, Ord e) => Ord (Array B ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

compare :: Array B ix e -> Array B ix e -> Ordering #

(<) :: Array B ix e -> Array B ix e -> Bool #

(<=) :: Array B ix e -> Array B ix e -> Bool #

(>) :: Array B ix e -> Array B ix e -> Bool #

(>=) :: Array B ix e -> Array B ix e -> Bool #

max :: Array B ix e -> Array B ix e -> Array B ix e #

min :: Array B ix e -> Array B ix e -> Array B ix e #

(Index ix, Ord e) => Ord (Array BL ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

compare :: Array BL ix e -> Array BL ix e -> Ordering #

(<) :: Array BL ix e -> Array BL ix e -> Bool #

(<=) :: Array BL ix e -> Array BL ix e -> Bool #

(>) :: Array BL ix e -> Array BL ix e -> Bool #

(>=) :: Array BL ix e -> Array BL ix e -> Bool #

max :: Array BL ix e -> Array BL ix e -> Array BL ix e #

min :: Array BL ix e -> Array BL ix e -> Array BL ix e #

(Index ix, Ord e) => Ord (Array DI ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

compare :: Array DI ix e -> Array DI ix e -> Ordering #

(<) :: Array DI ix e -> Array DI ix e -> Bool #

(<=) :: Array DI ix e -> Array DI ix e -> Bool #

(>) :: Array DI ix e -> Array DI ix e -> Bool #

(>=) :: Array DI ix e -> Array DI ix e -> Bool #

max :: Array DI ix e -> Array DI ix e -> Array DI ix e #

min :: Array DI ix e -> Array DI ix e -> Array DI ix e #

(Ragged L ix e, Show e) => Show (Array DL ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

showsPrec :: Int -> Array DL ix e -> ShowS #

show :: Array DL ix e -> String #

showList :: [Array DL ix e] -> ShowS #

(Ragged L ix e, Show e) => Show (Array L ix e) Source # 
Instance details

Defined in Data.Massiv.Core.List

Methods

showsPrec :: Int -> Array L ix e -> ShowS #

show :: Array L ix e -> String #

showList :: [Array L ix e] -> ShowS #

(Ragged L ix e, Show e) => Show (Array D ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

showsPrec :: Int -> Array D ix e -> ShowS #

show :: Array D ix e -> String #

showList :: [Array D ix e] -> ShowS #

(Ragged L ix e, Show e, Unbox e) => Show (Array U ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

showsPrec :: Int -> Array U ix e -> ShowS #

show :: Array U ix e -> String #

showList :: [Array U ix e] -> ShowS #

(Ragged L ix e, Show e, Storable e) => Show (Array S ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

showsPrec :: Int -> Array S ix e -> ShowS #

show :: Array S ix e -> String #

showList :: [Array S ix e] -> ShowS #

(Ragged L ix e, Show e, Prim e) => Show (Array P ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

showsPrec :: Int -> Array P ix e -> ShowS #

show :: Array P ix e -> String #

showList :: [Array P ix e] -> ShowS #

Show e => Show (Array DS Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

showsPrec :: Int -> Array DS Ix1 e -> ShowS #

show :: Array DS Ix1 e -> String #

showList :: [Array DS Ix1 e] -> ShowS #

(Ragged L ix e, Show e, NFData e) => Show (Array BN ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

showsPrec :: Int -> Array BN ix e -> ShowS #

show :: Array BN ix e -> String #

showList :: [Array BN ix e] -> ShowS #

(Ragged L ix e, Show e) => Show (Array B ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

showsPrec :: Int -> Array B ix e -> ShowS #

show :: Array B ix e -> String #

showList :: [Array B ix e] -> ShowS #

(Ragged L ix e, Show e) => Show (Array BL ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

showsPrec :: Int -> Array BL ix e -> ShowS #

show :: Array BL ix e -> String #

showList :: [Array BL ix e] -> ShowS #

(Ragged L ix e, Load DW ix e, Show e) => Show (Array DW ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

showsPrec :: Int -> Array DW ix e -> ShowS #

show :: Array DW ix e -> String #

showList :: [Array DW ix e] -> ShowS #

(Ragged L ix e, Show e) => Show (Array DI ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

showsPrec :: Int -> Array DI ix e -> ShowS #

show :: Array DI ix e -> String #

showList :: [Array DI ix e] -> ShowS #

Semigroup (Array DL Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

Methods

(<>) :: Array DL Ix1 e -> Array DL Ix1 e -> Array DL Ix1 e #

sconcat :: NonEmpty (Array DL Ix1 e) -> Array DL Ix1 e #

stimes :: Integral b => b -> Array DL Ix1 e -> Array DL Ix1 e #

Semigroup (Array DS Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

(<>) :: Array DS Ix1 e -> Array DS Ix1 e -> Array DS Ix1 e #

sconcat :: NonEmpty (Array DS Ix1 e) -> Array DS Ix1 e #

stimes :: Integral b => b -> Array DS Ix1 e -> Array DS Ix1 e #

Monoid (Array DL Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

Methods

mempty :: Array DL Ix1 e #

mappend :: Array DL Ix1 e -> Array DL Ix1 e -> Array DL Ix1 e #

mconcat :: [Array DL Ix1 e] -> Array DL Ix1 e #

Monoid (Array DS Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

mempty :: Array DS Ix1 e #

mappend :: Array DS Ix1 e -> Array DS Ix1 e -> Array DS Ix1 e #

mconcat :: [Array DS Ix1 e] -> Array DS Ix1 e #

NFData ix => NFData (Array U ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

rnf :: Array U ix e -> () #

NFData ix => NFData (Array S ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

rnf :: Array S ix e -> () #

Index ix => NFData (Array P ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

rnf :: Array P ix e -> () #

NFData (Array BN ix e) Source #

O(1) - BN is already in normal form

Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

rnf :: Array BN ix e -> () #

(Index ix, NFData e) => NFData (Array B ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

rnf :: Array B ix e -> () #

(Index ix, NFData e) => NFData (Array BL ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

rnf :: Array BL ix e -> () #

data Array DL ix e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

data Array DL ix e = DLArray {}
data Array L ix e Source # 
Instance details

Defined in Data.Massiv.Core.List

data Array L ix e = LArray {}
data Array D ix e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

data Array D ix e = DArray {}
data Array U ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

data Array U ix e = UArray {}
data Array S ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

data Array S ix e = SArray {}
data Array P ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

data Array P ix e = PArray {}
newtype Array BN ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

newtype Array BN ix e = BNArray (Array BL ix e)
newtype Array B ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

newtype Array B ix e = BArray (Array BL ix e)
data Array BL ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

data Array BL ix e = BLArray {}
data Array DW ix e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

data Array DW ix e = DWArray {}
newtype Array DI ix e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

newtype Array DI ix e = DIArray {}
newtype Array DS Ix1 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

newtype Array DS Ix1 e = DSArray {}
type Item (Array L ix e) Source # 
Instance details

Defined in Data.Massiv.Core.List

type Item (Array L ix e) = ListItem ix e
type Item (Array U ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

type Item (Array U ix e) = Item (Array L ix e)
type Item (Array S ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

type Item (Array S ix e) = Item (Array L ix e)
type Item (Array P ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

type Item (Array P ix e) = Item (Array L ix e)
type Item (Array DS Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

type Item (Array DS Ix1 e) = e
type Item (Array BN ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

type Item (Array BN ix e) = Item (Array L ix e)
type Item (Array B ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

type Item (Array B ix e) = Item (Array L ix e)
type Item (Array BL ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

type Item (Array BL ix e) = Item (Array L ix e)

data family MArray s r ix e :: Type Source #

Mutable version of a Manifest Array. The extra type argument s is for the state token used by IO and ST.

Since: 0.1.0

Instances

Instances details
NFData ix => NFData (MArray s U ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

rnf :: MArray s U ix e -> () #

NFData ix => NFData (MArray s S ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

rnf :: MArray s S ix e -> () #

NFData ix => NFData (MArray s P ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

rnf :: MArray s P ix e -> () #

data MArray s U ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

data MArray s U ix e = MUArray !(Sz ix) !(MVector s e)
data MArray s S ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

data MArray s S ix e = MSArray !(Sz ix) !(ForeignPtr e)
data MArray s P ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

data MArray s P ix e = MPArray !(Sz ix) !Int !(MutableByteArray s)
data MArray s BL ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

data MArray s BL ix e = MBLArray !(Sz ix) !Int !(MutableArray s e)
newtype MArray s B ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

newtype MArray s B ix e = MBArray (MArray s BL ix e)
newtype MArray s BN ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

newtype MArray s BN ix e = MBNArray (MArray s BL ix e)