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

Safe HaskellSafe
LanguageHaskell98

Data.Repa.Array.Meta.Window

Synopsis

Documentation

data W l Source #

Constructors

Window 

Fields

Instances

Eq (Name l) => Eq (Name (W l)) Source # 

Methods

(==) :: Name (W l) -> Name (W l) -> Bool #

(/=) :: Name (W l) -> Name (W l) -> Bool #

(Eq l, Eq (Index l)) => Eq (W l) Source # 

Methods

(==) :: W l -> W l -> Bool #

(/=) :: W l -> W l -> Bool #

Show (Name l) => Show (Name (W l)) Source # 

Methods

showsPrec :: Int -> Name (W l) -> ShowS #

show :: Name (W l) -> String #

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

(Show l, Show (Index l)) => Show (W l) Source # 

Methods

showsPrec :: Int -> W l -> ShowS #

show :: W l -> String #

showList :: [W l] -> ShowS #

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 #

Bulk l a => Bulk (W l) a Source #

Windowed arrays.

Associated Types

data Array (W l) a :: * Source #

Methods

layout :: Array (W l) a -> W l Source #

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

Bulk l a => Windowable (W l) a Source #

Windows are windowable.

Methods

window :: Index (W l) -> Index (W l) -> Array (W l) a -> Array (W l) a Source #

data Name (W l) Source # 
data Name (W l) = W (Name l)
type Index (W l) Source # 
type Index (W l) = Index l
data Array (W l) Source # 
data Array (W l) = WArray !(Index l) !(Index l) !(Array l a)

class Bulk l a => Windowable l a where Source #

Class of array representations that can be windowed directly.

The underlying representation can encode the window, without needing to add a wrapper to the existing layout.

Minimal complete definition

window

Methods

window :: Index l -> Index l -> Array l a -> Array l a Source #

Instances

Windowable B a Source #

Boxed windows.

Methods

window :: Index B -> Index B -> Array B a -> Array B a Source #

Storable a => Windowable F a Source #

Windowing Foreign arrays.

Methods

window :: Index F -> Index F -> Array F a -> Array F a Source #

Unbox a => Windowable U a Source #

Windowing Unboxed arrays.

Methods

window :: Index U -> Index U -> Array U a -> Array U a Source #

(BulkI l a, Windowable l a) => Windowable N (Array l a) Source #

Windowing Nested arrays.

Methods

window :: Index N -> Index N -> Array N (Array l a) -> Array N (Array l a) Source #

Bulk l a => Windowable (W l) a Source #

Windows are windowable.

Methods

window :: Index (W l) -> Index (W l) -> Array (W l) a -> Array (W l) a Source #

(Windowable l1 a, Windowable l2 b, (~) * (Index l1) (Index l2)) => Windowable (T2 l1 l2) (a, b) Source #

Tupled windows.

Methods

window :: Index (T2 l1 l2) -> Index (T2 l1 l2) -> Array (T2 l1 l2) (a, b) -> Array (T2 l1 l2) (a, b) Source #

windowed :: Index l -> Index l -> Array l a -> Array (W l) a Source #

Wrap a window around an exiting array.

entire :: Bulk l a => Array l a -> Array (W l) a Source #

Wrap a window around an existing array that encompases the entire array.

tail :: (Windowable l a, Index l ~ Int) => Array l a -> Maybe (Array l a) Source #

O(1). Take the tail of an array, or Nothing if it's empty.

init :: (Windowable l a, Index l ~ Int) => Array l a -> Maybe (Array l a) Source #

O(1). Take the initial elements of an array, or Nothing if it's empty.