repa-array-4.2.3.1: Bulk array representations and operators.

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Meta.Dense

Contents

Synopsis

Documentation

data E r l Source #

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 # 

Methods

(==) :: Name (E r l) -> Name (E r l) -> Bool #

(/=) :: Name (E r l) -> Name (E r l) -> Bool #

(Show (Name r), Show (Name l)) => Show (Name (E r l)) Source # 

Methods

showsPrec :: Int -> Name (E r l) -> ShowS #

show :: Name (E r l) -> String #

showList :: [Name (E r l)] -> ShowS #

(Eq r, Eq l) => Eq (E r l) Source # 

Methods

(==) :: E r l -> E r l -> Bool #

(/=) :: E r l -> E r l -> Bool #

(Show r, Show l) => Show (E r l) Source # 

Methods

showsPrec :: Int -> E r l -> ShowS #

show :: E r l -> String #

showList :: [E r l] -> ShowS #

((~) * (Index r) Int, Layout r, Layout l) => Layout (E r l) Source #

Dense arrays.

Associated Types

data Name (E r l) :: * Source #

type Index (E r l) :: * Source #

Methods

name :: Name (E r l) Source #

create :: Name (E r l) -> Index (E r l) -> E r l Source #

extent :: E r l -> Index (E r l) Source #

toIndex :: E r l -> Index (E r l) -> Int Source #

fromIndex :: E r l -> Int -> Index (E r l) Source #

((~) * (Index r) Int, Layout l, Bulk r a) => Bulk (E r l) a Source #

Dense arrays.

Associated Types

data Array (E r l) a :: * Source #

Methods

layout :: Array (E r l) a -> E r l Source #

index :: Array (E r l) a -> Index (E r l) -> a Source #

(Layout l, (~) * (Index r) Int, Target r a) => Target (E r l) a Source #

Dense buffers.

Associated Types

data Buffer (E r l) a :: * Source #

Methods

unsafeNewBuffer :: E r l -> IO (Buffer (E r l) a) Source #

unsafeReadBuffer :: Buffer (E r l) a -> Int -> IO a Source #

unsafeWriteBuffer :: Buffer (E r l) a -> Int -> a -> IO () Source #

unsafeGrowBuffer :: Buffer (E r l) a -> Int -> IO (Buffer (E r l) a) Source #

unsafeSliceBuffer :: Int -> Int -> Buffer (E r l) a -> IO (Buffer (E r l) a) Source #

unsafeFreezeBuffer :: Buffer (E r l) a -> IO (Array (E r l) a) Source #

unsafeThawBuffer :: Array (E r l) a -> IO (Buffer (E r l) a) Source #

touchBuffer :: Buffer (E r l) a -> IO () Source #

bufferLayout :: Buffer (E r l) a -> E r l Source #

data Name (E r l) Source # 
data Name (E r l) = E (Name r) (Name l)
type Index (E r l) Source # 
type Index (E r l) = Index l
data Array (E r l) Source # 
data Array (E r l) = Array l (Array r a)
data Buffer (E r l) Source # 
data Buffer (E r l) = EBuffer !l !(Buffer r a)

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.

matrix :: LayoutI l => Name l -> Int -> Int -> E l DIM2 Source #

Yield a layout for a matrix with the given number of rows and columns.

cube :: LayoutI l => Name l -> Int -> Int -> Int -> E l DIM3 Source #

Yield a layout for a cube with the given number of planes, rows, and columns.