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

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Meta.Delayed2

Synopsis

Documentation

data D2 l1 l2 Source #

A delayed array formed from two source arrays. The source arrays can have different layouts but must have the same extent.

Constructors

Delayed2 

Fields

Instances

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

Methods

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

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

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

Methods

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

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

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

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

Methods

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

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

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

Methods

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

show :: D2 l1 l2 -> String #

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

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

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

Delayed arrays.

Associated Types

data Array (D2 l1 l2) a :: * Source #

Methods

layout :: Array (D2 l1 l2) a -> D2 l1 l2 Source #

index :: Array (D2 l1 l2) a -> Index (D2 l1 l2) -> a Source #

(Layout lSrc1, Layout lSrc2, Target lDst a, (~) * (Index lSrc1) (Index lSrc2)) => Load (D2 lSrc1 lSrc2) lDst a Source # 

Methods

loadS :: Array (D2 lSrc1 lSrc2) a -> Buffer lDst a -> IO () Source #

loadP :: Gang -> Array (D2 lSrc1 lSrc2) a -> Buffer lDst a -> IO () Source #

data Name (D2 l1 l2) Source # 
data Name (D2 l1 l2) = D2 (Name l1) (Name l2)
type Index (D2 l1 l2) Source # 
type Index (D2 l1 l2) = Index l1
data Array (D2 l1 l2) Source # 
data Array (D2 l1 l2) = ADelayed2 !l1 !l2 (Index l1 -> a)

delay2 :: (Bulk l1 a, Bulk l2 b, Index l1 ~ Index l2) => Array l1 a -> Array l2 b -> Maybe (Array (D2 l1 l2) (a, b)) Source #

Wrap two existing arrays in a delayed array.

map2 :: (Bulk l1 a, Bulk l2 b, Index l1 ~ Index l2) => (a -> b -> c) -> Array l1 a -> Array l2 b -> Maybe (Array (D2 l1 l2) c) Source #

Combine two arrays element-wise using the given worker function.

The two source arrays must have the same extent, else Nothing.