accelerate-0.9.0.1: An embedded language for accelerated array processing

Portabilitynon-portable (GHC extensions)
Stabilityexperimental
MaintainerManuel M T Chakravarty <chak@cse.unsw.edu.au>
Safe HaskellNone

Data.Array.Accelerate.Smart

Contents

Description

This modules defines the AST of the user-visible embedded language using more convenient higher-order abstract syntax (instead of de Bruijn indices). Moreover, it defines smart constructors to construct programs.

Synopsis

HOAS AST

newtype Acc a Source

Array-valued collective computations

Constructors

Acc (PreAcc Acc a) 

Instances

Typeable1 Acc 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) 
(Elt t, IsBounded t) => Bounded (Exp t) 
(Elt t, IsScalar t) => Enum (Exp t) 
(Elt t, IsScalar t) => Eq (Exp t) 
(Elt t, IsFloating t) => Floating (Exp t) 
(Elt t, IsFloating t) => Fractional (Exp t) 
(Elt t, IsIntegral t) => Integral (Exp t) 
(Elt t, IsNum t) => Num (Exp t) 
(Elt t, IsScalar t) => Ord (Exp t) 
(Elt t, IsNum t) => Real (Exp t) 
(Elt t, IsFloating t) => RealFloat (Exp t) 
(Elt t, IsFloating t) => RealFrac (Exp t) 
Show (Exp a) 
Arrays arrs => Show (Acc arrs) 
(Elt t, IsNum t, IsIntegral t) => Bits (Exp t) 
Lift (Exp e) 
(Elt a, Elt b) => Unlift (Exp a, Exp b) 
(Elt e, Slice (Plain ix), Unlift ix) => Unlift (:. ix (Exp e)) 
(Elt e, Slice (Plain ix), Lift ix) => Lift (:. ix (Exp e)) 
(Elt a, Elt b, Elt c) => Unlift (Exp a, Exp b, Exp c) 
(Elt a, Elt b, Elt c, Elt d) => Unlift (Exp a, Exp b, Exp c, Exp d) 
(Elt a, Elt b, Elt c, Elt d, Elt e) => Unlift (Exp a, Exp b, Exp c, Exp d, Exp e) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Unlift (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Unlift (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Unlift (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Unlift (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) 

data PreAcc acc a whereSource

Array-valued collective computations without a recursive knot

Note [Pipe and sharing recovery] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The Pipe constructor is special. It is the only form that contains functions over array computations and these functions are fixed to be over vanilla Acc types. This enables us to perform sharing recovery independently from the context for them.

Constructors

Atag :: Arrays as => Int -> PreAcc acc as 
Pipe :: (Arrays as, Arrays bs, Arrays cs) => (Acc as -> Acc bs) -> (Acc bs -> Acc cs) -> acc as -> PreAcc acc cs 
Acond :: Arrays as => PreExp acc Bool -> acc as -> acc as -> PreAcc acc as 
FstArray :: (Shape sh1, Shape sh2, Elt e1, Elt e2) => acc (Array sh1 e1, Array sh2 e2) -> PreAcc acc (Array sh1 e1) 
SndArray :: (Shape sh1, Shape sh2, Elt e1, Elt e2) => acc (Array sh1 e1, Array sh2 e2) -> PreAcc acc (Array sh2 e2) 
PairArrays :: (Shape sh1, Shape sh2, Elt e1, Elt e2) => acc (Array sh1 e1) -> acc (Array sh2 e2) -> PreAcc acc (Array sh1 e1, Array sh2 e2) 
Use :: (Shape sh, Elt e) => Array sh e -> PreAcc acc (Array sh e) 
Unit :: Elt e => PreExp acc e -> PreAcc acc (Scalar e) 
Generate :: (Shape sh, Elt e) => PreExp acc sh -> (Exp sh -> PreExp acc e) -> PreAcc acc (Array sh e) 
Reshape :: (Shape sh, Shape sh', Elt e) => PreExp acc sh -> acc (Array sh' e) -> PreAcc acc (Array sh e) 
Replicate :: (Slice slix, Elt e, Typeable (SliceShape slix), Typeable (FullShape slix)) => PreExp acc slix -> acc (Array (SliceShape slix) e) -> PreAcc acc (Array (FullShape slix) e) 
Index :: (Slice slix, Elt e, Typeable (SliceShape slix), Typeable (FullShape slix)) => acc (Array (FullShape slix) e) -> PreExp acc slix -> PreAcc acc (Array (SliceShape slix) e) 
Map :: (Shape sh, Elt e, Elt e') => (Exp e -> PreExp acc e') -> acc (Array sh e) -> PreAcc acc (Array sh e') 
ZipWith :: (Shape sh, Elt e1, Elt e2, Elt e3) => (Exp e1 -> Exp e2 -> PreExp acc e3) -> acc (Array sh e1) -> acc (Array sh e2) -> PreAcc acc (Array sh e3) 
Fold :: (Shape sh, Elt e) => (Exp e -> Exp e -> PreExp acc e) -> PreExp acc e -> acc (Array (sh :. Int) e) -> PreAcc acc (Array sh e) 
Fold1 :: (Shape sh, Elt e) => (Exp e -> Exp e -> PreExp acc e) -> acc (Array (sh :. Int) e) -> PreAcc acc (Array sh e) 
FoldSeg :: (Shape sh, Elt e) => (Exp e -> Exp e -> PreExp acc e) -> PreExp acc e -> acc (Array (sh :. Int) e) -> acc Segments -> PreAcc acc (Array (sh :. Int) e) 
Fold1Seg :: (Shape sh, Elt e) => (Exp e -> Exp e -> PreExp acc e) -> acc (Array (sh :. Int) e) -> acc Segments -> PreAcc acc (Array (sh :. Int) e) 
Scanl :: Elt e => (Exp e -> Exp e -> PreExp acc e) -> PreExp acc e -> acc (Vector e) -> PreAcc acc (Vector e) 
Scanl' :: Elt e => (Exp e -> Exp e -> PreExp acc e) -> PreExp acc e -> acc (Vector e) -> PreAcc acc (Vector e, Scalar e) 
Scanl1 :: Elt e => (Exp e -> Exp e -> PreExp acc e) -> acc (Vector e) -> PreAcc acc (Vector e) 
Scanr :: Elt e => (Exp e -> Exp e -> PreExp acc e) -> PreExp acc e -> acc (Vector e) -> PreAcc acc (Vector e) 
Scanr' :: Elt e => (Exp e -> Exp e -> PreExp acc e) -> PreExp acc e -> acc (Vector e) -> PreAcc acc (Vector e, Scalar e) 
Scanr1 :: Elt e => (Exp e -> Exp e -> PreExp acc e) -> acc (Vector e) -> PreAcc acc (Vector e) 
Permute :: (Shape sh, Shape sh', Elt e) => (Exp e -> Exp e -> PreExp acc e) -> acc (Array sh' e) -> (Exp sh -> PreExp acc sh') -> acc (Array sh e) -> PreAcc acc (Array sh' e) 
Backpermute :: (Shape sh, Shape sh', Elt e) => PreExp acc sh' -> (Exp sh' -> PreExp acc sh) -> acc (Array sh e) -> PreAcc acc (Array sh' e) 
Stencil :: (Shape sh, Elt a, Elt b, Stencil sh a stencil) => (stencil -> PreExp acc b) -> Boundary a -> acc (Array sh a) -> PreAcc acc (Array sh b) 
Stencil2 :: (Shape sh, Elt a, Elt b, Elt c, Stencil sh a stencil1, Stencil sh b stencil2) => (stencil1 -> stencil2 -> PreExp acc c) -> Boundary a -> acc (Array sh a) -> Boundary b -> acc (Array sh b) -> PreAcc acc (Array sh c) 

type Exp t = PreExp Acc tSource

Scalar expressions for plain array computations.

data PreExp acc t whereSource

Scalar expressions to parametrise collective array operations, themselves parameterised over the type of collective array operations.

Constructors

Tag :: Elt t => Int -> PreExp acc t 
Const :: Elt t => t -> PreExp acc t 
Tuple :: (Elt t, IsTuple t) => Tuple (PreExp acc) (TupleRepr t) -> PreExp acc t 
Prj :: (Elt t, IsTuple t) => TupleIdx (TupleRepr t) e -> PreExp acc t -> PreExp acc e 
IndexNil :: PreExp acc Z 
IndexCons :: (Slice sl, Elt a) => PreExp acc sl -> PreExp acc a -> PreExp acc (sl :. a) 
IndexHead :: (Slice sl, Elt a) => PreExp acc (sl :. a) -> PreExp acc a 
IndexTail :: (Slice sl, Elt a) => PreExp acc (sl :. a) -> PreExp acc sl 
IndexAny :: Shape sh => PreExp acc (Any sh) 
Cond :: PreExp acc Bool -> PreExp acc t -> PreExp acc t -> PreExp acc t 
PrimConst :: Elt t => PrimConst t -> PreExp acc t 
PrimApp :: (Elt a, Elt r) => PrimFun (a -> r) -> PreExp acc a -> PreExp acc r 
IndexScalar :: (Shape sh, Elt t) => acc (Array sh t) -> PreExp acc sh -> PreExp acc t 
Shape :: (Shape sh, Elt e) => acc (Array sh e) -> PreExp acc sh 
Size :: (Shape sh, Elt e) => acc (Array sh e) -> PreExp acc Int 

Instances

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) 
(Elt t, IsBounded t) => Bounded (Exp t) 
(Elt t, IsScalar t) => Enum (Exp t) 
(Elt t, IsScalar t) => Eq (Exp t) 
(Elt t, IsFloating t) => Floating (Exp t) 
(Elt t, IsFloating t) => Fractional (Exp t) 
(Elt t, IsIntegral t) => Integral (Exp t) 
(Elt t, IsNum t) => Num (Exp t) 
(Elt t, IsScalar t) => Ord (Exp t) 
(Elt t, IsNum t) => Real (Exp t) 
(Elt t, IsFloating t) => RealFloat (Exp t) 
(Elt t, IsFloating t) => RealFrac (Exp t) 
Show (Exp a) 
(Elt t, IsNum t, IsIntegral t) => Bits (Exp t) 
Lift (Exp e) 
(Elt a, Elt b) => Unlift (Exp a, Exp b) 
(Elt e, Slice (Plain ix), Unlift ix) => Unlift (:. ix (Exp e)) 
(Elt e, Slice (Plain ix), Lift ix) => Lift (:. ix (Exp e)) 
(Elt a, Elt b, Elt c) => Unlift (Exp a, Exp b, Exp c) 
(Elt a, Elt b, Elt c, Elt d) => Unlift (Exp a, Exp b, Exp c, Exp d) 
(Elt a, Elt b, Elt c, Elt d, Elt e) => Unlift (Exp a, Exp b, Exp c, Exp d, Exp e) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Unlift (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Unlift (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Unlift (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Unlift (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) 

data Boundary a Source

Boundary condition specification for stencil operations.

Constructors

Clamp

clamp coordinates to the extent of the array

Mirror

mirror coordinates beyond the array extent

Wrap

wrap coordinates around on each dimension

Constant a

use a constant value for outlying coordinates

Instances

Read a => Read (Boundary a) 
Show a => Show (Boundary a) 

class (Elt (StencilRepr sh stencil), Stencil sh a (StencilRepr sh stencil)) => Stencil sh a stencil whereSource

Smart constructors for stencil reification -------------------------------------------

Associated Types

type StencilRepr sh stencil :: *Source

Methods

stencilPrj :: sh -> a -> Exp (StencilRepr sh stencil) -> stencilSource

Instances

Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) 
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) 
(Stencil (:. sh Int) a row2, Stencil (:. sh Int) a row1, Stencil (:. sh Int) a row0) => Stencil (:. (:. sh Int) Int) a (row2, row1, row0) 
(Stencil (:. sh Int) a row1, Stencil (:. sh Int) a row2, Stencil (:. sh Int) a row3, Stencil (:. sh Int) a row4, Stencil (:. sh Int) a row5) => Stencil (:. (:. sh Int) Int) a (row1, row2, row3, row4, row5) 
(Stencil (:. sh Int) a row1, Stencil (:. sh Int) a row2, Stencil (:. sh Int) a row3, Stencil (:. sh Int) a row4, Stencil (:. sh Int) a row5, Stencil (:. sh Int) a row6, Stencil (:. sh Int) a row7) => Stencil (:. (:. sh Int) Int) a (row1, row2, row3, row4, row5, row6, row7) 
(Stencil (:. sh Int) a row1, Stencil (:. sh Int) a row2, Stencil (:. sh Int) a row3, Stencil (:. sh Int) a row4, Stencil (:. sh Int) a row5, Stencil (:. sh Int) a row6, Stencil (:. sh Int) a row7, Stencil (:. sh Int) a row8, Stencil (:. sh Int) a row9) => Stencil (:. (:. sh Int) Int) a (row1, row2, row3, row4, row5, row6, row7, row8, row9) 

HOAS -> de Bruijn conversion

convertAcc :: Arrays arrs => Acc arrs -> Acc arrsSource

Conversion from HOAS to de Bruijn computation AST -

Convert a closed array expression to de Bruijn form while also incorporating sharing information.

convertAccFun1 :: forall a b. (Arrays a, Arrays b) => (Acc a -> Acc b) -> Afun (a -> b)Source

Convert a unary function over array computations

Smart constructors for pairing and unpairing

pair :: (Shape sh1, Shape sh2, Elt e1, Elt e2) => Acc (Array sh1 e1) -> Acc (Array sh2 e2) -> Acc (Array sh1 e1, Array sh2 e2)Source

unpair :: (Shape sh1, Shape sh2, Elt e1, Elt e2) => Acc (Array sh1 e1, Array sh2 e2) -> (Acc (Array sh1 e1), Acc (Array sh2 e2))Source

Smart constructors for literals

constant :: Elt t => t -> Exp tSource

Constant scalar expression

Smart constructors and destructors for tuples

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

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

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

tup5 :: (Elt a, Elt b, Elt c, Elt d, Elt e) => (Exp a, Exp b, Exp c, Exp d, Exp e) -> Exp (a, b, c, d, e)Source

tup6 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f) -> Exp (a, b, c, d, e, f)Source

tup7 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g) -> Exp (a, b, c, d, e, f, g)Source

tup8 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h) -> Exp (a, b, c, d, e, f, g, h)Source

tup9 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i) -> Exp (a, b, c, d, e, f, g, h, i)Source

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

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

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

untup5 :: (Elt a, Elt b, Elt c, Elt d, Elt e) => Exp (a, b, c, d, e) -> (Exp a, Exp b, Exp c, Exp d, Exp e)Source

untup6 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Exp (a, b, c, d, e, f) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f)Source

