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

Data.Massiv.Array.Manifest

Description

 
Synopsis

Manifest

class Source r e => Manifest r e Source #

Manifest arrays are backed by actual memory and values are looked up versus computed as it is with delayed arrays. Because manifest arrays are located in memory their contents can be mutated once thawed into MArray. The process of changed a mutable MArray back into an immutable Array is called freezing.

Instances

Instances details
Manifest B e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeLinearIndexM :: Index ix => Array B ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s B ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s B ix e -> MVector s B e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array B ix e -> m (MArray (PrimState m) B ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) B ix e -> m (Array B ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) B ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) B ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) B ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) B ix' e -> Ix1 -> MArray (PrimState m) B ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array B ix' e -> Ix1 -> MArray (PrimState m) B ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Sz ix -> m (MArray (PrimState m) B ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Sz ix -> m (MArray (PrimState m) B ix e) Source #

Manifest BL e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeLinearIndexM :: Index ix => Array BL ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s BL ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s BL ix e -> MVector s BL e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array BL ix e -> m (MArray (PrimState m) BL ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) BL ix e -> m (Array BL ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) BL ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) BL ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) BL ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) BL ix' e -> Ix1 -> MArray (PrimState m) BL ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array BL ix' e -> Ix1 -> MArray (PrimState m) BL ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Sz ix -> m (MArray (PrimState m) BL ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Sz ix -> m (MArray (PrimState m) BL ix e) Source #

NFData e => Manifest BN e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeLinearIndexM :: Index ix => Array BN ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s BN ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s BN ix e -> MVector s BN e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array BN ix e -> m (MArray (PrimState m) BN ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) BN ix e -> m (Array BN ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) BN ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) BN ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) BN ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) BN ix' e -> Ix1 -> MArray (PrimState m) BN ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array BN ix' e -> Ix1 -> MArray (PrimState m) BN ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Sz ix -> m (MArray (PrimState m) BN ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Sz ix -> m (MArray (PrimState m) BN ix e) Source #

Prim e => Manifest P e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

unsafeLinearIndexM :: Index ix => Array P ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s P ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s P ix e -> MVector s P e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array P ix e -> m (MArray (PrimState m) P ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) P ix e -> m (Array P ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) P ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) P ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) P ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) P ix' e -> Ix1 -> MArray (PrimState m) P ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array P ix' e -> Ix1 -> MArray (PrimState m) P ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Sz ix -> m (MArray (PrimState m) P ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Sz ix -> m (MArray (PrimState m) P ix e) Source #

Storable e => Manifest S e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

unsafeLinearIndexM :: Index ix => Array S ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s S ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s S ix e -> MVector s S e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array S ix e -> m (MArray (PrimState m) S ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) S ix e -> m (Array S ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) S ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) S ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) S ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) S ix' e -> Ix1 -> MArray (PrimState m) S ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array S ix' e -> Ix1 -> MArray (PrimState m) S ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Sz ix -> m (MArray (PrimState m) S ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Sz ix -> m (MArray (PrimState m) S ix e) Source #

Unbox e => Manifest U e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

unsafeLinearIndexM :: Index ix => Array U ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s U ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s U ix e -> MVector s U e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array U ix e -> m (MArray (PrimState m) U ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) U ix e -> m (Array U ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) U ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) U ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) U ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) U ix' e -> Ix1 -> MArray (PrimState m) U ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array U ix' e -> Ix1 -> MArray (PrimState m) U ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Sz ix -> m (MArray (PrimState m) U ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Sz ix -> m (MArray (PrimState m) U ix e) Source #

Generate

generateArray :: forall r ix e m. (MonadUnliftIO m, Manifest r e, Index ix) => Comp -> Sz ix -> (ix -> m e) -> m (Array r ix e) Source #

Just like generateArrayS, except this generator will respect the supplied computation strategy, and for that reason it is restricted to IO.

Since: 0.2.6

generateArrayLinear :: forall r ix e m. (MonadUnliftIO m, Manifest r e, Index ix) => Comp -> Sz ix -> (Ix1 -> m e) -> m (Array r ix e) Source #

Just like generateArray, except generating action will receive a row-major linear index.

Since: 0.3.0

generateArrayS Source #

Arguments

:: forall r ix e m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the array

-> (ix -> m e)

Element producing action

-> m (Array r ix e) 

Sequentially generate a pure array. Much like makeArray creates a pure array this function will use Manifest interface to generate a pure Array in the end, except that computation strategy is set to Seq. Element producing function no longer has to be pure but is a stateful action, becuase it is restricted to PrimMonad thus allows for sharing the state between computation of each element.

Examples

Expand
>>> import Data.Massiv.Array
>>> import Data.IORef
>>> ref <- newIORef (0 :: Int)
>>> generateArrayS (Sz1 6) (\ i -> modifyIORef' ref (+i) >> print i >> pure i) :: IO (Array U Ix1 Int)
0
1
2
3
4
5
Array U Seq (Sz1 6)
  [ 0, 1, 2, 3, 4, 5 ]
>>> readIORef ref
15

Since: 0.2.6

generateArrayLinearS Source #

Arguments

:: forall r ix e m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Resulting size of the array

-> (Int -> m e)

Element producing generator

-> m (Array r ix e) 

Same as generateArray but with action that accepts row-major linear index.

Since: 0.3.0

generateSplitSeedArray Source #

Arguments

:: forall r ix e g it. (Iterator it, Manifest r e, Index ix) 
=> it

Iterator

-> g

Initial seed

-> (forall s. g -> ST s (g, g))

An ST action that can split a seed into two independent seeds. It will be called the same number of times as the number of jobs that will get scheduled during parallelization. Eg. only once for the sequential case.

-> Comp

Computation strategy.

-> Sz ix

Resulting size of the array.

-> (forall s. Ix1 -> ix -> g -> ST s (e, g))

An ST action that produces a value and the next seed. It takes both versions of the index, in linear and in multi-dimensional forms, as well as the current seeding value. Returns the element for the array cell together with the new seed that will be used for the next element generation

-> (g, [g], Array r ix e)

Returned values are:

  • The final split of the supplied seed.
  • Results of scheduled jobs in the same order that they where scheduled
  • Final array that was fully filled using the supplied action and iterator.

Similar to makeSplitSeedArray, except it will produce a Manifest array and will return back the last unused seed together with all final seeds produced by each scheduled job. This function can be thought of as an unfolding done in parallel while iterating in a customizable manner.

Since: 1.0.2

Stateful worker threads

generateArrayWS :: forall r ix e s m. (Manifest r e, Index ix, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> Sz ix -> (ix -> s -> m e) -> m (Array r ix e) Source #

Use per worker thread state while generating elements of the array. Very useful for things that are not thread safe.

Since: 0.3.4

generateArrayLinearWS :: forall r ix e s m. (Manifest r e, Index ix, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> Sz ix -> (Int -> s -> m e) -> m (Array r ix e) Source #

Same as generateArrayWS, but use linear indexing instead.

Since: 0.3.4

Unfold

unfoldrPrimM_ Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> m (e, a))

Unfolding action

-> a

Initial accumulator

-> m (Array r ix e) 

Sequentially unfold an array from the left.

Examples

Expand

Create an array with Fibonacci numbers while performing an IO action at each iteration.

>>> import Data.Massiv.Array
>>> unfoldrPrimM_ (Sz1 10) (\(f0, f1) -> (f0, (f1, f0 + f1)) <$ print f1) (0, 1) :: IO (Array P Ix1 Int)
1
1
2
3
5
8
13
21
34
55
Array P Seq (Sz1 10)
  [ 0, 1, 1, 2, 3, 5, 8, 13, 21, 34 ]

Since: 0.3.0

iunfoldrPrimM_ Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> ix -> m (e, a))

Unfolding action

-> a

Initial accumulator

-> m (Array r ix e) 

Same as unfoldrPrimM_ but do the unfolding with index aware function.

Since: 0.3.0

unfoldrPrimM Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> m (e, a))

Unfolding action

-> a

Initial accumulator

-> m (a, Array r ix e) 

Just like iunfoldrPrimM, but do the unfolding with index aware function.

Since: 0.3.0

iunfoldrPrimM Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> ix -> m (e, a))

Unfolding action

-> a

Initial accumulator

-> m (a, Array r ix e) 

Just like iunfoldrPrimM_, but also returns the final value of the accumulator.

Since: 0.3.0

unfoldlPrimM_ Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> m (a, e))

Unfolding action

-> a

Initial accumulator

-> m (Array r ix e) 

Sequentially unfold an array from the left.

Examples

Expand

Create an array with Fibonacci numbers starting at the end while performing and IO action on the accumulator for each element of the array.

>>> import Data.Massiv.Array
>>> unfoldlPrimM_ (Sz1 10) (\a@(f0, f1) -> let fn = f0 + f1 in print a >> return ((f1, fn), f0)) (0, 1) :: IO (Array P Ix1 Int)
(0,1)
(1,1)
(1,2)
(2,3)
(3,5)
(5,8)
(8,13)
(13,21)
(21,34)
(34,55)
Array P Seq (Sz1 10)
  [ 34, 21, 13, 8, 5, 3, 2, 1, 1, 0 ]

