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

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Meta.RowWise

Synopsis

Documentation

data RW sh Source #

A row-wise layout that maps higher rank indices to linear ones in a row-major order.

Indices are ordered so the inner-most coordinate varies most frequently:

> Prelude.map (fromIndex (RowWise (ish2 2 3))) [0..5]
   [(Z :. 0) :. 0, (Z :. 0) :. 1, (Z :. 0) :. 2, 
    (Z :. 1) :. 0, (Z :. 1) :. 1, (Z :. 1) :. 2]
  • Indexing is not bounds checked. Indexing outside the extent yields the corresponding index.

Constructors

RowWise 

Fields

Instances

Eq (Name (RW sh)) => Eq (Name (RW ((:.) sh Int))) Source # 

Methods

(==) :: Name (RW (sh :. Int)) -> Name (RW (sh :. Int)) -> Bool #

(/=) :: Name (RW (sh :. Int)) -> Name (RW (sh :. Int)) -> Bool #

Eq (Name (RW Z)) Source # 

Methods

(==) :: Name (RW Z) -> Name (RW Z) -> Bool #

(/=) :: Name (RW Z) -> Name (RW Z) -> Bool #

Eq sh => Eq (RW sh) Source # 

Methods

(==) :: RW sh -> RW sh -> Bool #

(/=) :: RW sh -> RW sh -> Bool #

Show (Name (RW sh)) => Show (Name (RW ((:.) sh Int))) Source # 

Methods

showsPrec :: Int -> Name (RW (sh :. Int)) -> ShowS #

show :: Name (RW (sh :. Int)) -> String #

showList :: [Name (RW (sh :. Int))] -> ShowS #

Show (Name (RW Z)) Source # 

Methods

showsPrec :: Int -> Name (RW Z) -> ShowS #

show :: Name (RW Z) -> String #

showList :: [Name (RW Z)] -> ShowS #

Show sh => Show (RW sh) Source # 

Methods

showsPrec :: Int -> RW sh -> ShowS #

show :: RW sh -> String #

showList :: [RW sh] -> ShowS #

Shape sh => Shape (RW sh) Source # 

Methods

rank :: RW sh -> Int Source #

zeroDim :: RW sh Source #

unitDim :: RW sh Source #

intersectDim :: RW sh -> RW sh -> RW sh Source #

addDim :: RW sh -> RW sh -> RW sh Source #

size :: RW sh -> Int Source #

inShapeRange :: RW sh -> RW sh -> RW sh -> Bool Source #

listOfShape :: RW sh -> [Int] Source #

shapeOfList :: [Int] -> Maybe (RW sh) Source #

(Layout (RW sh), (~) * (Index (RW sh)) sh) => Layout (RW ((:.) sh Int)) Source # 

Associated Types

data Name (RW ((:.) sh Int)) :: * Source #

type Index (RW ((:.) sh Int)) :: * Source #

Methods

name :: Name (RW (sh :. Int)) Source #

create :: Name (RW (sh :. Int)) -> Index (RW (sh :. Int)) -> RW (sh :. Int) Source #

extent :: RW (sh :. Int) -> Index (RW (sh :. Int)) Source #

toIndex :: RW (sh :. Int) -> Index (RW (sh :. Int)) -> Int Source #

fromIndex :: RW (sh :. Int) -> Int -> Index (RW (sh :. Int)) Source #

Layout (RW Z) Source # 

Associated Types

data Name (RW Z) :: * Source #

type Index (RW Z) :: * Source #

Methods

name :: Name (RW Z) Source #

create :: Name (RW Z) -> Index (RW Z) -> RW Z Source #

extent :: RW Z -> Index (RW Z) Source #

toIndex :: RW Z -> Index (RW Z) -> Int Source #

fromIndex :: RW Z -> Int -> Index (RW Z) Source #

(Layout (RW sh), (~) * (Index (RW sh)) sh) => Bulk (RW sh) sh Source #

Row-wise arrays.

Associated Types

data Array (RW sh) sh :: * Source #

Methods

layout :: Array (RW sh) sh -> RW sh Source #

index :: Array (RW sh) sh -> Index (RW sh) -> sh Source #

data Name (RW ((:.) sh Int)) Source # 
data Name (RW ((:.) sh Int)) = RC (Name (RW sh))
data Name (RW Z) Source # 
data Name (RW Z) = RZ
type Index (RW ((:.) sh Int)) Source # 
type Index (RW ((:.) sh Int)) = (:.) sh Int
type Index (RW Z) Source # 
type Index (RW Z) = Z
data Array (RW sh) sh Source # 
data Array (RW sh) sh = RArray sh

rowWise :: sh -> Array (RW sh) sh Source #

Construct a rowWise array that produces the corresponding index for every element.

> toList $ rowWise (ish2 3 2) 
   [(Z :. 0) :. 0, (Z :. 0) :. 1,
    (Z :. 1) :. 0, (Z :. 1) :. 1,
    (Z :. 2) :. 0, (Z :. 2) :. 1]

Synonyms for common layouts.

type DIM1 = RW SH1 Source #

type DIM2 = RW SH2 Source #

type DIM3 = RW SH3 Source #

type DIM4 = RW SH4 Source #

type DIM5 = RW SH5 Source #

Helpers that contrain the coordinates to be Ints.

ix2 :: Int -> Int -> DIM2 Source #

ix3 :: Int -> Int -> Int -> DIM3 Source #

ix4 :: Int -> Int -> Int -> Int -> DIM4 Source #

ix5 :: Int -> Int -> Int -> Int -> Int -> DIM5 Source #