untup7 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Exp (a, b, c, d, e, f, g) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g)Source

untup8 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Exp (a, b, c, d, e, f, g, h) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h)Source

untup9 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Exp (a, b, c, d, e, f, g, h, i) -> (Exp a, Exp b, Exp c, Exp d, Exp e, Exp f, Exp g, Exp h, Exp i)Source

Smart constructors for constants

mkPi :: (Elt r, IsFloating r) => Exp rSource

mkSin :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkCos :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkTan :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkAsin :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkAcos :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkAtan :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkAsinh :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkAcosh :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkAtanh :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkSqrt :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkLog :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkFPow :: (Elt t, IsFloating t) => Exp t -> Exp t -> Exp tSource

mkLogBase :: (Elt t, IsFloating t) => Exp t -> Exp t -> Exp tSource

mkTruncate :: (Elt a, Elt b, IsFloating a, IsIntegral b) => Exp a -> Exp bSource

mkRound :: (Elt a, Elt b, IsFloating a, IsIntegral b) => Exp a -> Exp bSource

mkFloor :: (Elt a, Elt b, IsFloating a, IsIntegral b) => Exp a -> Exp bSource

mkCeiling :: (Elt a, Elt b, IsFloating a, IsIntegral b) => Exp a -> Exp bSource

mkAtan2 :: (Elt t, IsFloating t) => Exp t -> Exp t -> Exp tSource

