repa-3.4.1.3: High performance, regular, shape polymorphic parallel arrays.

Safe HaskellNone
LanguageHaskell98

Data.Array.Repa.Operators.Mapping

Contents

Synopsis

Generic maps

map :: (Shape sh, Source r a) => (a -> b) -> Array r sh a -> Array D sh b Source #

Apply a worker function to each element of an array, yielding a new array with the same extent.

zipWith :: (Shape sh, Source r1 a, Source r2 b) => (a -> b -> c) -> Array r1 sh a -> Array r2 sh b -> Array D sh c Source #

Combine two arrays, element-wise, with a binary operator. If the extent of the two array arguments differ, then the resulting array's extent is their intersection.

(+^) :: (Num c, Source r2 c, Source r1 c, Shape sh) => Array r1 sh c -> Array r2 sh c -> Array D sh c infixl 6 Source #

(-^) :: (Num c, Source r2 c, Source r1 c, Shape sh) => Array r1 sh c -> Array r2 sh c -> Array D sh c infixl 6 Source #

(*^) :: (Num c, Source r2 c, Source r1 c, Shape sh) => Array r1 sh c -> Array r2 sh c -> Array D sh c infixl 7 Source #

(/^) :: (Fractional c, Source r2 c, Source r1 c, Shape sh) => Array r1 sh c -> Array r2 sh c -> Array D sh c infixl 7 Source #

Structured maps

class Structured r1 a b where Source #

Structured versions of map and zipWith that preserve the representation of cursored and partitioned arrays.

For cursored (C) arrays, the cursoring of the source array is preserved.

For partitioned (P) arrays, the worker function is fused with each array partition separately, instead of treating the whole array as a single bulk object.

Preserving the cursored and/or paritioned representation of an array is will make follow-on computation more efficient than if the array was converted to a vanilla Delayed (D) array as with plain map and zipWith.

If the source array is not cursored or partitioned then smap and szipWith are identical to the plain functions.

Minimal complete definition

smap, szipWith

Associated Types

type TR r1 Source #

The target result representation.

Methods

smap :: Shape sh => (a -> b) -> Array r1 sh a -> Array (TR r1) sh b Source #

Structured map.

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array r1 sh a -> Array (TR r1) sh b Source #

Structured zipWith. If you have a cursored or partitioned source array then use that as the third argument (corresponding to r1 here)

Instances

Structured D a b Source # 

Associated Types

type TR D :: * Source #

Methods

smap :: Shape sh => (a -> b) -> Array D sh a -> Array (TR D) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array D sh a -> Array (TR D) sh b Source #

Structured B Word8 b Source # 

Associated Types

type TR B :: * Source #

Methods

smap :: Shape sh => (Word8 -> b) -> Array B sh Word8 -> Array (TR B) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> Word8 -> b) -> Array r sh c -> Array B sh Word8 -> Array (TR B) sh b Source #

Storable a => Structured F a b Source # 

Associated Types

type TR F :: * Source #

Methods

smap :: Shape sh => (a -> b) -> Array F sh a -> Array (TR F) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array F sh a -> Array (TR F) sh b Source #

Unbox a => Structured U a b Source # 

Associated Types

type TR U :: * Source #

Methods

smap :: Shape sh => (a -> b) -> Array U sh a -> Array (TR U) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array U sh a -> Array (TR U) sh b Source #

Structured X a b Source # 

Associated Types

type TR X :: * Source #

Methods

smap :: Shape sh => (a -> b) -> Array X sh a -> Array (TR X) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array X sh a -> Array (TR X) sh b Source #

Structured C a b Source # 

Associated Types

type TR C :: * Source #

Methods

smap :: Shape sh => (a -> b) -> Array C sh a -> Array (TR C) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array C sh a -> Array (TR C) sh b Source #

Structured r1 a b => Structured (I r1) a b Source # 

Associated Types

type TR (I r1) :: * Source #

Methods

smap :: Shape sh => (a -> b) -> Array (I r1) sh a -> Array (TR (I r1)) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array (I r1) sh a -> Array (TR (I r1)) sh b Source #

Structured r1 a b => Structured (S r1) a b Source # 

Associated Types

type TR (S r1) :: * Source #

Methods

smap :: Shape sh => (a -> b) -> Array (S r1) sh a -> Array (TR (S r1)) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array (S r1) sh a -> Array (TR (S r1)) sh b Source #

(Structured r1 a b, Structured r2 a b) => Structured (P r1 r2) a b Source # 

Associated Types

type TR (P r1 r2) :: * Source #

Methods

smap :: Shape sh => (a -> b) -> Array (P r1 r2) sh a -> Array (TR (P r1 r2)) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array (P r1 r2) sh a -> Array (TR (P r1 r2)) sh b Source #