| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Data.Repa.Array.Meta.Dense
Contents
Documentation
The Dense layout maps a higher-ranked index space to some underlying linear index space.
For example, we can create a dense 2D row-wise array where the elements are stored in a flat unboxed vector:
> import Data.Repa.Array.Material > let Just arr = fromListInto (matrix U 10 10) [1000..1099 :: Float] > :type arr arr :: Array (E U (RW DIM2) Float > arr ! (Z :. 5 :. 4) > 1054.0
Constructors
| Dense r l |
Instances
| (Eq (Name r), Eq (Name l)) => Eq (Name (E r l)) Source # | |
| (Show (Name r), Show (Name l)) => Show (Name (E r l)) Source # | |
| (Eq r, Eq l) => Eq (E r l) Source # | |
| (Show r, Show l) => Show (E r l) Source # | |
| ((~) * (Index r) Int, Layout r, Layout l) => Layout (E r l) Source # | Dense arrays. |
| ((~) * (Index r) Int, Layout l, Bulk r a) => Bulk (E r l) a Source # | Dense arrays. |
| (Layout l, (~) * (Index r) Int, Target r a) => Target (E r l) a Source # | Dense buffers. |
| data Name (E r l) Source # | |
| type Index (E r l) Source # | |
| data Array (E r l) Source # | |
| data Buffer (E r l) Source # | |
Common layouts
vector :: LayoutI l => Name l -> Int -> E l DIM1 Source #
Yield a layout for a dense vector of the given length.
The first argument is the name of the underlying linear layout which stores the elements.