Smart constructors for primitive functions

mkAdd :: (Elt t, IsNum t) => Exp t -> Exp t -> Exp tSource

mkSub :: (Elt t, IsNum t) => Exp t -> Exp t -> Exp tSource

mkMul :: (Elt t, IsNum t) => Exp t -> Exp t -> Exp tSource

mkNeg :: (Elt t, IsNum t) => Exp t -> Exp tSource

mkAbs :: (Elt t, IsNum t) => Exp t -> Exp tSource

mkSig :: (Elt t, IsNum t) => Exp t -> Exp tSource

mkQuot :: (Elt t, IsIntegral t) => Exp t -> Exp t -> Exp tSource

mkRem :: (Elt t, IsIntegral t) => Exp t -> Exp t -> Exp tSource

mkIDiv :: (Elt t, IsIntegral t) => Exp t -> Exp t -> Exp tSource

mkMod :: (Elt t, IsIntegral t) => Exp t -> Exp t -> Exp tSource

mkBAnd :: (Elt t, IsIntegral t) => Exp t -> Exp t -> Exp tSource

mkBOr :: (Elt t, IsIntegral t) => Exp t -> Exp t -> Exp tSource

mkBXor :: (Elt t, IsIntegral t) => Exp t -> Exp t -> Exp tSource

