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

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Meta.Tuple

Synopsis

Documentation

data T2 l1 l2 Source #

Tupled arrays where the components are unpacked and can have separate representations.

Constructors

Tup2 !l1 !l2 

Instances

(Eq (Name l1), Eq (Name l2)) => Eq (Name (T2 l1 l2)) Source # 

Methods

(==) :: Name (T2 l1 l2) -> Name (T2 l1 l2) -> Bool #

(/=) :: Name (T2 l1 l2) -> Name (T2 l1 l2) -> Bool #

(Show (Name l1), Show (Name l2)) => Show (Name (T2 l1 l2)) Source # 

Methods

showsPrec :: Int -> Name (T2 l1 l2) -> ShowS #

show :: Name (T2 l1 l2) -> String #

showList :: [Name (T2 l1 l2)] -> ShowS #

(Eq l1, Eq l2) => Eq (T2 l1 l2) Source # 

Methods

(==) :: T2 l1 l2 -> T2 l1 l2 -> Bool #

(/=) :: T2 l1 l2 -> T2 l1 l2 -> Bool #

(Show (Array l1 a), Show (Array l2 b)) => Show (Array (T2 l1 l2) (a, b)) Source # 

Methods

showsPrec :: Int -> Array (T2 l1 l2) (a, b) -> ShowS #

show :: Array (T2 l1 l2) (a, b) -> String #

showList :: [Array (T2 l1 l2) (a, b)] -> ShowS #

(Show l1, Show l2) => Show (T2 l1 l2) Source # 

Methods

showsPrec :: Int -> T2 l1 l2 -> ShowS #

show :: T2 l1 l2 -> String #

showList :: [T2 l1 l2] -> ShowS #

((~) * (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 #

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

Tupled arrays.

Associated Types

data Array (T2 l1 l2) (a, b) :: * Source #

Methods

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

index :: Array (T2 l1 l2) (a, b) -> Index (T2 l1 l2) -> (a, b) 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 #

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

Tupled buffers.

Associated Types

data Buffer (T2 l1 l2) (a, b) :: * Source #

Methods

unsafeNewBuffer :: T2 l1 l2 -> IO (Buffer (T2 l1 l2) (a, b)) Source #

unsafeReadBuffer :: Buffer (T2 l1 l2) (a, b) -> Int -> IO (a, b) Source #

unsafeWriteBuffer :: Buffer (T2 l1 l2) (a, b) -> Int -> (a, b) -> IO () Source #

unsafeGrowBuffer :: Buffer (T2 l1 l2) (a, b) -> Int -> IO (Buffer (T2 l1 l2) (a, b)) Source #

unsafeSliceBuffer :: Int -> Int -> Buffer (T2 l1 l2) (a, b) -> IO (Buffer (T2 l1 l2) (a, b)) Source #

unsafeFreezeBuffer :: Buffer (T2 l1 l2) (a, b) -> IO (Array (T2 l1 l2) (a, b)) Source #

unsafeThawBuffer :: Array (T2 l1 l2) (a, b) -> IO (Buffer (T2 l1 l2) (a, b)) Source #

touchBuffer :: Buffer (T2 l1 l2) (a, b) -> IO () Source #

bufferLayout :: Buffer (T2 l1 l2) (a, b) -> T2 l1 l2 Source #

data Name (T2 l1 l2) Source # 
data Name (T2 l1 l2) = T2 !(Name l1) !(Name l2)
type Index (T2 l1 l2) Source # 
type Index (T2 l1 l2) = Index l1
data Array (T2 l1 l2) (a, b) Source # 
data Array (T2 l1 l2) (a, b) = T2Array !(Array l1 a) !(Array l2 b)
data Buffer (T2 l1 l2) (a, b) Source # 
data Buffer (T2 l1 l2) (a, b) = T2Buffer !(Buffer l1 a) !(Buffer l2 b)

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

Tuple two arrays into an array of pairs.

The two argument arrays must have the same index type, but can have different extents. The extent of the result is the intersection of the extents of the two argument arrays.

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

Untuple an array of tuples in to a tuple of arrays.

  • The two returned components may have different extents, though they are guaranteed to be at least as big as the argument array. This is the key property that makes untup2 different from unzip.