dph-lifted-vseg-0.7.0.1: Data Parallel Haskell lifted array combinators.

Safe HaskellNone

Data.Array.Parallel.Lifted.Closure

Contents

Description

Closures. Used when closure converting the source program during vectorisation.

Synopsis

Closures.

data a :-> b Source

Define the fixity of the closure type constructor.

The type of closures. This bundles up:

Constructors

forall env . PA env => Clo (env -> a -> b) (Int -> PData env -> PData a -> PData b) env 

Instances

Typeable2 :-> 
PR (:-> a b) 
(PR (PRepr (:-> a b)), PA a, PA b) => PA (:-> a b) 

($:) :: (a :-> b) -> a -> bSource

Closure application.

Array Closures.

data family PData a Source

A chunk of parallel array data with a linear index space.

In contrast to a PArray, a PData may not have a fixed length, and its elements may have been converted to a generic representation. Whereas a PArray is the "user view" of an array, a PData is a type only used internally to the library.

($:^) :: PArray (a :-> b) -> PArray a -> PArray bSource

Lifted closure application.

liftedApply :: Int -> PData (a :-> b) -> PData a -> PData bSource

Lifted closure application, taking an explicit lifting context.

Closure Construction.

closure1 :: (a -> b) -> (Int -> PData a -> PData b) -> a :-> bSource

Construct an arity-1 closure, from unlifted and lifted versions of a primitive function.

closure2 :: forall a b c. PA a => (a -> b -> c) -> (Int -> PData a -> PData b -> PData c) -> a :-> (b :-> c)Source

Construct an arity-2 closure, from lifted and unlifted versions of a primitive function.

closure3 :: forall a b c d. (PA a, PA b) => (a -> b -> c -> d) -> (Int -> PData a -> PData b -> PData c -> PData d) -> a :-> (b :-> (c :-> d))Source

Construct an arity-3 closure from lifted and unlifted versions of a primitive function.

closure4 :: forall a b c d e. (PA a, PA b, PA c) => (a -> b -> c -> d -> e) -> (Int -> PData a -> PData b -> PData c -> PData d -> PData e) -> a :-> (b :-> (c :-> (d :-> e)))Source

Construct an arity-4 closure from lifted and unlifted versions of a primitive function.

closure5 :: forall a b c d e f. (PA a, PA b, PA c, PA d) => (a -> b -> c -> d -> e -> f) -> (Int -> PData a -> PData b -> PData c -> PData d -> PData e -> PData f) -> a :-> (b :-> (c :-> (d :-> (e :-> f))))Source

Construct an arity-5 closure from lifted and unlifted versions of a primitive function.

closure6 :: forall a b c d e f g. (PA a, PA b, PA c, PA d, PA e) => (a -> b -> c -> d -> e -> f -> g) -> (Int -> PData a -> PData b -> PData c -> PData d -> PData e -> PData f -> PData g) -> a :-> (b :-> (c :-> (d :-> (e :-> (f :-> g)))))Source

Construct an arity-6 closure from lifted and unlifted versions of a primitive function.

closure7 :: forall a b c d e f g h. (PA a, PA b, PA c, PA d, PA e, PA f) => (a -> b -> c -> d -> e -> f -> g -> h) -> (Int -> PData a -> PData b -> PData c -> PData d -> PData e -> PData f -> PData g -> PData h) -> a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> h))))))Source

Construct an arity-6 closure from lifted and unlifted versions of a primitive function.

closure8 :: forall a b c d e f g h i. (PA a, PA b, PA c, PA d, PA e, PA f, PA g) => (a -> b -> c -> d -> e -> f -> g -> h -> i) -> (Int -> PData a -> PData b -> PData c -> PData d -> PData e -> PData f -> PData g -> PData h -> PData i) -> a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> i)))))))Source

Construct an arity-6 closure from lifted and unlifted versions of a primitive function.

closure1' :: forall a b. (a -> b) -> (PArray a -> PArray b) -> a :-> bSource

Construct an arity-1 closure.

closure2' :: forall a b c. PA a => (a -> b -> c) -> (PArray a -> PArray b -> PArray c) -> a :-> (b :-> c)Source

Construct an arity-2 closure.

closure3' :: forall a b c d. (PA a, PA b) => (a -> b -> c -> d) -> (PArray a -> PArray b -> PArray c -> PArray d) -> a :-> (b :-> (c :-> d))Source

Construct an arity-3 closure.

closure4' :: forall a b c d e. (PA a, PA b, PA c) => (a -> b -> c -> d -> e) -> (PArray a -> PArray b -> PArray c -> PArray d -> PArray e) -> a :-> (b :-> (c :-> (d :-> e)))Source

Construct an arity-4 closure.

closure5' :: forall a b c d e f. (PA a, PA b, PA c, PA d) => (a -> b -> c -> d -> e -> f) -> (PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f) -> a :-> (b :-> (c :-> (d :-> (e :-> f))))Source

Construct an arity-5 closure.

closure6' :: forall a b c d e f g. (PA a, PA b, PA c, PA d, PA e, PA f) => (a -> b -> c -> d -> e -> f -> g) -> (PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f -> PArray g) -> a :-> (b :-> (c :-> (d :-> (e :-> (f :-> g)))))Source

Construct an arity-6 closure.

closure7' :: forall a b c d e f g h. (PA a, PA b, PA c, PA d, PA e, PA f, PA g) => (a -> b -> c -> d -> e -> f -> g -> h) -> (PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f -> PArray g -> PArray h) -> a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> h))))))Source

Construct an arity-7 closure.

closure8' :: forall a b c d e f g h i. (PA a, PA b, PA c, PA d, PA e, PA f, PA g, PA h) => (a -> b -> c -> d -> e -> f -> g -> h -> i) -> (PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f -> PArray g -> PArray h -> PArray i) -> a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> i)))))))Source

Construct an arity-8 closure.