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

Safe HaskellSafe
LanguageHaskell98

Data.Repa.Array.Generic.Index

Contents

Description

Shapes and Indices

Synopsis

Shapes

class Eq sh => Shape sh where Source #

Class of types that can be used as array shapes and indices.

Methods

rank :: sh -> Int Source #

Get the number of dimensions in a shape.

zeroDim :: sh Source #

The shape of an array of size zero, with a particular dimensionality.

unitDim :: sh Source #

The shape of an array with size one, with a particular dimensionality.

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

Compute the intersection of two shapes.

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

Add the coordinates of two shapes componentwise

size :: sh -> Int Source #

Get the total number of elements in an array with this shape.

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

Given a starting and ending index, check if some index is with that range.

listOfShape :: sh -> [Int] Source #

Convert a shape into its list of dimensions.

shapeOfList :: [Int] -> Maybe sh Source #

Convert a list of dimensions to a shape

Instances

Shape Int Source # 
Shape Z Source # 
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 #

Shape sh => Shape ((:.) sh Int) Source # 

Methods

rank :: (sh :. Int) -> Int Source #

zeroDim :: sh :. Int Source #

unitDim :: sh :. Int Source #

intersectDim :: (sh :. Int) -> (sh :. Int) -> sh :. Int Source #

addDim :: (sh :. Int) -> (sh :. Int) -> sh :. Int Source #

size :: (sh :. Int) -> Int Source #

inShapeRange :: (sh :. Int) -> (sh :. Int) -> (sh :. Int) -> Bool Source #

listOfShape :: (sh :. Int) -> [Int] Source #

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

inShape :: Shape sh => sh -> sh -> Bool Source #

Given an array shape and index, check whether the index is in the shape.

showShape :: Shape sh => sh -> String Source #

Nicely format a shape as a string

Polymorphic Shapes

data Z Source #

An index of dimension zero

Constructors

Z 

Instances

Eq Z Source # 

Methods

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

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

Ord Z Source # 

Methods

compare :: Z -> Z -> Ordering #

(<) :: Z -> Z -> Bool #

(<=) :: Z -> Z -> Bool #

(>) :: Z -> Z -> Bool #

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

max :: Z -> Z -> Z #

min :: Z -> Z -> Z #

Read Z Source # 
Show Z Source # 

Methods

showsPrec :: Int -> Z -> ShowS #

show :: Z -> String #

showList :: [Z] -> ShowS #

Shape Z Source # 
Slice Z Source # 
Eq (Name (RW Z)) # 

Methods

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

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

Show (Name (RW Z)) # 

Methods

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

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

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

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 #

type SliceShape Z Source # 
type SliceShape Z = Z
type FullShape Z Source # 
type FullShape Z = Z
data Name (RW Z) Source # 
data Name (RW Z) = RZ
type Index (RW Z) Source # 
type Index (RW Z) = Z

data tail :. head infixl 3 Source #

Our index type, used for both shapes and indices.

Constructors

!tail :. !head infixl 3 

Instances

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

Methods

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

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

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

Methods

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

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

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

