module Control.Composition
(
(.*)
, (.**)
, (.***)
, (.****)
, (-.)
, (-.*)
, (-.**)
, (-.***)
, (-.****)
, (-$)
, bisequence'
, axe
, biaxe
, thread
, both
, (<&>)
, (&)
, fix
, on
) where
import Control.Arrow ((***))
import Control.Monad
import Data.Function (fix, on, (&))
import Data.Functor ((<&>))
infixr 8 .*
infixr 8 .**
infixr 8 .***
infixr 8 .****
infixr 8 -.*
infixr 8 -.**
infixr 8 -.***
infixr 8 -.****
infixl 8 -$
axe :: (Traversable t, Monad m) => t (a -> m ()) -> a -> m ()
axe = sequence_ .* sequence
bisequence' :: (Traversable t, Monad m) => t (a -> b -> m c) -> a -> b -> t (m c)
bisequence' = sequence .* sequence
biaxe :: (Traversable t, Monad m) => t (a -> b -> m ()) -> a -> b -> m ()
biaxe = sequence_ .** bisequence'
both :: (a -> b) -> (a, a) -> (b, b)
both = join (***)
(-$) :: (a -> b -> c) -> b -> a -> c
(-$) f x y = f y x
(.*) :: (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)
(-.*) :: (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)
(-.) :: (a -> b) -> (b -> c) -> a -> c
(-.) f g x = g (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 #-}