Since: 0.3.0

iunfoldlPrimM_ Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> ix -> m (a, e))

Unfolding action

-> a

Initial accumulator

-> m (Array r ix e) 

Same as unfoldlPrimM_ but do the unfolding with index aware function.

Since: 0.3.0

unfoldlPrimM Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> m (a, e))

Unfolding action

-> a

Initial accumulator

-> m (a, Array r ix e) 

Just like iunfoldlPrimM, but do the unfolding with index aware function.

Since: 0.3.0

iunfoldlPrimM Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> ix -> m (a, e))

Unfolding action

-> a

Initial accumulator

-> m (a, Array r ix e) 

Just like iunfoldlPrimM_, but also returns the final value of the accumulator.

Since: 0.3.0

Mapping

forPrimM :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m e) -> m () Source #

Sequentially loop over a mutable array while modifying each element with an action.

Since: 0.4.0

forPrimM_ :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m ()) -> m () Source #

Sequentially loop over a mutable array while reading each element and applying an action to it. There is no mutation to the array, unless the action itself modifies it.

Since: 0.4.0

iforPrimM :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (ix -> e -> m e) -> m () Source #

Sequentially loop over a mutable array while modifying each element with an index aware action.

Since: 0.4.0

iforPrimM_ :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (ix -> e -> m ()) -> m () Source #

Sequentially loop over a mutable array while reading each element and applying an index aware action to it. There is no mutation to the array, unless the action itself modifies it.

Since: 0.4.0

iforLinearPrimM :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (Int -> e -> m e) -> m () Source #

Sequentially loop over a mutable array while modifying each element with an index aware action.

Since: 0.4.0

iforLinearPrimM_ :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (Int -> e -> m ()) -> m () Source #

Sequentially loop over a mutable array while reading each element and applying a linear index aware action to it. There is no mutation to the array, unless the action itself modifies it.

Since: 0.4.0

for2PrimM_ :: forall r1 r2 e1 e2 ix m. (PrimMonad m, Index ix, Manifest r1 e1, Manifest r2 e2) => MArray (PrimState m) r1 ix e1 -> MArray (PrimState m) r2 ix e2 -> (e1 -> e2 -> m ()) -> m () Source #

Sequentially loop over the intersection of two mutable arrays while reading elements from both and applying an action to it. There is no mutation to the actual arrays, unless the action itself modifies either one of them.

Since: 1.0.0

ifor2PrimM_ :: forall r1 r2 e1 e2 ix m. (PrimMonad m, Index ix, Manifest r1 e1, Manifest r2 e2) => MArray (PrimState m) r1 ix e1 -> MArray (PrimState m) r2 ix e2 -> (ix -> e1 -> e2 -> m ()) -> m () Source #

Same as for2PrimM_, but with index aware action.

Since: 1.0.0

Boxed

data B Source #

Array representation for Boxed elements. Its elements are strict to Weak Head Normal Form (WHNF) only.

Constructors

B 

Instances

Instances details
Show B Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

showsPrec :: Int -> B -> ShowS #

show :: B -> String #

showList :: [B] -> ShowS #

Size B Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

size :: Array B ix e -> Sz ix Source #

unsafeResize :: (Index ix, Index ix') => Sz ix' -> Array B ix e -> Array B ix' e Source #

Strategy B Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

setComp :: Comp -> Array B ix e -> Array B ix e Source #

getComp :: Array B ix e -> Comp Source #

repr :: B

Manifest B e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeLinearIndexM :: Index ix => Array B ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s B ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s B ix e -> MVector s B e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array B ix e -> m (MArray (PrimState m) B ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) B ix e -> m (Array B ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) B ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) B ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) B ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) B ix' e -> Ix1 -> MArray (PrimState m) B ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array B ix' e -> Ix1 -> MArray (PrimState m) B ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Sz ix -> m (MArray (PrimState m) B ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Sz ix -> m (MArray (PrimState m) B ix e) Source #

Index ix => Shape B ix Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Source B e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeIndex :: Index ix => Array B ix e -> ix -> e Source #

unsafeLinearIndex :: Index ix => Array B ix e -> Int -> e Source #

unsafePrefIndex :: Index ix => Array B ix e -> PrefIndex ix e Source #

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

unsafeLinearSlice :: Index ix => Ix1 -> Sz1 -> Array B ix e -> Array B Ix1 e Source #

Num e => FoldNumeric B e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

sumArray :: Index ix => Array B ix e -> e Source #

productArray :: Index ix => Array B ix e -> e Source #

powerSumArray :: Index ix => Array B ix e -> Int -> e Source #

unsafeDotProduct :: Index ix => Array B ix e -> Array B ix e -> e Source #

foldArray :: Index ix => (e -> e -> e) -> e -> Array B ix e -> e Source #

Num e => Numeric B e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

plusScalar :: Index ix => Array B ix e -> e -> Array B ix e Source #

minusScalar :: Index ix => Array B ix e -> e -> Array B ix e Source #

scalarMinus :: Index ix => e -> Array B ix e -> Array B ix e Source #

multiplyScalar :: Index ix => Array B ix e -> e -> Array B ix e Source #

absPointwise :: Index ix => Array B ix e -> Array B ix e Source #

additionPointwise :: Index ix => Array B ix e -> Array B ix e -> Array B ix e Source #

subtractionPointwise :: Index ix => Array B ix e -> Array B ix e -> Array B ix e Source #

multiplicationPointwise :: Index ix => Array B ix e -> Array B ix e -> Array B ix e Source #

powerPointwise :: Index ix => Array B ix e -> Int -> Array B ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array B ix e -> Array B ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array B ix e -> Array B ix e -> Array B ix e Source #

Index ix => Load B ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

makeArray :: Comp -> Sz ix -> (ix -> e) -> Array B ix e Source #

makeArrayLinear :: Comp -> Sz ix -> (Int -> e) -> Array B ix e Source #

replicate :: Comp -> Sz ix -> e -> Array B ix e Source #

iterArrayLinearST_ :: Scheduler s () -> Array B ix e -> (Int -> e -> ST s ()) -> ST s () Source #

iterArrayLinearWithSetST_ :: Scheduler s () -> Array B ix e -> (Ix1 -> e -> ST s ()) -> (Ix1 -> Sz1 -> e -> ST s ()) -> ST s () Source #

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

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

Index ix => Stream B ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

toStream :: Array B ix e -> Steps Id e Source #

toStreamIx :: Array B ix e -> Steps Id (ix, e) Source #

Index ix => StrideLoad B ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

iterArrayLinearWithStrideST_ :: Scheduler s () -> Stride ix -> Sz ix -> Array B ix e -> (Int -> e -> ST s ()) -> ST s () Source #

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

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

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

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

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

data BL Source #

Array representation for Boxed elements. This data structure is lazy with respect to its elements.

Example

Expand

Memoized version of a factorial that relies on laziness. Note that computing memoized factorial of a million would likely overflow memory.

>>> import Data.Massiv.Array as A
>>> :{
mkMemoFactorial :: Int -> (Int -> Integer)
mkMemoFactorial n =
  let arr = makeVectorR BL Seq (Sz1 n) fact
      fact i | i == 0 = 1
             | otherwise = (arr ! (i - 1)) * toInteger i
  in (arr !)
:}
>>> let fact = mkMemoFactorial 1000001
>>> fact 50
30414093201713378043612608166064768844377641568960512000000000000
>>> length $ show $ fact 5000
16326

Constructors

BL 

Instances

Instances details
Show BL Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

showsPrec :: Int -> BL -> ShowS #

show :: BL -> String #

showList :: [BL] -> ShowS #

Size BL Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

size :: Array BL ix e -> Sz ix Source #

unsafeResize :: (Index ix, Index ix') => Sz ix' -> Array BL ix e -> Array BL ix' e Source #

Strategy BL Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

setComp :: Comp -> Array BL ix e -> Array BL ix e Source #

getComp :: Array BL ix e -> Comp Source #

repr :: BL

Manifest BL e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeLinearIndexM :: Index ix => Array BL ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s BL ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s BL ix e -> MVector s BL e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array BL ix e -> m (MArray (PrimState m) BL ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) BL ix e -> m (Array BL ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) BL ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) BL ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) BL ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) BL ix' e -> Ix1 -> MArray (PrimState m) BL ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array BL ix' e -> Ix1 -> MArray (PrimState m) BL ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Sz ix -> m (MArray (PrimState m) BL ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Sz ix -> m (MArray (PrimState m) BL ix e) Source #

Index ix => Shape BL ix Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Source BL e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeIndex :: Index ix => Array BL ix e -> ix -> e Source #

unsafeLinearIndex :: Index ix => Array BL ix e -> Int -> e Source #

unsafePrefIndex :: Index ix => Array BL ix e -> PrefIndex ix e Source #

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

unsafeLinearSlice :: Index ix => Ix1 -> Sz1 -> Array BL ix e -> Array BL Ix1 e Source #

Num e => FoldNumeric BL e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

sumArray :: Index ix => Array BL ix e -> e Source #

productArray :: Index ix => Array BL ix e -> e Source #

powerSumArray :: Index ix => Array BL ix e -> Int -> e Source #

unsafeDotProduct :: Index ix => Array BL ix e -> Array BL ix e -> e Source #

foldArray :: Index ix => (e -> e -> e) -> e -> Array BL ix e -> e Source #

Num e => Numeric BL e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

plusScalar :: Index ix => Array BL ix e -> e -> Array BL ix e Source #

minusScalar :: Index ix => Array BL ix e -> e -> Array BL ix e Source #

scalarMinus :: Index ix => e -> Array BL ix e -> Array BL ix e Source #

multiplyScalar :: Index ix => Array BL ix e -> e -> Array BL ix e Source #

absPointwise :: Index ix => Array BL ix e -> Array BL ix e Source #

additionPointwise :: Index ix => Array BL ix e -> Array BL ix e -> Array BL ix e Source #

subtractionPointwise :: Index ix => Array BL ix e -> Array BL ix e -> Array BL ix e Source #

multiplicationPointwise :: Index ix => Array BL ix e -> Array BL ix e -> Array BL ix e Source #

powerPointwise :: Index ix => Array BL ix e -> Int -> Array BL ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array BL ix e -> Array BL ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array BL ix e -> Array BL ix e -> Array BL ix e Source #

Index ix => Load BL ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

makeArray :: Comp -> Sz ix -> (ix -> e) -> Array BL ix e Source #

makeArrayLinear :: Comp -> Sz ix -> (Int -> e) -> Array BL ix e Source #

replicate :: Comp -> Sz ix -> e -> Array BL ix e Source #

iterArrayLinearST_ :: Scheduler s () -> Array BL ix e -> (Int -> e -> ST s ()) -> ST s () Source #

iterArrayLinearWithSetST_ :: Scheduler s () -> Array BL ix e -> (Ix1 -> e -> ST s ()) -> (Ix1 -> Sz1 -> e -> ST s ()) -> ST s () Source #

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

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

Index ix => Stream BL ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

toStream :: Array BL ix e -> Steps Id e Source #

toStreamIx :: Array BL ix e -> Steps Id (ix, e) Source #

Index ix => StrideLoad BL ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

iterArrayLinearWithStrideST_ :: Scheduler s () -> Stride ix -> Sz ix -> Array BL ix e -> (Int -> e -> ST s ()) -> ST s () Source #

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

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 #

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

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

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

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

data Array BL ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

data Array BL ix e = BLArray {}
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)
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 BN Source #

