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

Safe HaskellNone
LanguageHaskell98

Data.Array.Accelerate.Utility.Lift.Exp

Synopsis

Documentation

class (Elt (Tuple pattern), Plain (Unlifted pattern) ~ Tuple pattern) => Unlift pattern where Source #

This class simplifies untupling of expressions. If you have a function

g :: ((Exp a, Exp b), Exp (c,d)) -> (Exp e, Exp f)

you cannot apply it to an array arr :: Array sh ((a,b),(c,d)) using map. Here, the modify function helps:

modify ((expr,expr),expr) g :: Exp ((a,b),(c,d)) -> Exp (e,f)

The expr-pattern tells, how deep the tuple shall be unlifted. This way you can write:

A.map
   (Exp.modify ((expr,expr),expr) $ \((a,b), cd) -> g ((a,b), cd))
   arr

modify is based on unlift. In contrast to unlift it does not only unlift one level of tupels, but is guided by an expr-pattern. In the example I have demonstrated, how the pair (a,b) is unlifted, but the pair (c,d) is not. For the result tuple, modify simply calls lift. In contrast to unlift, lift lifts over all tupel levels until it obtains a single Exp.

Minimal complete definition

unlift

Associated Types

type Unlifted pattern Source #

type Tuple pattern Source #

Methods

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

Instances

Unlift p => Unlift (Complex p) Source # 

Associated Types

type Unlifted (Complex p) :: * Source #

type Tuple (Complex p) :: * Source #

Methods

unlift :: Complex p -> Exp (Tuple (Complex p)) -> Unlifted (Complex p) Source #

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 #

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

Associated Types

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

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

Methods

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

(Unlift pa, Slice (Tuple pa), (~) * int (Exp Int)) => Unlift ((:.) pa int) Source # 

Associated Types

type Unlifted (pa :. int) :: * Source #

type Tuple (pa :. int) :: * Source #

Methods

unlift :: (pa :. int) -> Exp (Tuple (pa :. int)) -> Unlifted (pa :. int) 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) -> Exp (Tuple (pa, pb, pc)) -> Unlifted (pa, pb, pc) Source #

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

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

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

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

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

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

atom :: Exp e Source #

Deprecated: use expr instead

for compatibility with accelerate-utility-0.0

unliftPair :: (Elt a, Elt b) => Exp (a, b) -> (Exp a, Exp b) Source #

unliftTriple :: (Elt a, Elt b, Elt c) => Exp (a, b, c) -> (Exp a, Exp b, Exp c) Source #

unliftQuadruple :: (Elt a, Elt b, Elt c, Elt d) => Exp (a, b, c, d) -> (Exp a, Exp b, Exp c, Exp d) Source #

asExp :: Exp a -> Exp a Source #

mapFst :: (Elt a, Elt b, Elt c) => (Exp a -> Exp b) -> Exp (a, c) -> Exp (b, c) Source #

mapSnd :: (Elt a, Elt b, Elt c) => (Exp b -> Exp c) -> Exp (a, b) -> Exp (a, c) Source #

fst3 :: (Elt a, Elt b, Elt c) => Exp (a, b, c) -> Exp a Source #

snd3 :: (Elt a, Elt b, Elt c) => Exp (a, b, c) -> Exp b Source #

thd3 :: (Elt a, Elt b, Elt c) => Exp (a, b, c) -> Exp c Source #

indexCons :: Slice ix => Exp ix -> Exp Int -> Exp (ix :. Int) Source #