reverse-arguments-0.1.0.0: Reverse the arguments of arbitrary functions.

Copyright(c) Anselm Jonas Scholl 2016
LicenseBSD3
Maintaineranselm.scholl@tu-harburg.de
Stabilityexperimental
Portabilitynon-portable (uses type families and more)
Safe HaskellNone
LanguageHaskell2010

Data.Function.Reverse

Contents

Description

This module provides the reverseArgs function which flips the arguments of a function of arbitrary arity. The return value of the flipped function can not be fully polymorphic as this could imply it is a function.

Example:

myFlip :: (a -> b -> c -> d -> [e]) -> d -> c -> b -> a -> [e]
myFlip = reverseArgs

However, if you supply a proof (of the form IsFun a ~ 'False) that a is not a function, you can also return a polymorphic type.

Example:

myFlip :: IsFun e ~ 'False => (a -> b -> c -> d -> e) -> d -> c -> b -> a -> e
myFlip = reverseArgs

Synopsis

Reversing arguments

reverseArgs :: (ReverseArgs (BoxResult a), Coercible a (BoxResult a), Coercible (ReversedArgs a) (BoxResult (ReversedArgs a)), ReversedArgs (BoxResult a) ~ BoxResult (ReversedArgs a)) => a -> ReversedArgs a Source

Reverse the arguments of a function. Does work with polymorphic return values if you supply a proof that the result is not a function.

Utilities

type family IsFun f Source

Determine whether the argument is a function.

Equations

IsFun (a -> b) = True 
IsFun a = False 

Internal types and functions

Applying the last argument

type family ApplyLast a z Source

Apply the last argument of a function to it.

Equations

ApplyLast (a -> b) z = If (IsFun b) (a -> ApplyLast b z) (MatchLastArg a b z) 

type family MatchLastArg a b z Source

Match the last argument away.

Equations

MatchLastArg z b z = b 

class ApplyingLast f z | f -> z where Source

Like ApplyLast, but on the value level.

Methods

applyLast :: f -> z -> ApplyLast f z Source

Apply a function f to its last argument z.

Instances

((~) * (ApplyLast (a -> b -> c) z) (a -> ApplyLast (b -> c) z), ApplyingLast (b -> c) z) => ApplyingLast (a -> b -> c) z Source 
((~) Bool (IsFun b) False, (~) * a c) => ApplyingLast (a -> b) c Source 

Reversing arguments

type ReversedArgs a = If (IsFun a) (ReverseOneArg a) a Source

Reverse the arguments of a function.

type family ReverseOneArg a Source

Reverse one of the arguments of a function and recurse for the rest.

Equations

ReverseOneArg (a -> b) = InsertAtEnd a (ReversedArgs b) 

type InsertAtEnd a f = If (IsFun f) (InsertAtEndStep a f) (a -> f) Source

Insert an argument at the end.

type family InsertAtEndStep a f Source

Shift one to the left and insert something at the end.

Equations

InsertAtEndStep a (x -> y) = x -> InsertAtEnd a y 

class ReverseArgs a where Source

Methods

reverseArgs' :: a -> ReversedArgs a Source

Reverse the arguments of some function. Does not work with functions with fully polymorphic return values, use reverseArgs instead.

Instances

(~) * (ReversedArgs a) a => ReverseArgs a Source 
(ApplyingLast (a -> b) z, (~) * (ReversedArgs (a -> b)) (z -> r), (~) * (ReversedArgs (ApplyLast (a -> b) z)) r, ReverseArgs (ApplyLast (a -> b) z)) => ReverseArgs (a -> b) Source 

Boxing results

type BoxResult a = If (IsFun a) (BoxArrow a) (Identity a) Source

Box the result in the Identity monad.

type family BoxArrow a Source

Box the result of a function in the Identity monad.

Equations

BoxArrow (a -> b) = a -> BoxResult b 

boxResult :: Coercible a (BoxResult a) => a -> BoxResult a Source

Box the result in the Identity monad.

unboxResult :: Coercible a (BoxResult a) => BoxResult a -> a Source

Unbox the result, which is in the Identity monad.