(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 #

(Eq tail, Eq head) => Eq ((:.) tail head) Source # 

Methods

(==) :: (tail :. head) -> (tail :. head) -> Bool #

(/=) :: (tail :. head) -> (tail :. head) -> Bool #

(Ord tail, Ord head) => Ord ((:.) tail head) Source # 

Methods

compare :: (tail :. head) -> (tail :. head) -> Ordering #

(<) :: (tail :. head) -> (tail :. head) -> Bool #

(<=) :: (tail :. head) -> (tail :. head) -> Bool #

(>) :: (tail :. head) -> (tail :. head) -> Bool #

(>=) :: (tail :. head) -> (tail :. head) -> Bool #

max :: (tail :. head) -> (tail :. head) -> tail :. head #

min :: (tail :. head) -> (tail :. head) -> tail :. head #

(Read tail, Read head) => Read ((:.) tail head) Source # 

Methods

readsPrec :: Int -> ReadS (tail :. head) #

readList :: ReadS [tail :. head] #

readPrec :: ReadPrec (tail :. head) #

readListPrec :: ReadPrec [tail :. head] #

(Show tail, Show head) => Show ((:.) tail head) Source # 

Methods

showsPrec :: Int -> (tail :. head) -> ShowS #

show :: (tail :. head) -> String #

showList :: [tail :. head] -> ShowS #

Shape sh => Shape ((:.) sh Int) Source # 

Methods

rank :: (sh :. Int) -> Int Source #

zeroDim :: sh :. Int Source #

unitDim :: sh :. Int Source #

intersectDim :: (sh :. Int) -> (sh :. Int) -> sh :. Int Source #

addDim :: (sh :. Int) -> (sh :. Int) -> sh :. Int Source #

size :: (sh :. Int) -> Int Source #

inShapeRange :: (sh :. Int) -> (sh :. Int) -> (sh :. Int) -> Bool Source #

listOfShape :: (sh :. Int) -> [Int] Source #

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

Slice sl => Slice ((:.) sl All) Source # 

Methods

sliceOfFull :: (sl :. All) -> FullShape (sl :. All) -> SliceShape (sl :. All) Source #

fullOfSlice :: (sl :. All) -> SliceShape (sl :. All) -> FullShape (sl :. All) Source #

Slice sl => Slice ((:.) sl Int) Source # 

Methods

sliceOfFull :: (sl :. Int) -> FullShape (sl :. Int) -> SliceShape (sl :. Int) Source #

fullOfSlice :: (sl :. Int) -> SliceShape (sl :. Int) -> FullShape (sl :. Int) Source #

data Name (RW ((:.) sh Int)) Source # 
data Name (RW ((:.) sh Int)) = RC (Name (RW sh))
type Index (RW ((:.) sh Int)) Source # 
type Index (RW ((:.) sh Int)) = (:.) sh Int
type SliceShape ((:.) sl All) Source # 
type SliceShape ((:.) sl Int) Source # 
type SliceShape ((:.) sl Int) = SliceShape sl
type FullShape ((:.) sl All) Source # 
type FullShape ((:.) sl All) = (:.) (FullShape sl) Int
type FullShape ((:.) sl Int) Source # 
type FullShape ((:.) sl Int) = (:.) (FullShape sl) Int

Synonyms for common layouts.

type SH0 = Z Source #

type SH1 = SH0 :. Int Source #

type SH2 = SH1 :. Int Source #

type SH3 = SH2 :. Int Source #

type SH4 = SH3 :. Int Source #

type SH5 = SH4 :. Int Source #

Helpers that constrain the coordinates to be Ints.

ish2 :: Int -> Int -> SH2 Source #

ish3 :: Int -> Int -> Int -> SH3 Source #

ish4 :: Int -> Int -> Int -> Int -> SH4 Source #

ish5 :: Int -> Int -> Int -> Int -> Int -> SH5 Source #

Layouts

class Shape (Index l) => Layout l where Source #

A layout provides a total order on the elements of an index space.

We can talk about the n-th element of an array, independent of its shape and dimensionality.

Minimal complete definition

name, create, extent, toIndex, fromIndex

Associated Types

data Name l Source #

Short name for a layout which does not include details of the exact extent.

type Index l Source #

Type used to index into this array layout.

Methods

name :: Name l Source #

O(1). Proxy for the layout name.

create :: Name l -> Index l -> l Source #

O(1). Create a default layout of the given extent.

extent :: l -> Index l Source #

O(1). Yield the extent of the layout.

toIndex :: l -> Index l -> Int Source #

O(1). Convert a polymorphic index to a linear one.

fromIndex :: l -> Int -> Index l Source #

O(1). Convert a linear index to a polymorphic one.

Instances

Layout L Source #

Linear layout.

Associated Types

data Name L :: * Source #

type Index L :: * Source #

Layout B Source #

Boxed arrays.

Associated Types

data Name B :: * Source #

type Index B :: * Source #

Layout F Source #

Foreign arrays.

Associated Types

data Name F :: * Source #

type Index F :: * Source #

Layout U Source #

Unboxed arrays.

Associated Types

data Name U :: * Source #

type Index U :: * Source #

Layout N Source #

Nested arrays.

Associated Types

data Name N :: * Source #

type Index N :: * Source #

Layout A Source # 

Associated Types

data Name A :: * Source #

type Index A :: * Source #

Layout l => Layout (W l) Source #

Windowed arrays.

Associated Types

data Name (W l) :: * Source #

type Index (W l) :: * Source #

Methods

name :: Name (W l) Source #

create :: Name (W l) -> Index (W l) -> W l Source #

extent :: W l -> Index (W l) Source #

toIndex :: W l -> Index (W l) -> Int Source #

fromIndex :: W l -> Int -> Index (W l) 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 l => Layout (D l) Source #

Delayed arrays.

Associated Types

data Name (D l) :: * Source #

type Index (D l) :: * Source #

Methods

name :: Name (D l) Source #

create :: Name (D l) -> Index (D l) -> D l Source #

extent :: D l -> Index (D l) Source #

toIndex :: D l -> Index (D l) -> Int Source #

fromIndex :: D l -> Int -> Index (D l) Source #

(Layout l1, Layout l2, (~) * (Index l1) (Index l2)) => Layout (D2 l1 l2) Source #

Delayed arrays.

Associated Types

data Name (D2 l1 l2) :: * Source #

type Index (D2 l1 l2) :: * Source #

Methods

name :: Name (D2 l1 l2) Source #

create :: Name (D2 l1 l2) -> Index (D2 l1 l2) -> D2 l1 l2 Source #

extent :: D2 l1 l2 -> Index (D2 l1 l2) Source #

toIndex :: D2 l1 l2 -> Index (D2 l1 l2) -> Int Source #

fromIndex :: D2 l1 l2 -> Int -> Index (D2 l1 l2) Source #

((~) * (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 l1) (Index l2), Layout l1, Layout l2) => Layout (T2 l1 l2) Source # 

Associated Types

data Name (T2 l1 l2) :: * Source #

type Index (T2 l1 l2) :: * Source #

Methods

name :: Name (T2 l1 l2) Source #

create :: Name (T2 l1 l2) -> Index (T2 l1 l2) -> T2 l1 l2 Source #

extent :: T2 l1 l2 -> Index (T2 l1 l2) Source #

toIndex :: T2 l1 l2 -> Index (T2 l1 l2) -> Int Source #

fromIndex :: T2 l1 l2 -> Int -> Index (T2 l1 l2) Source #

type LayoutI l = (Layout l, Index l ~ Int) Source #