Constructors

BN 

Instances

Instances details
Show BN Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

showsPrec :: Int -> BN -> ShowS #

show :: BN -> String #

showList :: [BN] -> ShowS #

Size BN Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

size :: Array BN ix e -> Sz ix Source #

unsafeResize :: (Index ix, Index ix') => Sz ix' -> Array BN ix e -> Array BN ix' e Source #

Strategy BN Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

setComp :: Comp -> Array BN ix e -> Array BN ix e Source #

getComp :: Array BN ix e -> Comp Source #

repr :: BN

NFData e => Manifest BN e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeLinearIndexM :: Index ix => Array BN ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s BN ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s BN ix e -> MVector s BN e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array BN ix e -> m (MArray (PrimState m) BN ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) BN ix e -> m (Array BN ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) BN ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) BN ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) BN ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) BN ix' e -> Ix1 -> MArray (PrimState m) BN ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array BN ix' e -> Ix1 -> MArray (PrimState m) BN ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Sz ix -> m (MArray (PrimState m) BN ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Sz ix -> m (MArray (PrimState m) BN ix e) Source #

Index ix => Shape BN ix Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

NFData e => Source BN e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeIndex :: Index ix => Array BN ix e -> ix -> e Source #

unsafeLinearIndex :: Index ix => Array BN ix e -> Int -> e Source #

unsafePrefIndex :: Index ix => Array BN ix e -> PrefIndex ix e Source #

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

unsafeLinearSlice :: Index ix => Ix1 -> Sz1 -> Array BN ix e -> Array BN Ix1 e Source #

(NFData e, Num e) => FoldNumeric BN e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

sumArray :: Index ix => Array BN ix e -> e Source #

productArray :: Index ix => Array BN ix e -> e Source #

powerSumArray :: Index ix => Array BN ix e -> Int -> e Source #

unsafeDotProduct :: Index ix => Array BN ix e -> Array BN ix e -> e Source #

foldArray :: Index ix => (e -> e -> e) -> e -> Array BN ix e -> e Source #

(NFData e, Num e) => Numeric BN e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

plusScalar :: Index ix => Array BN ix e -> e -> Array BN ix e Source #

minusScalar :: Index ix => Array BN ix e -> e -> Array BN ix e Source #

scalarMinus :: Index ix => e -> Array BN ix e -> Array BN ix e Source #

multiplyScalar :: Index ix => Array BN ix e -> e -> Array BN ix e Source #

absPointwise :: Index ix => Array BN ix e -> Array BN ix e Source #

additionPointwise :: Index ix => Array BN ix e -> Array BN ix e -> Array BN ix e Source #

subtractionPointwise :: Index ix => Array BN ix e -> Array BN ix e -> Array BN ix e Source #

multiplicationPointwise :: Index ix => Array BN ix e -> Array BN ix e -> Array BN ix e Source #

powerPointwise :: Index ix => Array BN ix e -> Int -> Array BN ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array BN ix e -> Array BN ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array BN ix e -> Array BN ix e -> Array BN ix e Source #

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

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

makeArray :: Comp -> Sz ix -> (ix -> e) -> Array BN ix e Source #

makeArrayLinear :: Comp -> Sz ix -> (Int -> e) -> Array BN ix e Source #

replicate :: Comp -> Sz ix -> e -> Array BN ix e Source #

iterArrayLinearST_ :: Scheduler s () -> Array BN ix e -> (Int -> e -> ST s ()) -> ST s () Source #

iterArrayLinearWithSetST_ :: Scheduler s () -> Array BN ix e -> (Ix1 -> e -> ST s ()) -> (Ix1 -> Sz1 -> e -> ST s ()) -> ST s () Source #

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

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

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

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

toStream :: Array BN ix e -> Steps Id e Source #

toStreamIx :: Array BN ix e -> Steps Id (ix, e) Source #

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

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

iterArrayLinearWithStrideST_ :: Scheduler s () -> Stride ix -> Sz ix -> Array BN ix e -> (Int -> e -> ST s ()) -> ST s () Source #

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

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

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

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 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)
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 N = BN Source #

Deprecated: In favor of more consistently named BN

Type and pattern N have been added for backwards compatibility and will be replaced in the future in favor of BN.

Deprecated - since 1.0.0

pattern N :: N Source #

Deprecated: In favor of more consistently named BN

data Uninitialized Source #

An error that gets thrown when an unitialized element of a boxed array gets accessed. Can only happen when array was constructed with unsafeNew.

Constructors

Uninitialized 

Access

findIndex :: (Index ix, Manifest r e) => (e -> Bool) -> Array r ix e -> Maybe ix Source #

O(n) - Perform a row-major search starting at 0 for an element. Returns the index of the first occurance of an element or Nothing if a predicate could not be satisifed after it was applyied to all elements of the array.

Since: 0.5.5

Conversion

Important part of all conversions in this section is that the actual boxed Array, which holds the pointers to values isn't copied around, it is always kept as the same array. Conversion to Massiv boxed array will undergo evaluation during which computation strategies will be respected.

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

O(1) - Cast a strict boxed array into a lazy boxed array.

Since: 0.6.0

evalLazyArray :: Index ix => Array BL ix e -> Array B ix e Source #

O(n) - Evaluate all elements of a boxed lazy array to weak head normal form

Since: 0.6.0

forceLazyArray :: (NFData e, Index ix) => Array BL ix e -> Array N ix e Source #

O(n) - Evaluate all elements of a boxed lazy array to normal form

Since: 0.6.0

unwrapNormalForm :: Array N ix e -> Array B ix e Source #

O(1) - Converts array from N to B representation.

Since: 0.5.0

evalNormalForm :: (Index ix, NFData e) => Array B ix e -> Array N ix e Source #

O(n) - Compute all elements of a boxed array to NF (normal form)

Since: 0.5.0

Primitive Boxed Array

unwrapLazyArray :: Array BL ix e -> Array e Source #

O(1) - Unwrap boxed array. This will discard any possible slicing that has been applied to the array.

Since: 0.6.0

wrapLazyArray :: Array e -> Vector BL e Source #

O(1) - Wrap a boxed array.

Since: 0.6.0

unwrapArray :: Array B ix e -> Array e Source #

O(1) - Unwrap boxed array. This will discard any possible slicing that has been applied to the array.

Since: 0.2.1

evalArray Source #

Arguments

:: Comp

Computation strategy

-> Array e

Lazy boxed array from primitive package.

-> Vector B e 

O(n) - Wrap a boxed array and evaluate all elements to a WHNF.

Since: 0.2.1

unwrapMutableArray :: MArray s B ix e -> MutableArray s e Source #