mkBNot :: (Elt t, IsIntegral t) => Exp t -> Exp tSource

mkBShiftL :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp tSource

mkBShiftR :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp tSource

mkBRotateL :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp tSource

mkBRotateR :: (Elt t, IsIntegral t) => Exp t -> Exp Int -> Exp tSource

mkFDiv :: (Elt t, IsFloating t) => Exp t -> Exp t -> Exp tSource

mkRecip :: (Elt t, IsFloating t) => Exp t -> Exp tSource

mkLt :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

mkGt :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

mkLtEq :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

mkGtEq :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

mkEq :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

mkNEq :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp BoolSource

mkMax :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp tSource

mkMin :: (Elt t, IsScalar t) => Exp t -> Exp t -> Exp tSource

Smart constructors for type coercion functions

mkFromIntegral :: (Elt a, Elt b, IsIntegral a, IsNum b) => Exp a -> Exp bSource

Auxiliary functions

($$) :: (b -> a) -> (c -> d -> b) -> c -> d -> aSource

($$$) :: (b -> a) -> (c -> d -> e -> b) -> c -> d -> e -> aSource

($$$$) :: (b -> a) -> (c -> d -> e -> f -> b) -> c -> d -> e -> f -> aSource

($$$$$) :: (b -> a) -> (c -> d -> e -> f -> g -> b) -> c -> d -> e -> f -> g -> aSource