accelerate-utility-1.0.0.1: Utility functions for the Accelerate framework

Safe HaskellNone
LanguageHaskell98

Data.Array.Accelerate.Utility.Lift.Acc

Synopsis

Documentation

class Arrays (Tuple pattern) => Unlift pattern where Source #

This class is like Unlift but for the Acc environment. It allows you to unlift an Acc of nested tuples into tuples of Exp and Acc values. It can be quite handy when working with acond and awhile. It can also be useful in connection with running an accelerate algorithm at a certain backend, like run1. But in this case you might prefer Data.Array.Accelerate.Utility.Lift.Run.

Minimal complete definition

unlift

Associated Types

type Unlifted pattern Source #

type Tuple pattern Source #

Methods

unlift :: pattern -> Acc (Tuple pattern) -> Unlifted pattern Source #

Instances

Elt a => Unlift (Exp a) Source # 

Associated Types

type Unlifted (Exp a) :: * Source #

type Tuple (Exp a) :: * Source #

Methods

unlift :: Exp a -> Acc (Tuple (Exp a)) -> Unlifted (Exp a) Source #

Arrays a => Unlift (Acc a) Source # 

Associated Types

type Unlifted (Acc a) :: * Source #

type Tuple (Acc a) :: * Source #

Methods

unlift :: Acc a -> Acc (Tuple (Acc a)) -> Unlifted (Acc a) Source #

(Unlift pa, Unlift pb) => Unlift (pa, pb) Source # 

Associated Types

type Unlifted (pa, pb) :: * Source #

type Tuple (pa, pb) :: * Source #

Methods

unlift :: (pa, pb) -> Acc (Tuple (pa, pb)) -> Unlifted (pa, pb) Source #

(Unlift pa, Unlift pb, Unlift pc) => Unlift (pa, pb, pc) Source # 

Associated Types

type Unlifted (pa, pb, pc) :: * Source #

type Tuple (pa, pb, pc) :: * Source #

Methods

unlift :: (pa, pb, pc) -> Acc (Tuple (pa, pb, pc)) -> Unlifted (pa, pb, pc) Source #

unlift :: Unlift pattern => pattern -> Acc (Tuple pattern) -> Unlifted pattern Source #

modify :: (Lift Acc a, Unlift pattern) => pattern -> (Unlifted pattern -> a) -> Acc (Tuple pattern) -> Acc (Plain a) Source #

modify2 :: (Lift Acc a, Unlift patternA, Unlift patternB) => patternA -> patternB -> (Unlifted patternA -> Unlifted patternB -> a) -> Acc (Tuple patternA) -> Acc (Tuple patternB) -> Acc (Plain a) Source #

modify3 :: (Lift Acc a, Unlift patternA, Unlift patternB, Unlift patternC) => patternA -> patternB -> patternC -> (Unlifted patternA -> Unlifted patternB -> Unlifted patternC -> a) -> Acc (Tuple patternA) -> Acc (Tuple patternB) -> Acc (Tuple patternC) -> Acc (Plain a) Source #

modify4 :: (Lift Acc a, Unlift patternA, Unlift patternB, Unlift patternC, Unlift patternD) => patternA -> patternB -> patternC -> patternD -> (Unlifted patternA -> Unlifted patternB -> Unlifted patternC -> Unlifted patternD -> a) -> Acc (Tuple patternA) -> Acc (Tuple patternB) -> Acc (Tuple patternC) -> Acc (Tuple patternD) -> Acc (Plain a) Source #

data Acc a Source #

Constructors

Acc 

Instances

Arrays a => Unlift (Acc a) Source # 

Associated Types

type Unlifted (Acc a) :: * Source #

type Tuple (Acc a) :: * Source #

Methods

unlift :: Acc a -> Acc (Tuple (Acc a)) -> Unlifted (Acc a) Source #

type Unlifted (Acc a) Source # 
type Unlifted (Acc a) = Acc a
type Tuple (Acc a) Source # 
type Tuple (Acc a) = a

data Exp e Source #

Constructors

Exp 

Instances

Elt a => Unlift (Exp a) Source # 

Associated Types

type Unlifted (Exp a) :: * Source #

type Tuple (Exp a) :: * Source #

Methods

unlift :: Exp a -> Exp (Tuple (Exp a)) -> Unlifted (Exp a) Source #

Elt a => Unlift (Exp a) Source # 

Associated Types

type Unlifted (Exp a) :: * Source #

type Tuple (Exp a) :: * Source #

Methods

unlift :: Exp a -> Acc (Tuple (Exp a)) -> Unlifted (Exp a) Source #

type Unlifted (Exp a) Source # 
type Unlifted (Exp a) = Exp a
type Tuple (Exp a) Source # 
type Tuple (Exp a) = a
type Unlifted (Exp a) Source # 
type Unlifted (Exp a) = Exp a
type Tuple (Exp a) Source # 
type Tuple (Exp a) = Scalar a

unliftPair :: (Arrays a, Arrays b) => Acc (a, b) -> (Acc a, Acc b) Source #

unliftTriple :: (Arrays a, Arrays b, Arrays c) => Acc (a, b, c) -> (Acc a, Acc b, Acc c) Source #

unliftQuadruple :: (Arrays a, Arrays b, Arrays c, Arrays d) => Acc (a, b, c, d) -> (Acc a, Acc b, Acc c, Acc d) Source #

mapFst :: (Arrays a, Arrays b, Arrays c) => (Acc a -> Acc b) -> Acc (a, c) -> Acc (b, c) Source #

mapSnd :: (Arrays a, Arrays b, Arrays c) => (Acc b -> Acc c) -> Acc (a, b) -> Acc (a, c) Source #

singleton :: Elt e => e -> Scalar e Source #

like unit in the Acc environment

the :: Elt e => Scalar e -> e Source #

like the in the Acc environment