O(1) - Unwrap mutable boxed array. This will discard any possible slicing that has been applied to the array.

Since: 0.2.1

unwrapMutableLazyArray :: MArray s BL ix e -> MutableArray s e Source #

O(1) - Unwrap mutable boxed lazy array. This will discard any possible slicing that has been applied to the array.

Since: 0.6.0

evalMutableArray Source #

Arguments

:: PrimMonad m 
=> MutableArray (PrimState m) e

Mutable array that will get wrapped

-> m (MArray (PrimState m) B Ix1 e) 

O(n) - Wrap mutable boxed array and evaluate all elements to WHNF.

Since: 0.2.1

unwrapNormalFormArray :: Array N ix e -> Array e Source #

O(1) - Unwrap a fully evaluated boxed array. This will discard any possible slicing that has been applied to the array.

Since: 0.2.1

evalNormalFormArray Source #

Arguments

:: NFData e 
=> Comp

Computation strategy

-> Array e

Lazy boxed array

-> Array N Ix1 e 

O(n) - Wrap a boxed array and evaluate all elements to a Normal Form (NF).

Since: 0.2.1

unwrapNormalFormMutableArray :: MArray s N ix e -> MutableArray s e Source #

O(1) - Unwrap a fully evaluated mutable boxed array. This will discard any possible slicing that has been applied to the array.

Since: 0.2.1

evalNormalFormMutableArray :: (PrimMonad m, NFData e) => MutableArray (PrimState m) e -> m (MArray (PrimState m) N Ix1 e) Source #

O(n) - Wrap mutable boxed array and evaluate all elements to NF.

Since: 0.2.1

Boxed Vector

toBoxedVector :: Index ix => Array BL ix a -> Vector a Source #

O(1) - Converts a boxed Array into a Vector without touching any elements.

Since: 0.5.0

toBoxedMVector :: Index ix => MArray s BL ix a -> MVector s a Source #

O(1) - Converts a boxed MArray into a MVector.

Since: 0.5.0

fromBoxedVector :: Vector a -> Vector BL a Source #

O(1) - Cast a boxed vector without touching any elements.

Since: 0.6.0

fromBoxedMVector :: MVector s a -> MArray s BL Ix1 a Source #

O(1) - Convert mutable boxed vector to a lazy mutable boxed array. Both keep pointing to the same memory

Since: 0.6.0

evalBoxedVector :: Comp -> Vector a -> Array B Ix1 a Source #

O(n) - Convert a boxed vector and evaluate all elements to WHNF. Computation strategy will be respected during evaluation

Since: 0.5.0

evalBoxedMVector :: PrimMonad m => MVector (PrimState m) a -> m (MArray (PrimState m) B Ix1 a) Source #

O(n) - Convert mutable boxed vector and evaluate all elements to WHNF sequentially. Both keep pointing to the same memory

Since: 0.5.0

Primitive

data P Source #

Representation for Primitive elements

Constructors

P 

Instances

Instances details
Show P Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

showsPrec :: Int -> P -> ShowS #

show :: P -> String #

showList :: [P] -> ShowS #

Size P Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

size :: Array P ix e -> Sz ix Source #

unsafeResize :: (Index ix, Index ix') => Sz ix' -> Array P ix e -> Array P ix' e Source #

Strategy P Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

setComp :: Comp -> Array P ix e -> Array P ix e Source #

getComp :: Array P ix e -> Comp Source #

repr :: P

Prim e => Manifest P e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

unsafeLinearIndexM :: Index ix => Array P ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s P ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s P ix e -> MVector s P e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array P ix e -> m (MArray (PrimState m) P ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) P ix e -> m (Array P ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) P ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) P ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) P ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) P ix' e -> Ix1 -> MArray (PrimState m) P ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array P ix' e -> Ix1 -> MArray (PrimState m) P ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Sz ix -> m (MArray (PrimState m) P ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Sz ix -> m (MArray (PrimState m) P ix e) Source #

Index ix => Shape P ix Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Prim e => Source P e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

unsafeIndex :: Index ix => Array P ix e -> ix -> e Source #

unsafeLinearIndex :: Index ix => Array P ix e -> Int -> e Source #

unsafePrefIndex :: Index ix => Array P ix e -> PrefIndex ix e Source #

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

unsafeLinearSlice :: Index ix => Ix1 -> Sz1 -> Array P ix e -> Array P Ix1 e Source #

(Prim e, Num e) => FoldNumeric P e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

sumArray :: Index ix => Array P ix e -> e Source #

productArray :: Index ix => Array P ix e -> e Source #

powerSumArray :: Index ix => Array P ix e -> Int -> e Source #

unsafeDotProduct :: Index ix => Array P ix e -> Array P ix e -> e Source #

foldArray :: Index ix => (e -> e -> e) -> e -> Array P ix e -> e Source #

(Prim e, Num e) => Numeric P e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

plusScalar :: Index ix => Array P ix e -> e -> Array P ix e Source #

minusScalar :: Index ix => Array P ix e -> e -> Array P ix e Source #

scalarMinus :: Index ix => e -> Array P ix e -> Array P ix e Source #

multiplyScalar :: Index ix => Array P ix e -> e -> Array P ix e Source #

absPointwise :: Index ix => Array P ix e -> Array P ix e Source #

additionPointwise :: Index ix => Array P ix e -> Array P ix e -> Array P ix e Source #

subtractionPointwise :: Index ix => Array P ix e -> Array P ix e -> Array P ix e Source #

multiplicationPointwise :: Index ix => Array P ix e -> Array P ix e -> Array P ix e Source #

powerPointwise :: Index ix => Array P ix e -> Int -> Array P ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array P ix e -> Array P ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array P ix e -> Array P ix e -> Array P ix e Source #

(Prim e, Floating e) => NumericFloat P e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

divideScalar :: Index ix => Array P ix e -> e -> Array P ix e Source #

scalarDivide :: Index ix => e -> Array P ix e -> Array P ix e Source #

divisionPointwise :: Index ix => Array P ix e -> Array P ix e -> Array P ix e Source #

recipPointwise :: Index ix => Array P ix e -> Array P ix e Source #

sqrtPointwise :: Index ix => Array P ix e -> Array P ix e Source #

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

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

makeArray :: Comp -> Sz ix -> (ix -> e) -> Array P ix e Source #

makeArrayLinear :: Comp -> Sz ix -> (Int -> e) -> Array P ix e Source #

replicate :: Comp -> Sz ix -> e -> Array P ix e Source #

iterArrayLinearST_ :: Scheduler s () -> Array P ix e -> (Int -> e -> ST s ()) -> ST s () Source #

iterArrayLinearWithSetST_ :: Scheduler s () -> Array P ix e -> (Ix1 -> e -> ST s ()) -> (Ix1 -> Sz1 -> e -> ST s ()) -> ST s () Source #

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

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

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

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

toStream :: Array P ix e -> Steps Id e Source #

toStreamIx :: Array P ix e -> Steps Id (ix, e) Source #

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

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

iterArrayLinearWithStrideST_ :: Scheduler s () -> Stride ix -> Sz ix -> Array P ix e -> (Int -> e -> ST s ()) -> ST s () Source #

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

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

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

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

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

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

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

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 Array P ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

data Array P ix e = PArray {}
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)
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)

class Prim a #

