Copyright | (c) Alexey Kuleshevich 2018-2022 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data D = D
- delay :: (Index ix, Source r e) => Array r ix e -> Array D ix e
- 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
- 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)
- data DL = DL
- toLoadArray :: forall r ix e. (Size r, Load r ix e) => Array r ix e -> Array DL ix e
- makeLoadArrayS :: forall ix e. Index ix => Sz ix -> e -> (forall m. Monad m => (ix -> e -> m Bool) -> m ()) -> Array DL ix e
- makeLoadArray :: forall ix e. Index ix => Comp -> Sz ix -> e -> (forall s. Scheduler s () -> (ix -> e -> ST s Bool) -> ST s ()) -> Array DL ix e
- fromStrideLoad :: forall r ix e. StrideLoad r ix e => Stride ix -> Array r ix e -> Array DL ix e
- data DS = DS
- toStreamArray :: (Index ix, Source r e) => Array r ix e -> Vector DS e
- toSteps :: Vector DS e -> Steps Id e
- fromSteps :: Steps Id e -> Vector DS e
- data DI = DI
- toInterleaved :: (Index ix, Source r e) => Array r ix e -> Array DI ix e
- fromInterleaved :: Array DI ix e -> Array D ix e
- data DW = DW
- data Window ix e = Window {
- windowStart :: !ix
- windowSize :: !(Sz ix)
- windowIndex :: ix -> e
- windowUnrollIx2 :: !(Maybe Int)
- insertWindow :: Index ix => Array D ix e -> Window ix e -> Array DW ix e
- getWindow :: Array DW ix e -> Maybe (Window ix e)
- dropWindow :: Array DW ix e -> Array D ix e
- makeWindowedArray :: (Index ix, Source r e) => Array r ix e -> ix -> Sz ix -> (ix -> e) -> Array DW ix e
Delayed
Delayed Pull Array
Delayed representation.
Instances
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
Delayed load representation. Also known as Push array.
Instances
:: 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
:: 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
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.
Instances
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
Delayed array that will be loaded in an interleaved fashion during parallel computation.
Warning - Will be deprecated in the next major version update.
Instances
Size DI Source # | |
Strategy DI Source # | |
Index ix => Shape DI ix Source # | |
Index ix => Load DI ix e Source # | |
Defined in Data.Massiv.Array.Delayed.Interleaved 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 # | |
Index ix => StrideLoad DI ix e Source # | |
Index ix => Foldable (Array DI ix) Source # | |
Defined in Data.Massiv.Array.Delayed.Interleaved 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 # | |
Index ix => Applicative (Array DI ix) Source # | |
Defined in Data.Massiv.Array.Delayed.Interleaved | |
Functor (Array DI ix) Source # | |
(Ragged L ix e, Show e) => Show (Array DI ix e) Source # | |
(Index ix, Eq e) => Eq (Array DI ix e) Source # | |
(Index ix, Ord e) => Ord (Array DI ix e) Source # | |
Defined in Data.Massiv.Array.Delayed.Interleaved 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 # | |
newtype Array DI ix e Source # | |
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
Delayed Windowed Array representation.
Instances
Window | |
|
:: 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
:: (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