Copyright | (c) Alexey Kuleshevich 2018 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Data.Massiv.Core
Description
- data family Array r ix e :: *
- type family Elt r ix e :: * where ...
- type family EltRepr r ix :: *
- class (Typeable r, Index ix) => Construct r ix e
- class Size r ix e => Source r ix e
- class Size r ix e => Load r ix e where
- class Construct r ix e => Size r ix e
- class Size r ix e => Slice r ix e
- class OuterSlice r ix e where
- class Size r ix e => InnerSlice r ix e
- class Source r ix e => Manifest r ix e
- class Manifest r ix e => Mutable r ix e
- class Construct r ix e => Ragged r ix e where
- class Nested r ix e where
- type family NestedStruct r ix e :: *
- data L = L
- data LN
- type family ListItem ix e :: * where ...
- data Comp
- pattern Par :: Comp
- module Data.Massiv.Core.Index
- elemsCount :: Size r ix e => Array r ix e -> Int
- isEmpty :: Size r ix e => Array r ix e -> Bool
Documentation
data family Array r ix e :: * Source #
The array family. Representations r
describes how data is arranged or computed. All arrays
have a common property that each index ix
always maps to the same unique element, even if that
element does not exist in memory and has to be computed upon lookup. Data is always arranged in a
nested fasion, depth of which is controlled by
.Rank
ix
Instances
Functor (Array D ix) # | |
Functor (Array DW ix) # | |
Functor (Array DI ix) # | |
Index ix => Applicative (Array D ix) # | |
Index ix => Foldable (Array D ix) # | Row-major sequential folding over a delayed array. |
Index ix => Foldable (Array M ix) # | Row-major sequential folding over a Manifest array. |
Index ix => Foldable (Array B ix) # | Row-major sequential folding over a Boxed array. |
Nested LN ix e => IsList (Array L ix e) # | |
Nested LN ix e => IsList (Array LN ix e) # | |
(Unbox e, IsList (Array L ix e), Nested LN ix e, Nested L ix e, Ragged L ix e) => IsList (Array U ix e) # | |
(Storable e, IsList (Array L ix e), Nested LN ix e, Nested L ix e, Ragged L ix e) => IsList (Array S ix e) # | |
(Prim e, IsList (Array L ix e), Nested LN ix e, Nested L ix e, Ragged L ix e) => IsList (Array P ix e) # | |
(NFData e, IsList (Array L ix e), Nested LN ix e, Nested L ix e, Ragged L ix e) => IsList (Array N ix e) # | |
(IsList (Array L ix e), Nested LN ix e, Nested L ix e, Ragged L ix e) => IsList (Array B ix e) # | |
(Eq e, Index ix) => Eq (Array D ix e) # | |
(Unbox e, Eq e, Index ix) => Eq (Array U ix e) # | |
(Storable e, Eq e, Index ix) => Eq (Array S ix e) # | |
(Prim e, Eq e, Index ix) => Eq (Array P ix e) # | |
(Index ix, NFData e, Eq e) => Eq (Array N ix e) # | |
(Index ix, Eq e) => Eq (Array B ix e) # | |
(Index ix, Floating e) => Floating (Array D ix e) # | |
(Index ix, Fractional e) => Fractional (Array D ix e) # | |
(Index ix, Num e) => Num (Array D ix e) # | |
(Ragged L ix e, Show e) => Show (Array L ix e) # | |
(Ragged L ix e, Nested LN ix e, Show e) => Show (Array LN ix e) # | |
(Index ix, NFData e) => NFData (Array U ix e) # | |
(Index ix, NFData e) => NFData (Array S ix e) # | |
(Index ix, NFData e) => NFData (Array P ix e) # | |
(Index ix, NFData e) => NFData (Array N ix e) # | |
(Index ix, NFData e) => NFData (Array B ix e) # | |
data Array L Source # | |
data Array LN Source # | |
data Array D Source # | |
data Array M Source # | |
data Array DW Source # | |
data Array DI Source # | |
data Array U Source # | |
data Array S Source # | |
data Array P Source # | |
data Array N Source # | |
data Array B Source # | |
type Item (Array L ix e) # | |
type Item (Array LN ix e) # | |
type Item (Array U ix e) # | |
type Item (Array S ix e) # | |
type Item (Array P ix e) # | |
type Item (Array N ix e) # | |
type Item (Array B ix e) # | |
class (Typeable r, Index ix) => Construct r ix e Source #
Array types that can be constructed.
Minimal complete definition
Instances
(Index ix, Ragged L ix e, Ragged L (Lower ix) e, (~) * (Elt L ix e) (Array L (Lower ix) e)) => Construct L ix e Source # | |
Construct L Ix1 e Source # | |
Index ix => Construct D ix e Source # | |
Index ix => Construct M ix e Source # | |
Index ix => Construct DW ix e Source # | |
Index ix => Construct DI ix e Source # | |
(Unbox e, Index ix) => Construct U ix e Source # | |
(Storable e, Index ix) => Construct S ix e Source # | |
(Prim e, Index ix) => Construct P ix e Source # | |
(Index ix, NFData e) => Construct N ix e Source # | |
Index ix => Construct B ix e Source # | |
class Size r ix e => Source r ix e Source #
Arrays that can be used as source to practically any manipulation function.
Instances
class Size r ix e => Load r ix e where Source #
Any array that can be computed
Methods
Arguments
:: Monad m | |
=> Array r ix e | Array that is being loaded |
-> (Int -> m e) | Function that reads an element from target array |
-> (Int -> e -> m ()) | Function that writes an element into target array |
-> m () |
Load an array into memory sequentially
Arguments
:: [Int] | List of capabilities to run workers on, as described in
|
-> Array r ix e | Array that is being loaded |
-> (Int -> IO e) | Function that reads an element from target array |
-> (Int -> e -> IO ()) | Function that writes an element into target array |
-> IO () |
Load an array into memory in parallel
class Construct r ix e => Size r ix e Source #
An array that contains size information. They can be resized and new arrays extracted from it in constant time.
Minimal complete definition
Instances
Index ix => Size D ix e Source # | |
Index ix => Size M ix e Source # | |
Index ix => Size DW ix e Source # | Any resize or extract on Windowed Array will hurt the performance. |
Index ix => Size DI ix e Source # | |
(Unbox e, Index ix) => Size U ix e Source # | |
(Storable e, Index ix) => Size S ix e Source # | |
(Prim e, Index ix) => Size P ix e Source # | |
(Index ix, NFData e) => Size N ix e Source # | |
Index ix => Size B ix e Source # | |
class Size r ix e => Slice r ix e Source #
Minimal complete definition
Instances
(Index ix, Index (Lower ix), (~) * (Elt D ix e) (Array D (Lower ix) e)) => Slice D ix e Source # | |
(Index ix, Index (Lower ix), (~) * (Elt M ix e) (Array M (Lower ix) e)) => Slice M ix e Source # | |
Slice M Ix1 e Source # | |
(Unbox e, Index ix, Index (Lower ix), (~) * (Elt U ix e) (Elt M ix e), (~) * (Elt M ix e) (Array M (Lower ix) e)) => Slice U ix e Source # | |
Unbox e => Slice U Ix1 e Source # | |
(Prim e, Index ix, Index (Lower ix), (~) * (Elt P ix e) (Elt M ix e), (~) * (Elt M ix e) (Array M (Lower ix) e)) => Slice P ix e Source # | |
Prim e => Slice P Ix1 e Source # | |
class OuterSlice r ix e where Source #
Minimal complete definition
Methods
outerLength :: Array r ix e -> Int Source #
Instances
Ragged L ix e => OuterSlice L ix e Source # | |
OuterSlice L Ix1 e Source # | |
((~) * (Elt D ix e) (Array D (Lower ix) e), Index ix) => OuterSlice D ix e Source # | |
((~) * (Elt M ix e) (Array M (Lower ix) e), Index ix, Index (Lower ix)) => OuterSlice M ix e Source # | |
OuterSlice M Ix1 e Source # | |
(Unbox e, Index ix, Index (Lower ix), (~) * (Elt U ix e) (Elt M ix e), (~) * (Elt M ix e) (Array M (Lower ix) e)) => OuterSlice U ix e Source # | |
Unbox e => OuterSlice U Ix1 e Source # | |
(Storable e, Index ix, Index (Lower ix), (~) * (Elt M ix e) (Array M (Lower ix) e), (~) * (Elt S ix e) (Array M (Lower ix) e)) => OuterSlice S ix e Source # | |
(Prim e, Index ix, Index (Lower ix), (~) * (Elt M ix e) (Array M (Lower ix) e), (~) * (Elt P ix e) (Array M (Lower ix) e)) => OuterSlice P ix e Source # | |
Prim e => OuterSlice P Ix1 e Source # | |
(NFData e, Index ix, Index (Lower ix), (~) * (Elt M ix e) (Array M (Lower ix) e), (~) * (Elt N ix e) (Array M (Lower ix) e)) => OuterSlice N ix e Source # | |
(NFData e, Index ix, Index (Lower ix), (~) * (Elt M ix e) (Array M (Lower ix) e), (~) * (Elt B ix e) (Array M (Lower ix) e)) => OuterSlice B ix e Source # | |
class Size r ix e => InnerSlice r ix e Source #
Minimal complete definition
Instances
((~) * (Elt D ix e) (Array D (Lower ix) e), Index ix) => InnerSlice D ix e Source # | |
((~) * (Elt M ix e) (Array M (Lower ix) e), Index ix, Index (Lower ix)) => InnerSlice M ix e Source # | |
InnerSlice M Ix1 e Source # | |
(Unbox e, Index ix, Index (Lower ix), (~) * (Elt U ix e) (Elt M ix e), (~) * (Elt M ix e) (Array M (Lower ix) e)) => InnerSlice U ix e Source # | |
Unbox e => InnerSlice U Ix1 e Source # | |
(Storable e, Index ix, Index (Lower ix), (~) * (Elt M ix e) (Array M (Lower ix) e), (~) * (Elt S ix e) (Array M (Lower ix) e)) => InnerSlice S ix e Source # | |
(Prim e, Index ix, Index (Lower ix), (~) * (Elt M ix e) (Array M (Lower ix) e), (~) * (Elt P ix e) (Array M (Lower ix) e)) => InnerSlice P ix e Source # | |
Prim e => InnerSlice P Ix1 e Source # | |
(NFData e, Index ix, Index (Lower ix), (~) * (Elt M ix e) (Array M (Lower ix) e), (~) * (Elt N ix e) (Array M (Lower ix) e)) => InnerSlice N ix e Source # | |
(NFData e, Index ix, Index (Lower ix), (~) * (Elt M ix e) (Array M (Lower ix) e), (~) * (Elt B ix e) (Array M (Lower ix) e)) => InnerSlice B ix e Source # | |
class Source r ix e => Manifest r ix e Source #
Manifest arrays are backed by actual memory and values are looked up versus
computed as it is with delayed arrays. Because of this fact indexing functions
(
, !
)(
, etc. are constrained to manifest arrays only.!?
)
Minimal complete definition
class Manifest r ix e => Mutable r ix e Source #
Minimal complete definition
msize, unsafeThaw, unsafeFreeze, unsafeNew, unsafeNewZero, unsafeLinearRead, unsafeLinearWrite
class Construct r ix e => Ragged r ix e where Source #
Minimal complete definition
empty, isNull, cons, uncons, unsafeGenerateM, edgeSize, flatten, loadRagged, raggedFormat
Methods
empty :: Comp -> Array r ix e Source #
isNull :: Array r ix e -> Bool Source #
cons :: Elt r ix e -> Array r ix e -> Array r ix e Source #
uncons :: Array r ix e -> Maybe (Elt r ix e, Array r ix e) Source #
edgeSize :: Array r ix e -> ix Source #
flatten :: Array r ix e -> Array r Ix1 e Source #
loadRagged :: (IO () -> IO ()) -> (Int -> e -> IO a) -> Int -> Int -> Lower ix -> Array r ix e -> IO () Source #
raggedFormat :: (e -> String) -> String -> Array r ix e -> String Source #
class Nested r ix e where Source #
Minimal complete definition
Methods
fromNested :: NestedStruct r ix e -> Array r ix e Source #
toNested :: Array r ix e -> NestedStruct r ix e Source #
type family NestedStruct r ix e :: * Source #
Instances
type NestedStruct L ix e Source # | |
type NestedStruct LN ix e Source # | |
Constructors
L |
Instances
(Index ix, Index (Lower ix), Ragged L (Lower ix) e, (~) * (Elt L ix e) (Array L (Lower ix) e), (~) * (Elt LN ix e) (Array LN (Lower ix) e), Coercible * (Elt LN ix e) [Elt LN (Lower ix) e]) => Ragged L ix e Source # | |
Ragged L Ix1 e Source # | |
Nested L ix e Source # | |
Ragged L ix e => OuterSlice L ix e Source # | |
OuterSlice L Ix1 e Source # | |
(Index ix, Ragged L ix e, Ragged L (Lower ix) e, (~) * (Elt L ix e) (Array L (Lower ix) e)) => Construct L ix e Source # | |
Construct L Ix1 e Source # | |
Nested LN ix e => IsList (Array L ix e) Source # | |
(Ragged L ix e, Show e) => Show (Array L ix e) Source # | |
data Array L Source # | |
type EltRepr L ix Source # | |
type NestedStruct L ix e Source # | |
type Item (Array L ix e) Source # | |
Instances
((~) * (Elt LN ix e) (Array LN (Lower ix) e), (~) * (ListItem ix e) [ListItem (Lower ix) e], Coercible * (Elt LN ix e) (ListItem ix e)) => Nested LN ix e Source # | |
Nested LN Ix1 e Source # | |
Nested LN ix e => IsList (Array LN ix e) Source # | |
(Ragged L ix e, Nested LN ix e, Show e) => Show (Array LN ix e) Source # | |
data Array LN Source # | |
type EltRepr LN ix Source # | |
type NestedStruct LN ix e Source # | |
type Item (Array LN ix e) Source # | |
Computation type to use.
Constructors
Seq | Sequential computation |
ParOn [Int] | Use Parallel computation with a list of capabilities to run computation
on. Specifying an empty list ( |
module Data.Massiv.Core.Index