Class of types supporting primitive array operations. This includes interfacing with GC-managed memory (functions suffixed with ByteArray#) and interfacing with unmanaged memory (functions suffixed with Addr#). Endianness is platform-dependent.

Instances

Instances details
Prim CBool 
Instance details

Defined in Data.Primitive.Types

Prim CChar 
Instance details

Defined in Data.Primitive.Types

Prim CClock 
Instance details

Defined in Data.Primitive.Types

Prim CDouble 
Instance details

Defined in Data.Primitive.Types

Prim CFloat 
Instance details

Defined in Data.Primitive.Types

Prim CInt 
Instance details

Defined in Data.Primitive.Types

Prim CIntMax 
Instance details

Defined in Data.Primitive.Types

Prim CIntPtr 
Instance details

Defined in Data.Primitive.Types

Prim CLLong 
Instance details

Defined in Data.Primitive.Types

Prim CLong 
Instance details

Defined in Data.Primitive.Types

Prim CPtrdiff 
Instance details

Defined in Data.Primitive.Types

Prim CSChar 
Instance details

Defined in Data.Primitive.Types

Prim CSUSeconds 
Instance details

Defined in Data.Primitive.Types

Prim CShort 
Instance details

Defined in Data.Primitive.Types

Prim CSigAtomic 
Instance details

Defined in Data.Primitive.Types

Prim CSize 
Instance details

Defined in Data.Primitive.Types

Prim CTime 
Instance details

Defined in Data.Primitive.Types

Prim CUChar 
Instance details

Defined in Data.Primitive.Types

Prim CUInt 
Instance details

Defined in Data.Primitive.Types

Prim CUIntMax 
Instance details

Defined in Data.Primitive.Types

Prim CUIntPtr 
Instance details

Defined in Data.Primitive.Types

Prim CULLong 
Instance details

Defined in Data.Primitive.Types

Prim CULong 
Instance details

Defined in Data.Primitive.Types

Prim CUSeconds 
Instance details

Defined in Data.Primitive.Types

Prim CUShort 
Instance details

Defined in Data.Primitive.Types

Prim CWchar 
Instance details

Defined in Data.Primitive.Types

Prim IntPtr

Since: primitive-0.7.1.0

Instance details

Defined in Data.Primitive.Types

Prim WordPtr

Since: primitive-0.7.1.0

Instance details

Defined in Data.Primitive.Types

Prim Int16 
Instance details

Defined in Data.Primitive.Types

Prim Int32 
Instance details

Defined in Data.Primitive.Types

Prim Int64 
Instance details

Defined in Data.Primitive.Types

Prim Int8 
Instance details

Defined in Data.Primitive.Types

Prim Word16 
Instance details

Defined in Data.Primitive.Types

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Prim Word64 
Instance details

Defined in Data.Primitive.Types

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Prim CBlkCnt 
Instance details

Defined in Data.Primitive.Types

Prim CBlkSize 
Instance details

Defined in Data.Primitive.Types

Prim CCc 
Instance details

Defined in Data.Primitive.Types

Prim CClockId 
Instance details

Defined in Data.Primitive.Types

Prim CDev 
Instance details

Defined in Data.Primitive.Types

Prim CFsBlkCnt 
Instance details

Defined in Data.Primitive.Types

Prim CFsFilCnt 
Instance details

Defined in Data.Primitive.Types

Prim CGid 
Instance details

Defined in Data.Primitive.Types

Prim CId 
Instance details

Defined in Data.Primitive.Types

Prim CIno 
Instance details

Defined in Data.Primitive.Types

Prim CKey 
Instance details

Defined in Data.Primitive.Types

Prim CMode 
Instance details

Defined in Data.Primitive.Types

Prim CNlink 
Instance details

Defined in Data.Primitive.Types

Prim COff 
Instance details

Defined in Data.Primitive.Types

Prim CPid 
Instance details

Defined in Data.Primitive.Types

Prim CRLim 
Instance details

Defined in Data.Primitive.Types

Prim CSpeed 
Instance details

Defined in Data.Primitive.Types

Prim CSsize 
Instance details

Defined in Data.Primitive.Types

Prim CTcflag 
Instance details

Defined in Data.Primitive.Types

Prim CTimer 
Instance details

Defined in Data.Primitive.Types

Prim CUid 
Instance details

Defined in Data.Primitive.Types

Prim Fd 
Instance details

Defined in Data.Primitive.Types

Prim Char 
Instance details

Defined in Data.Primitive.Types

Prim Double 
Instance details

Defined in Data.Primitive.Types

Prim Float 
Instance details

Defined in Data.Primitive.Types

Prim Int 
Instance details

Defined in Data.Primitive.Types

Prim Word 
Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Identity a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Down a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (First a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Last a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Max a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Max a -> Int# #

alignment# :: Max a -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Max a #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Max a #) #

writeByteArray# :: MutableByteArray# s -> Int# -> Max a -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Max a -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Max a #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Max a #) #

writeOffAddr# :: Addr# -> Int# -> Max a -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Max a -> State# s -> State# s #

Prim a => Prim (Min a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Min a -> Int# #

alignment# :: Min a -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Min a #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Min a #) #

writeByteArray# :: MutableByteArray# s -> Int# -> Min a -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Min a -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Min a #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Min a #) #

writeOffAddr# :: Addr# -> Int# -> Min a -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Min a -> State# s -> State# s #

Prim a => Prim (Dual a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Product a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Sum a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Sum a -> Int# #

alignment# :: Sum a -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Sum a #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Sum a #) #

writeByteArray# :: MutableByteArray# s -> Int# -> Sum a -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Sum a -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Sum a #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Sum a #) #

writeOffAddr# :: Addr# -> Int# -> Sum a -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Sum a -> State# s -> State# s #

Prim (FunPtr a) 
Instance details

Defined in Data.Primitive.Types

Prim (Ptr a) 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Ptr a -> Int# #

alignment# :: Ptr a -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Ptr a #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Ptr a #) #

writeByteArray# :: MutableByteArray# s -> Int# -> Ptr a -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Ptr a -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Ptr a #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Ptr a #) #

writeOffAddr# :: Addr# -> Int# -> Ptr a -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Ptr a -> State# s -> State# s #

Prim (StablePtr a) 
Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Const a b)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Const a b -> Int# #

alignment# :: Const a b -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Const a b #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Const a b #) #

writeByteArray# :: MutableByteArray# s -> Int# -> Const a b -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Const a b -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Const a b #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Const a b #) #

writeOffAddr# :: Addr# -> Int# -> Const a b -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Const a b -> State# s -> State# s #

Conversion

Primitive ByteArray

toByteArray :: (Index ix, Prim e) => Array P ix e -> ByteArray Source #

O(n) - Ensure that the size matches the internal ByteArray. If not make a copy of the slice and return it as ByteArray

Since: 0.2.1

toByteArrayM :: (Prim e, Index ix, MonadThrow m) => Array P ix e -> m ByteArray Source #

O(1) - Unwrap Ensure that the size matches the internal ByteArray.

Since: 0.5.0

unwrapByteArray :: Array P ix e -> ByteArray Source #

O(1) - Extract the internal ByteArray. This will ignore any possible slicing that has been applied to the array. Use toByteArray in order to preserve slicing or unwrapByteArrayOffset to get ahold of the offset

Since: 0.5.0

unwrapByteArrayOffset :: Array P ix e -> Int Source #

O(1) - Extract potential linear offset into the underlying ByteArray, which can also be extracted with unwrapByteArray.

Since: 0.5.9

fromByteArray :: forall e. Prim e => Comp -> ByteArray -> Array P Ix1 e Source #

O(1) - Construct a flat Array from ByteArray

Since: 0.4.0

fromByteArrayM :: (MonadThrow m, Index ix, Prim e) => Comp -> Sz ix -> ByteArray -> m (Array P ix e) Source #

O(1) - Construct a primitive array from the ByteArray. Will return Nothing if number of elements doesn't match.

Since: 0.3.0

fromByteArrayOffsetM :: (MonadThrow m, Index ix, Prim e) => Comp -> Sz ix -> Int -> ByteArray -> m (Array P ix e) Source #

O(1) - Construct a primitive array from the ByteArray. Will return Nothing if number of elements doesn't match.

Since: 0.5.9

toMutableByteArray :: forall ix e m. (Prim e, Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> m (Bool, MutableByteArray (PrimState m)) Source #

O(n) - Try to cast a mutable array to MutableByteArray, if sizes do not match make a copy. Returns True if an array was converted without a copy, in which case it means that the source at the resulting array are still pointing to the same location in memory.

Since: 0.5.0

unwrapMutableByteArray :: MArray s P ix e -> MutableByteArray s Source #

O(1) - Extract the internal MutableByteArray. This will discard any possible slicing that has been applied to the array.

Since: 0.5.0

unwrapMutableByteArrayOffset :: MArray s P ix e -> Int Source #

O(1) - Extract the linear offset into underlying MutableByteArray, which can aslo be extracted with unwrapMutableByteArray.

Since: 0.5.9

fromMutableByteArray :: forall e s. Prim e => MutableByteArray s -> MArray s P Ix1 e Source #

O(1) - Construct a flat Array from MutableByteArray

Since: 0.4.0

fromMutableByteArrayM :: (MonadThrow m, Index ix, Prim e) => Sz ix -> MutableByteArray s -> m (MArray s P ix e) Source #

O(1) - Construct a primitive mutable array from the MutableByteArray. Will throw SizeElementsMismatchException if number of elements doesn't match.

Since: 0.3.0

fromMutableByteArrayOffsetM :: (MonadThrow m, Index ix, Prim e) => Sz ix -> Ix1 -> MutableByteArray s -> m (MArray s P ix e) Source #

O(1) - Construct a primitive mutable array from the MutableByteArray. Will throw SizeElementsMismatchException if number of elements doesn't match.

Since: 0.5.9

Primitive Vector

toPrimitiveVector :: Index ix => Array P ix e -> Vector e Source #

O(1) - Cast a primitive array to a primitive vector.

Since: 0.5.0

toPrimitiveMVector :: Index ix => MArray s P ix e -> MVector s e Source #

O(1) - Cast a mutable primitive array to a mutable primitive vector.

Since: 0.5.0

fromPrimitiveVector :: Vector e -> Array P Ix1 e Source #

O(1) - Cast a primitive vector to a primitive array.

Since: 0.5.0

fromPrimitiveMVector :: MVector s e -> MArray s P Ix1 e Source #

O(1) - Cast a mutable primitive vector to a mutable primitive array.

Since: 0.5.0

Storable

data S Source #

Representation for Storable elements

Constructors

S 

Instances

Instances details
Show S Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

showsPrec :: Int -> S -> ShowS #

show :: S -> String #

showList :: [S] -> ShowS #

Size S Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

size :: Array S ix e -> Sz ix Source #

unsafeResize :: (Index ix, Index ix') => Sz ix' -> Array S ix e -> Array S ix' e Source #

Strategy S Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

setComp :: Comp -> Array S ix e -> Array S ix e Source #

getComp :: Array S ix e -> Comp Source #

repr :: S

Storable e => Manifest S e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

unsafeLinearIndexM :: Index ix => Array S ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s S ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s S ix e -> MVector s S e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array S ix e -> m (MArray (PrimState m) S ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) S ix e -> m (Array S ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) S ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) S ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) S ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) S ix' e -> Ix1 -> MArray (PrimState m) S ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array S ix' e -> Ix1 -> MArray (PrimState m) S ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Sz ix -> m (MArray (PrimState m) S ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Sz ix -> m (MArray (PrimState m) S ix e) Source #

Index ix => Shape S ix Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Storable e => Source S e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

unsafeIndex :: Index ix => Array S ix e -> ix -> e Source #

unsafeLinearIndex :: Index ix => Array S ix e -> Int -> e Source #

unsafePrefIndex :: Index ix => Array S ix e -> PrefIndex ix e Source #

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

unsafeLinearSlice :: Index ix => Ix1 -> Sz1 -> Array S ix e -> Array S Ix1 e Source #

(Storable e, Num e) => FoldNumeric S e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

sumArray :: Index ix => Array S ix e -> e Source #

productArray :: Index ix => Array S ix e -> e Source #

powerSumArray :: Index ix => Array S ix e -> Int -> e Source #

unsafeDotProduct :: Index ix => Array S ix e -> Array S ix e -> e Source #

foldArray :: Index ix => (e -> e -> e) -> e -> Array S ix e -> e Source #

(Storable e, Num e) => Numeric S e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

plusScalar :: Index ix => Array S ix e -> e -> Array S ix e Source #

minusScalar :: Index ix => Array S ix e -> e -> Array S ix e Source #

scalarMinus :: Index ix => e -> Array S ix e -> Array S ix e Source #

multiplyScalar :: Index ix => Array S ix e -> e -> Array S ix e Source #

absPointwise :: Index ix => Array S ix e -> Array S ix e Source #

additionPointwise :: Index ix => Array S ix e -> Array S ix e -> Array S ix e Source #

subtractionPointwise :: Index ix => Array S ix e -> Array S ix e -> Array S ix e Source #

multiplicationPointwise :: Index ix => Array S ix e -> Array S ix e -> Array S ix e Source #

powerPointwise :: Index ix => Array S ix e -> Int -> Array S ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array S ix e -> Array S ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array S ix e -> Array S ix e -> Array S ix e Source #

(Storable e, Floating e) => NumericFloat S e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

divideScalar :: Index ix => Array S ix e -> e -> Array S ix e Source #

scalarDivide :: Index ix => e -> Array S ix e -> Array S ix e Source #

divisionPointwise :: Index ix => Array S ix e -> Array S ix e -> Array S ix e Source #

recipPointwise :: Index ix => Array S ix e -> Array S ix e Source #

sqrtPointwise :: Index ix => Array S ix e -> Array S ix e Source #

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

Defined in Data.Massiv.Array.Manifest.Storable

Methods

makeArray :: Comp -> Sz ix -> (ix -> e) -> Array S ix e Source #

makeArrayLinear :: Comp -> Sz ix -> (Int -> e) -> Array S ix e Source #

replicate :: Comp -> Sz ix -> e -> Array S ix e Source #

iterArrayLinearST_ :: Scheduler s () -> Array S ix e -> (Int -> e -> ST s ()) -> ST s () Source #

iterArrayLinearWithSetST_ :: Scheduler s () -> Array S ix e -> (Ix1 -> e -> ST s ()) -> (Ix1 -> Sz1 -> e -> ST s ()) -> ST s () Source #

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

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

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

Defined in Data.Massiv.Array.Manifest.Storable

Methods

toStream :: Array S ix e -> Steps Id e Source #

toStreamIx :: Array S ix e -> Steps Id (ix, e) Source #

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

Defined in Data.Massiv.Array.Manifest.Storable

Methods

iterArrayLinearWithStrideST_ :: Scheduler s () -> Stride ix -> Sz ix -> Array S ix e -> (Int -> e -> ST s ()) -> ST s () Source #

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

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

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

Defined in Data.Massiv.Array.Manifest.Storable

Methods

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

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

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

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

data Array S ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

data Array S ix e = SArray {}
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)
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)

class Storable a #

The member functions of this class facilitate writing values of primitive types to raw memory (which may have been allocated with the above mentioned routines) and reading values from blocks of raw memory. The class, furthermore, includes support for computing the storage requirements and alignment restrictions of storable types.

Memory addresses are represented as values of type Ptr a, for some a which is an instance of class Storable. The type argument to Ptr helps provide some valuable type safety in FFI code (you can't mix pointers of different types without an explicit cast), while helping the Haskell type system figure out which marshalling method is needed for a given pointer.

All marshalling between Haskell and a foreign language ultimately boils down to translating Haskell data structures into the binary representation of a corresponding data structure of the foreign language and vice versa. To code this marshalling in Haskell, it is necessary to manipulate primitive data types stored in unstructured memory blocks. The class Storable facilitates this manipulation on all types for which it is instantiated, which are the standard basic types of Haskell, the fixed size Int types (Int8, Int16, Int32, Int64), the fixed size Word types (Word8, Word16, Word32, Word64), StablePtr, all types from Foreign.C.Types, as well as Ptr.

Minimal complete definition

sizeOf, alignment, (peek | peekElemOff | peekByteOff), (poke | pokeElemOff | pokeByteOff)

Instances

Instances details
Storable CBool 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CBool -> Int #

alignment :: CBool -> Int #

peekElemOff :: Ptr CBool -> Int -> IO CBool #

pokeElemOff :: Ptr CBool -> Int -> CBool -> IO () #

peekByteOff :: Ptr b -> Int -> IO CBool #

pokeByteOff :: Ptr b -> Int -> CBool -> IO () #

peek :: Ptr CBool -> IO CBool #

poke :: Ptr CBool -> CBool -> IO () #

Storable CChar 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CChar -> Int #

alignment :: CChar -> Int #

peekElemOff :: Ptr CChar -> Int -> IO CChar #

pokeElemOff :: Ptr CChar -> Int -> CChar -> IO () #

peekByteOff :: Ptr b -> Int -> IO CChar #

pokeByteOff :: Ptr b -> Int -> CChar -> IO () #

peek :: Ptr CChar -> IO CChar #

poke :: Ptr CChar -> CChar -> IO () #

Storable CClock 
Instance details

Defined in Foreign.C.Types

Storable CDouble 
Instance details

Defined in Foreign.C.Types

Storable CFloat 
Instance details

Defined in Foreign.C.Types

Storable CInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CInt -> Int #

alignment :: CInt -> Int #

peekElemOff :: Ptr CInt -> Int -> IO CInt #

pokeElemOff :: Ptr CInt -> Int -> CInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CInt #

pokeByteOff :: Ptr b -> Int -> CInt -> IO () #

peek :: Ptr CInt -> IO CInt #

poke :: Ptr CInt -> CInt -> IO () #

Storable CIntMax 
Instance details

Defined in Foreign.C.Types

Storable CIntPtr 
Instance details

Defined in Foreign.C.Types

Storable CLLong 
Instance details

Defined in Foreign.C.Types

Storable CLong 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CLong -> Int #

alignment :: CLong -> Int #

peekElemOff :: Ptr CLong -> Int -> IO CLong #

pokeElemOff :: Ptr CLong -> Int -> CLong -> IO () #

peekByteOff :: Ptr b -> Int -> IO CLong #

pokeByteOff :: Ptr b -> Int -> CLong -> IO () #

peek :: Ptr CLong -> IO CLong #

poke :: Ptr CLong -> CLong -> IO () #

Storable CPtrdiff 
Instance details

Defined in Foreign.C.Types

Storable CSChar 
Instance details

Defined in Foreign.C.Types

Storable CSUSeconds 
Instance details

Defined in Foreign.C.Types

Storable CShort 
Instance details

Defined in Foreign.C.Types

Storable CSigAtomic 
Instance details

Defined in Foreign.C.Types

Storable CSize 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CSize -> Int #

alignment :: CSize -> Int #

peekElemOff :: Ptr CSize -> Int -> IO CSize #

pokeElemOff :: Ptr CSize -> Int -> CSize -> IO () #

peekByteOff :: Ptr b -> Int -> IO CSize #

pokeByteOff :: Ptr b -> Int -> CSize -> IO () #

peek :: Ptr CSize -> IO CSize #

poke :: Ptr CSize -> CSize -> IO () #

Storable CTime 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CTime -> Int #

alignment :: CTime -> Int #

peekElemOff :: Ptr CTime -> Int -> IO CTime #

pokeElemOff :: Ptr CTime -> Int -> CTime -> IO () #

peekByteOff :: Ptr b -> Int -> IO CTime #

pokeByteOff :: Ptr b -> Int -> CTime -> IO () #

peek :: Ptr CTime -> IO CTime #

poke :: Ptr CTime -> CTime -> IO () #

Storable CUChar 
Instance details

Defined in Foreign.C.Types

Storable CUInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CUInt -> Int #

alignment :: CUInt -> Int #

peekElemOff :: Ptr CUInt -> Int -> IO CUInt #

pokeElemOff :: Ptr CUInt -> Int -> CUInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CUInt #

pokeByteOff :: Ptr b -> Int -> CUInt -> IO () #

peek :: Ptr CUInt -> IO CUInt #

poke :: Ptr CUInt -> CUInt -> IO () #

Storable CUIntMax 
Instance details

Defined in Foreign.C.Types

Storable CUIntPtr 
Instance details

Defined in Foreign.C.Types

Storable CULLong 
Instance details

Defined in Foreign.C.Types

Storable CULong 
Instance details

Defined in Foreign.C.Types

Storable CUSeconds 
Instance details

Defined in Foreign.C.Types

Storable CUShort 
Instance details

Defined in Foreign.C.Types

Storable CWchar 
Instance details

Defined in Foreign.C.Types

Storable IntPtr 
Instance details

Defined in Foreign.Ptr

Storable WordPtr 
Instance details

Defined in Foreign.Ptr

Storable Fingerprint

Since: base-4.4.0.0

Instance details

Defined in Foreign.Storable

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Storable Int8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Storable IoSubSystem

Since: base-4.9.0.0

Instance details

Defined in GHC.RTS.Flags

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Storable ()

Since: base-4.9.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: () -> Int #

alignment :: () -> Int #

peekElemOff :: Ptr () -> Int -> IO () #

pokeElemOff :: Ptr () -> Int -> () -> IO () #

peekByteOff :: Ptr b -> Int -> IO () #

pokeByteOff :: Ptr b -> Int -> () -> IO () #

peek :: Ptr () -> IO () #

poke :: Ptr () -> () -> IO () #

Storable Bool

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Storable Char

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Char -> Int #

alignment :: Char -> Int #

peekElemOff :: Ptr Char -> Int -> IO Char #

pokeElemOff :: Ptr Char -> Int -> Char -> IO () #

peekByteOff :: Ptr b -> Int -> IO Char #

pokeByteOff :: Ptr b -> Int -> Char -> IO () #

peek :: Ptr Char -> IO Char #

poke :: Ptr Char -> Char -> IO () #

Storable Double

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Float

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

pokeElemOff :: Ptr Float -> Int -> Float -> IO () #

peekByteOff :: Ptr b -> Int -> IO Float #

pokeByteOff :: Ptr b -> Int -> Float -> IO () #

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

Storable Int

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

peekElemOff :: Ptr Int -> Int -> IO Int #

pokeElemOff :: Ptr Int -> Int -> Int -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int #

pokeByteOff :: Ptr b -> Int -> Int -> IO () #

peek :: Ptr Int -> IO Int #

poke :: Ptr Int -> Int -> IO () #

Storable Word

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

pokeElemOff :: Ptr Word -> Int -> Word -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word #

pokeByteOff :: Ptr b -> Int -> Word -> IO () #

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Storable a => Storable (Complex a)

Since: base-4.8.0.0

Instance details

Defined in Data.Complex

Methods

sizeOf :: Complex a -> Int #

alignment :: Complex a -> Int #

peekElemOff :: Ptr (Complex a) -> Int -> IO (Complex a) #

pokeElemOff :: Ptr (Complex a) -> Int -> Complex a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Complex a) #

pokeByteOff :: Ptr b -> Int -> Complex a -> IO () #

peek :: Ptr (Complex a) -> IO (Complex a) #

poke :: Ptr (Complex a) -> Complex a -> IO () #

Storable a => Storable (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Storable a => Storable (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

sizeOf :: Down a -> Int #

alignment :: Down a -> Int #

peekElemOff :: Ptr (Down a) -> Int -> IO (Down a) #

pokeElemOff :: Ptr (Down a) -> Int -> Down a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Down a) #

pokeByteOff :: Ptr b -> Int -> Down a -> IO () #

peek :: Ptr (Down a) -> IO (Down a) #

poke :: Ptr (Down a) -> Down a -> IO () #

Storable (FunPtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: FunPtr a -> Int #

alignment :: FunPtr a -> Int #

peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) #

pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (FunPtr a) #

pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () #

peek :: Ptr (FunPtr a) -> IO (FunPtr a) #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () #

Storable (Ptr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ptr a -> Int #

alignment :: Ptr a -> Int #

peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) #

pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ptr a) #

pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () #

peek :: Ptr (Ptr a) -> IO (Ptr a) #

poke :: Ptr (Ptr a) -> Ptr a -> IO () #

(Storable a, Integral a) => Storable (Ratio a)

Since: base-4.8.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ratio a -> Int #

alignment :: Ratio a -> Int #

peekElemOff :: Ptr (Ratio a) -> Int -> IO (Ratio a) #

pokeElemOff :: Ptr (Ratio a) -> Int -> Ratio a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ratio a) #

