module Control.Composition ( -- * Postcomposition (.*) , (.**) , (.***) , (.****) -- * Precomposition , (-.) , (-.*) , (-.**) , (-.***) , (-.****) -- * Fancy function application , (-$) -- * Monadic helpers , bisequence' -- * Monadic actions , axe , biaxe -- * Composition with lists of functions , thread -- * Tuple helpers , both -- * Functor helpers , (<&>) -- * Reëxports from base , (&) , fix , on ) where import Control.Arrow ((***)) import Control.Monad #if MIN_VERSION_base(4,8,0) import Data.Function (fix, on, (&)) #else import Data.Function (fix, on) #endif infixr 8 .* infixr 8 .** infixr 8 .*** infixr 8 .**** infixr 8 -.* infixr 8 -.** infixr 8 -.*** infixr 8 -.**** infixl 8 -$ #if !(MIN_VERSION_base(4,8,0)) infixl 1 & #endif infixl 1 <&> #if !(MIN_VERSION_base(4,8,0)) (&) :: a -> (a -> b) -> b (&) x f = f x #endif #if !MIN_VERSION_base(4,8,0) axe :: (Monad m) => [a -> m ()] -> a -> m () #else axe :: (Traversable t, Monad m) => t (a -> m ()) -> a -> m () #endif axe = sequence_ .* sequence #if !MIN_VERSION_base(4,8,0) bisequence' :: (Monad m) => [a -> b -> m c] -> a -> b -> [m c] #else bisequence' :: (Traversable t, Monad m) => t (a -> b -> m c) -> a -> b -> t (m c) #endif bisequence' = sequence .* sequence #if !MIN_VERSION_base(4,8,0) biaxe :: (Monad m) => [a -> b -> m ()] -> a -> b -> m () #else biaxe :: (Traversable t, Monad m) => t (a -> b -> m ()) -> a -> b -> m () #endif biaxe = sequence_ .** bisequence' both :: (a -> b) -> (a, a) -> (b, b) both = join (***) -- | Backwards function application (-$) :: (a -> b -> c) -> b -> a -> c (-$) f x y = f y x -- | As an example: -- -- > λ:> ((*2) .* (+)) 1 3 4 -- > 16 (.*) :: (c -> d) -> (a -> b -> c) -> a -> b -> d (.*) f g x y = f (g x y) (.**) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e (.**) f g x y z = f (g x y z) (.***) :: (e -> f) -> (a -> b -> c -> d -> e) -> a -> b -> c -> d -> f (.***) f g w x y z = f (g w x y z) (.****) :: (f -> g) -> (a -> b -> c -> d -> e -> f) -> a -> b -> c -> d -> e -> g (.****) f g v w x y z = f (g v w x y z) -- | The Oedipus combinator (-.*) :: (b -> c) -> (a -> c -> d) -> a -> b -> d (-.*) f g x y = g x (f y) (-.**) :: (c -> d) -> (a -> b -> d -> e) -> a -> b -> c -> e (-.**) f g x y z = g x y (f z) (-.***) :: (d -> e) -> (a -> b -> c -> e -> f) -> a -> b -> c -> d -> f (-.***) f g w x y z = g w x y (f z) (-.****) :: (e -> f) -> (a -> b -> c -> d -> f -> g) -> a -> b -> c -> d -> e -> g (-.****) f g v w x y z = g v w x y (f z) -- | Backwards function composition (-.) :: (a -> b) -> (b -> c) -> a -> c (-.) f g x = g (f x) (<&>) :: Functor f => f a -> (a -> b) -> f b x <&> f = fmap f x {-# RULES "thread" forall f g. thread [f, g] = f . g #-} {-# RULES "thread" forall f g h. thread [f, g, h] = f . g . h #-} {-# RULES "thread/fmap" forall f fs. thread (f:fs) = f . thread fs #-} thread :: [a -> a] -> a -> a thread = foldr (.) id {-# INLINE [1] thread #-}