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

Data.Massiv.Array.Delayed

Description

 
Synopsis

Delayed

Delayed Pull Array

data D Source #

Delayed representation.

Constructors

D 

Instances

Instances details
Show D Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

showsPrec :: Int -> D -> ShowS #

show :: D -> String #

showList :: [D] -> ShowS #

Size D Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

Strategy D Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

Source D e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

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

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

Index ix => Shape D ix Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Floating e => NumericFloat D e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

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

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

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

Num e => Numeric D e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

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

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

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

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

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

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

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

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

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

Num e => FoldNumeric D e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

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

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

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

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

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

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

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

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

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

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

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

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

Functor (Array D ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

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

Defined in Data.Massiv.Array.Delayed.Pull

Methods

pure :: a -> Array D ix a #

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

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

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

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

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

Row-major sequential folding over a Delayed array.

Instance details

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

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

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

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

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

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

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

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

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

null :: Array D ix a -> Bool #

length :: Array D ix a -> Int #

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

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

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

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

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

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

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

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

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

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

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

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

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

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

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

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

Defined in Data.Massiv.Array.Delayed.Pull

Methods

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

show :: Array D ix e -> String #

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

data Array D ix e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Pull

data Array D ix e = DArray {}

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

O(1) Conversion from a source array to D representation.

liftArray2' :: (HasCallStack, Index ix, Source r1 a, Source r2 b) => (a -> b -> e) -> Array r1 ix a -> Array r2 ix b -> Array D ix e Source #

Same as liftArray2M, but throws an imprecise exception on mismatched sizes.

Since: 1.0.0

liftArray2M :: (Index ix, Source r1 a, Source r2 b, MonadThrow m) => (a -> b -> e) -> Array r1 ix a -> Array r2 ix b -> m (Array D ix e) Source #

Similar to zipWith, except dimensions of both arrays have to be the same, otherwise it throws SizeMismatchException.

Since: 1.0.0

Delayed Push Array

data DL Source #

Delayed load representation. Also known as Push array.

Constructors

DL 

Instances

Instances details
Show DL Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

Methods

showsPrec :: Int -> DL -> ShowS #

show :: DL -> String #

showList :: [DL] -> ShowS #

Size DL Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

Methods

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

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

Strategy DL Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

Methods

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

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

Index ix => Shape DL ix Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

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

Defined in Data.Massiv.Array.Delayed.Push

Methods

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

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

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

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

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

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

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

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

Defined in Data.Massiv.Array.Delayed.Push

Methods

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

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

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

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

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

show :: Array DL ix e -> String #

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

Semigroup (Array DL Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

Methods

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

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

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

Monoid (Array DL Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

Methods

mempty :: Array DL Ix1 e #

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

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

data Array DL ix e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Push

data Array DL ix e = DLArray {}

toLoadArray :: forall r ix e. (Size r, Load r ix e) => Array r ix e -> Array DL ix e Source #

Convert any Loadable array into DL representation.

Since: 0.3.0

makeLoadArrayS Source #

Arguments

:: forall ix e. Index ix 
=> Sz ix

Size of the resulting array

-> e

Default value to use for all cells that might have been ommitted by the writing function

-> (forall m. Monad m => (ix -> e -> m Bool) -> m ())

Writing function that described which elements to write into the target array.

-> Array DL ix e 

Describe how an array should be loaded into memory sequentially. For parallelizable version see makeLoadArray.

Since: 0.3.1

makeLoadArray Source #

Arguments

:: forall ix e. Index ix 
=> Comp

Computation strategy to use. Directly affects the scheduler that gets created for the loading function.

-> Sz ix

Size of the resulting array

-> e

Default value to use for all cells that might have been ommitted by the writing function

-> (forall s. Scheduler s () -> (ix -> e -> ST s Bool) -> ST s ())

Writing function that described which elements to write into the target array. It accepts a scheduler, that can be used for parallelization, as well as a safe element writing function.

-> Array DL ix e 

Specify how an array should be loaded into memory. Unlike makeLoadArrayS, loading function accepts a scheduler, thus can be parallelized. If you need an unsafe version of this function see unsafeMakeLoadArray.

Since: 0.4.0

fromStrideLoad :: forall r ix e. StrideLoad r ix e => Stride ix -> Array r ix e -> Array DL ix e Source #

Convert an array that can be loaded with stride into DL representation.

Since: 0.3.0

Delayed Stream Array

data DS Source #

Delayed stream array that represents a sequence of values that can be loaded sequentially. Important distinction from other arrays is that its size might no be known until it is computed.

Constructors

DS 

Instances

Instances details
Strategy DS Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

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

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

Shape DS Ix1 Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Load DS Ix1 e Source #

O(n) - size implementation.

Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

makeArray :: Comp -> Sz Ix1 -> (Ix1 -> e) -> Array DS Ix1 e Source #

makeArrayLinear :: Comp -> Sz Ix1 -> (Int -> e) -> Array DS Ix1 e Source #

replicate :: Comp -> Sz Ix1 -> e -> Array DS Ix1 e Source #

iterArrayLinearST_ :: Scheduler s () -> Array DS Ix1 e -> (Int -> e -> ST s ()) -> ST s () Source #

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

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

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

Stream DS Ix1 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

toStream :: Array DS Ix1 e -> Steps Id e Source #

toStreamIx :: Array DS Ix1 e -> Steps Id (Ix1, e) Source #

Monad (Array DS Ix1) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

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

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

return :: a -> Array DS Ix1 a #

Functor (Array DS Ix1) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

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

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

Applicative (Array DS Ix1) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

pure :: a -> Array DS Ix1 a #

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

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

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

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

Foldable (Array DS Ix1) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

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

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

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

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

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

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

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

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

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

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

null :: Array DS Ix1 a -> Bool #

length :: Array DS Ix1 a -> Int #

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

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

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

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

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

IsList (Array DS Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Associated Types

type Item (Array DS Ix1 e) #

Methods

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

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

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

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

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

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

show :: Array DS Ix1 e -> String #

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

Semigroup (Array DS Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

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

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

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

Monoid (Array DS Ix1 e) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

Methods

mempty :: Array DS Ix1 e #

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

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

newtype Array DS Ix1 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Stream

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

Defined in Data.Massiv.Array.Delayed.Stream

type Item (Array DS Ix1 e) = e

toStreamArray :: (Index ix, Source r e) => Array r ix e -> Vector DS e Source #

Flatten an array into a stream of values.

Since: 0.4.1

toSteps :: Vector DS e -> Steps Id e Source #

O(1) - Convert delayed stream array into Steps.

Since: 0.4.1

fromSteps :: Steps Id e -> Vector DS e Source #

O(1) - Convert Steps into delayed stream array

Since: 0.4.1

Delayed Interleaved Array

data DI Source #

Delayed array that will be loaded in an interleaved fashion during parallel computation.

Constructors

DI 

Instances

Instances details
Size DI Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

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

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

Strategy DI Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

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

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

Index ix => Shape DI ix Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

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

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

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

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

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

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

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

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

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

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

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

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

Functor (Array DI ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

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

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

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

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

pure :: a -> Array DI ix a #

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

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

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

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

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

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

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

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

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

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

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

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

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

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

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

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

null :: Array DI ix a -> Bool #

length :: Array DI ix a -> Int #

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

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

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

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

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

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

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

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

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

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

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

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

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

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

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

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

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

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

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

Defined in Data.Massiv.Array.Delayed.Interleaved

Methods

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

show :: Array DI ix e -> String #

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

newtype Array DI ix e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Interleaved

newtype Array DI ix e = DIArray {}

toInterleaved :: (Index ix, Source r e) => Array r ix e -> Array DI ix e Source #

Convert a source array into an array that, when computed, will have its elemets evaluated out of order (interleaved amongst cores), hence making unbalanced computation better parallelizable.

fromInterleaved :: Array DI ix e -> Array D ix e Source #

O(1) - Unwrap the interleved array.

Since: 0.2.1

Delayed Windowed Array

data DW Source #

Delayed Windowed Array representation.

Constructors

DW 

Instances

Instances details
Strategy DW Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

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

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

Index ix => Shape DW ix Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

StrideLoad DW Ix1 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

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

StrideLoad DW Ix2 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

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

Load DW Ix1 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

makeArray :: Comp -> Sz Ix1 -> (Ix1 -> e) -> Array DW Ix1 e Source #

makeArrayLinear :: Comp -> Sz Ix1 -> (Int -> e) -> Array DW Ix1 e Source #

replicate :: Comp -> Sz Ix1 -> e -> Array DW Ix1 e Source #

iterArrayLinearST_ :: Scheduler s () -> Array DW Ix1 e -> (Int -> e -> ST s ()) -> ST s () Source #

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

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

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

Load DW Ix2 e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

makeArray :: Comp -> Sz Ix2 -> (Ix2 -> e) -> Array DW Ix2 e Source #

makeArrayLinear :: Comp -> Sz Ix2 -> (Int -> e) -> Array DW Ix2 e Source #

replicate :: Comp -> Sz Ix2 -> e -> Array DW Ix2 e Source #

iterArrayLinearST_ :: Scheduler s () -> Array DW Ix2 e -> (Int -> e -> ST s ()) -> ST s () Source #

iterArrayLinearWithSetST_ :: Scheduler s () -> Array DW Ix2 e -> (Ix1 -> e -> ST s ()) -> (Ix1 -> Sz1 -> e -> ST s ()) -> ST s () Source #

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

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

(Index (IxN n), StrideLoad DW (Ix (n - 1)) e) => StrideLoad DW (IxN n) e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

iterArrayLinearWithStrideST_ :: Scheduler s () -> Stride (IxN n) -> Sz (IxN n) -> Array DW (IxN n) e -> (Int -> e -> ST s ()) -> ST s () Source #

(Index (IxN n), Load DW (Ix (n - 1)) e) => Load DW (IxN n) e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

makeArray :: Comp -> Sz (IxN n) -> (IxN n -> e) -> Array DW (IxN n) e Source #

makeArrayLinear :: Comp -> Sz (IxN n) -> (Int -> e) -> Array DW (IxN n) e Source #

replicate :: Comp -> Sz (IxN n) -> e -> Array DW (IxN n) e Source #

iterArrayLinearST_ :: Scheduler s () -> Array DW (IxN n) e -> (Int -> e -> ST s ()) -> ST s () Source #

iterArrayLinearWithSetST_ :: Scheduler s () -> Array DW (IxN n) e -> (Ix1 -> e -> ST s ()) -> (Ix1 -> Sz1 -> e -> ST s ()) -> ST s () Source #

unsafeLoadIntoST :: Manifest r' e => MVector s r' e -> Array DW (IxN n) e -> ST s (MArray s r' (IxN n) e) Source #

unsafeLoadIntoIO :: Manifest r' e => MVector RealWorld r' e -> Array DW (IxN n) e -> IO (MArray RealWorld r' (IxN n) e) Source #

Functor (Array DW ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

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

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

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

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

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

show :: Array DW ix e -> String #

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

data Array DW ix e Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

data Array DW ix e = DWArray {}

data Window ix e Source #

Constructors

Window 

Fields

  • windowStart :: !ix

    Index of where window will start at.

  • windowSize :: !(Sz ix)

    Size of the window

  • windowIndex :: ix -> e

    Indexing function for the window

  • windowUnrollIx2 :: !(Maybe Int)

    Setting this value during stencil application improves cache utilization by unrolling the loop for Ix2 and higher dimensions. Has no affect on arrays with one dimension.

Instances

Instances details
Functor (Window ix) Source # 
Instance details

Defined in Data.Massiv.Array.Delayed.Windowed

Methods

fmap :: (a -> b) -> Window ix a -> Window ix b #

(<$) :: a -> Window ix b -> Window ix a #

insertWindow Source #

Arguments

:: Index ix 
=> Array D ix e

Source array that will have a window inserted into it

-> Window ix e

Window to place inside the delayed array

-> Array DW ix e 

Inserts a Window into a delayed array while scaling the window down if it doesn't fit inside that array.

Since: 0.3.0

getWindow :: Array DW ix e -> Maybe (Window ix e) Source #

Get the Window from a windowed array.

Since: 0.2.1

dropWindow :: Array DW ix e -> Array D ix e Source #

Drop the Window from a windowed array.

Since: 0.3.0

makeWindowedArray Source #

Arguments

:: (Index ix, Source r e) 
=> Array r ix e

Source array that will have a window inserted into it

-> ix

Start index for the window

-> Sz ix

Size of the window

-> (ix -> e)

Indexing function foto use inside window

-> Array DW ix e 

Construct a delayed windowed array by supply a separate element producing function for the interior of an array. This is very usful for stencil mapping, where interior function does not perform boundary checks, thus significantly speeding up computation process.

Since: 0.1.3