pokeByteOff :: Ptr b -> Int -> Ratio a -> IO () #

peek :: Ptr (Ratio a) -> IO (Ratio a) #

poke :: Ptr (Ratio a) -> Ratio a -> IO () #

Storable (StablePtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: StablePtr a -> Int #

alignment :: StablePtr a -> Int #

peekElemOff :: Ptr (StablePtr a) -> Int -> IO (StablePtr a) #

pokeElemOff :: Ptr (StablePtr a) -> Int -> StablePtr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (StablePtr a) #

pokeByteOff :: Ptr b -> Int -> StablePtr a -> IO () #

peek :: Ptr (StablePtr a) -> IO (StablePtr a) #

poke :: Ptr (StablePtr a) -> StablePtr a -> IO () #

Prim a => Storable (PrimStorable a) 
Instance details

Defined in Data.Primitive.Types

Storable g => Storable (StateGen g) 
Instance details

Defined in System.Random.Internal

Methods

sizeOf :: StateGen g -> Int #

alignment :: StateGen g -> Int #

peekElemOff :: Ptr (StateGen g) -> Int -> IO (StateGen g) #

pokeElemOff :: Ptr (StateGen g) -> Int -> StateGen g -> IO () #

peekByteOff :: Ptr b -> Int -> IO (StateGen g) #

pokeByteOff :: Ptr b -> Int -> StateGen g -> IO () #

peek :: Ptr (StateGen g) -> IO (StateGen g) #

poke :: Ptr (StateGen g) -> StateGen g -> IO () #

Storable g => Storable (AtomicGen g) 
Instance details

Defined in System.Random.Stateful

Methods

sizeOf :: AtomicGen g -> Int #

alignment :: AtomicGen g -> Int #

peekElemOff :: Ptr (AtomicGen g) -> Int -> IO (AtomicGen g) #

pokeElemOff :: Ptr (AtomicGen g) -> Int -> AtomicGen g -> IO () #

peekByteOff :: Ptr b -> Int -> IO (AtomicGen g) #

pokeByteOff :: Ptr b -> Int -> AtomicGen g -> IO () #

peek :: Ptr (AtomicGen g) -> IO (AtomicGen g) #

poke :: Ptr (AtomicGen g) -> AtomicGen g -> IO () #

Storable g => Storable (IOGen g) 
Instance details

Defined in System.Random.Stateful

Methods

sizeOf :: IOGen g -> Int #

alignment :: IOGen g -> Int #

peekElemOff :: Ptr (IOGen g) -> Int -> IO (IOGen g) #

pokeElemOff :: Ptr (IOGen g) -> Int -> IOGen g -> IO () #

peekByteOff :: Ptr b -> Int -> IO (IOGen g) #

pokeByteOff :: Ptr b -> Int -> IOGen g -> IO () #

peek :: Ptr (IOGen g) -> IO (IOGen g) #

poke :: Ptr (IOGen g) -> IOGen g -> IO () #

Storable g => Storable (STGen g) 
Instance details

Defined in System.Random.Stateful

Methods

sizeOf :: STGen g -> Int #

alignment :: STGen g -> Int #

peekElemOff :: Ptr (STGen g) -> Int -> IO (STGen g) #

pokeElemOff :: Ptr (STGen g) -> Int -> STGen g -> IO () #

peekByteOff :: Ptr b -> Int -> IO (STGen g) #

pokeByteOff :: Ptr b -> Int -> STGen g -> IO () #

peek :: Ptr (STGen g) -> IO (STGen g) #

poke :: Ptr (STGen g) -> STGen g -> IO () #

Storable g => Storable (TGen g) 
Instance details

Defined in System.Random.Stateful

Methods

sizeOf :: TGen g -> Int #

alignment :: TGen g -> Int #

peekElemOff :: Ptr (TGen g) -> Int -> IO (TGen g) #

pokeElemOff :: Ptr (TGen g) -> Int -> TGen g -> IO () #

peekByteOff :: Ptr b -> Int -> IO (TGen g) #

pokeByteOff :: Ptr b -> Int -> TGen g -> IO () #

peek :: Ptr (TGen g) -> IO (TGen g) #

poke :: Ptr (TGen g) -> TGen g -> IO () #

Prim a => Storable (PVar a RealWorld)

poke+peek will result in a new copy of a PVar

Instance details

Defined in Data.Primitive.PVar.Internal

Storable a => Storable (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

sizeOf :: Const a b -> Int #

alignment :: Const a b -> Int #

peekElemOff :: Ptr (Const a b) -> Int -> IO (Const a b) #

pokeElemOff :: Ptr (Const a b) -> Int -> Const a b -> IO () #

peekByteOff :: Ptr b0 -> Int -> IO (Const a b) #

pokeByteOff :: Ptr b0 -> Int -> Const a b -> IO () #

peek :: Ptr (Const a b) -> IO (Const a b) #

poke :: Ptr (Const a b) -> Const a b -> IO () #

mallocCompute :: forall r ix e. (Size r, Load r ix e, Storable e) => Array r ix e -> IO (Array S ix e) Source #

Very similar to computeAs S except load the source array into memory allocated with malloc on C heap. It can potentially be useful when iteroperating with some C programs.

Since: 0.5.9

mallocCopy :: forall ix e. (Index ix, Storable e) => Array S ix e -> IO (Array S ix e) Source #

Allocate memory on C heap with malloc and copy the source array over.

Since: 0.5.9

Conversion

Storable Vector

toStorableVector :: Index ix => Array S ix e -> Vector e Source #

O(1) - Unwrap storable array and pull out the underlying storable vector.

Since: 0.2.1

toStorableMVector :: Index ix => MArray s S ix e -> MVector s e Source #

O(1) - Unwrap storable mutable array and pull out the underlying storable mutable vector.

Since: 0.2.1

fromStorableVector :: Comp -> Vector e -> Vector S e Source #

O(1) - Cast a storable vector to a storable array.

Since: 0.5.0

fromStorableMVector :: MVector s e -> MVector s S e Source #

O(1) - Cast a mutable storable vector to a mutable storable array.

Since: 0.5.0

Direct Pointer Access

withPtr :: MonadUnliftIO m => MArray RealWorld S ix e -> (Ptr e -> m b) -> m b Source #

A pointer to the beginning of the mutable array.

Since: 0.1.3

Unboxed

data U Source #

Representation for Unboxed elements

Constructors

U 

Instances

Instances details
Show U Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

showsPrec :: Int -> U -> ShowS #

show :: U -> String #

showList :: [U] -> ShowS #

Size U Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

size :: Array U ix e -> Sz ix Source #

unsafeResize :: (Index ix, Index ix') => Sz ix' -> Array U ix e -> Array U ix' e Source #

Strategy U Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

setComp :: Comp -> Array U ix e -> Array U ix e Source #

getComp :: Array U ix e -> Comp Source #

repr :: U

Unbox e => Manifest U e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

unsafeLinearIndexM :: Index ix => Array U ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s U ix e -> Sz ix Source #

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

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s U ix e -> MVector s U e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array U ix e -> m (MArray (PrimState m) U ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) U ix e -> m (Array U ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) U ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) U ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) U ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) U ix' e -> Ix1 -> MArray (PrimState m) U ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array U ix' e -> Ix1 -> MArray (PrimState m) U ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Sz ix -> m (MArray (PrimState m) U ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Sz ix -> m (MArray (PrimState m) U ix e) Source #

Index ix => Shape U ix Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Unbox e => Source U e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

unsafeIndex :: Index ix => Array U ix e -> ix -> e Source #

unsafeLinearIndex :: Index ix => Array U ix e -> Int -> e Source #

unsafePrefIndex :: Index ix => Array U ix e -> PrefIndex ix e Source #

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

unsafeLinearSlice :: Index ix => Ix1 -> Sz1 -> Array U ix e -> Array U Ix1 e Source #

(Unbox e, Num e) => FoldNumeric U e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

sumArray :: Index ix => Array U ix e -> e Source #

productArray :: Index ix => Array U ix e -> e Source #

powerSumArray :: Index ix => Array U ix e -> Int -> e Source #

unsafeDotProduct :: Index ix => Array U ix e -> Array U ix e -> e Source #

foldArray :: Index ix => (e -> e -> e) -> e -> Array U ix e -> e Source #

(Unbox e, Num e) => Numeric U e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

plusScalar :: Index ix => Array U ix e -> e -> Array U ix e Source #

minusScalar :: Index ix => Array U ix e -> e -> Array U ix e Source #

scalarMinus :: Index ix => e -> Array U ix e -> Array U ix e Source #

multiplyScalar :: Index ix => Array U ix e -> e -> Array U ix e Source #

absPointwise :: Index ix => Array U ix e -> Array U ix e Source #

additionPointwise :: Index ix => Array U ix e -> Array U ix e -> Array U ix e Source #

subtractionPointwise :: Index ix => Array U ix e -> Array U ix e -> Array U ix e Source #

multiplicationPointwise :: Index ix => Array U ix e -> Array U ix e -> Array U ix e Source #

powerPointwise :: Index ix => Array U ix e -> Int -> Array U ix e Source #

unsafeLiftArray :: Index ix => (e -> e) -> Array U ix e -> Array U ix e Source #

unsafeLiftArray2 :: Index ix => (e -> e -> e) -> Array U ix e -> Array U ix e -> Array U ix e Source #

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

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

makeArray :: Comp -> Sz ix -> (ix -> e) -> Array U ix e Source #

makeArrayLinear :: Comp -> Sz ix -> (Int -> e) -> Array U ix e Source #

replicate :: Comp -> Sz ix -> e -> Array U ix e Source #

iterArrayLinearST_ :: Scheduler s () -> Array U ix e -> (Int -> e -> ST s ()) -> ST s () Source #

iterArrayLinearWithSetST_ :: Scheduler s () -> Array U ix e -> (Ix1 -> e -> ST s ()) -> (Ix1 -> Sz1 -> e -> ST s ()) -> ST s () Source #

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

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

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

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

toStream :: Array U ix e -> Steps Id e Source #

toStreamIx :: Array U ix e -> Steps Id (ix, e) Source #

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

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

iterArrayLinearWithStrideST_ :: Scheduler s () -> Stride ix -> Sz ix -> Array U ix e -> (Int -> e -> ST s ()) -> ST s () Source #

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

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

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

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

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

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

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

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

data Array U ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

data Array U ix e = UArray {}
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)
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)

class (Vector Vector a, MVector MVector a) => Unbox a #

Instances

Instances details
Unbox All 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Any 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Ix2 Source #

Unboxing of a Ix2.

Instance details

Defined in Data.Massiv.Core.Index.Ix

Unbox () 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Char 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Double 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Float 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Int 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Word 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

(3 <= n, Unbox (Ix (n - 1))) => Unbox (IxN n) Source #

Unboxing of a IxN.

Instance details

Defined in Data.Massiv.Core.Index.Ix

(Unbox a, Unbox b) => Unbox (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b) => Unbox (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox (f a) => Unbox (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b, Unbox c) => Unbox (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b, Unbox c, Unbox d) => Unbox (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox (f (g a)) => Unbox (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Unbox (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Unbox (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

Conversion

Unboxed Vector

toUnboxedVector :: Array U ix e -> Vector e Source #

O(1) - Unwrap unboxed array and pull out the underlying unboxed vector.

Since: 0.2.1

toUnboxedMVector :: MArray s U ix e -> MVector s e Source #

O(1) - Unwrap unboxed mutable array and pull out the underlying unboxed mutable vector.

Since: 0.2.1

fromUnboxedVector :: Unbox e => Comp -> Vector e -> Vector U e Source #

O(1) - Wrap an unboxed vector and produce an unboxed flat array.

Since: 0.6.0

fromUnboxedMVector :: Unbox e => MVector s e -> MVector s U e Source #

O(1) - Wrap an unboxed mutable vector and produce a mutable unboxed flat array.

Since: 0.5.0

ByteString Conversion

fromByteString Source #

Arguments

:: Load r Ix1 Word8 
=> Comp

Computation strategy

-> ByteString

Strict ByteString to use as a source.

-> Vector r Word8 

O(n) - Convert a strict ByteString into a manifest array. Will return Nothing if length doesn't match the total number of elements of new array.

Since: 0.2.1

castFromByteString :: Comp -> ByteString -> Vector S Word8 Source #

O(1) - Cast a strict ByteString into a Storable array

Since: 0.3.0

toByteString Source #

Arguments

:: Load r ix Word8 
=> Array r ix Word8

Source array

-> ByteString 

O(n) - Convert any source array into a strict ByteString. In case when the source array is actually storable, no memory copy will occur.

Since: 0.2.1

castToByteString :: Index ix => Array S ix Word8 -> ByteString Source #

O(1) - Cast a Storable array into a strict ByteString

Since: 0.3.0

toBuilder :: (Index ix, Source r e) => (e -> Builder) -> Array r ix e -> Builder Source #

O(n) - Conversion of array monoidally into a ByteString Builder.

Since: 0.2.1

castToBuilder :: Index ix => Array S ix Word8 -> Builder Source #

O(1) - Cast a storable array of Word8 to ByteString Builder.

Since: 0.5.0