{-# LANGUAGE CPP #-}

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
    , ap
    , bool
    ) where

import           Control.Arrow ((***))
import           Control.Monad
#if MIN_VERSION_base(4,7,0)
import           Data.Bool     (bool)
#endif
#if MIN_VERSION_base(4,8,0)
import           Data.Function (fix, on, (&))
#elif defined(MIN_VERSION_lens)
#if MIN_VERSION_lens(4,0)
import           Control.Lens  ((&))
#elif defined(MIN_VERSION_microlens)
import           Lens.Mico     ((&))
#endif
#else
import           Data.Function (fix, on)
#endif
#if defined(MIN_VERSION_lens)
#if MIN_VERSION_lens(3,0)
import           Control.Lens  ((<&>))
#endif
#elif defined(MIN_VERSION_microlens)
#if MIN_VERSION_microlens(4,5)
import           Lens.Micro    ((<&>))
#endif
#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)) && !defined(MIN_VERSION_lens) && !defined(MIN_VERSION_microlens)
infixl 1 &
#elif defined(MIN_VERSION_lens)
#if !(MIN_VERSION_lens(4,0))
infixl 1 &
#endif
#endif
#if defined(MIN_VERSION_lens)
#if !MIN_VERSION_lens(3,0)
infixl 1 <&>
#endif
#elif defined(MIN_VERSION_microlens)
#if !MIN_VERSION_microlens(4,5)
infixl 1 <&>
#endif
#else
infixl 1 <&>
#endif

#if !(MIN_VERSION_base(4,8,0)) && !defined(MIN_VERSION_lens) && !defined(MIN_VERSION_microlens)
(&) :: a -> (a -> b) -> b
(&) x f = f x
#elif defined(MIN_VERSION_lens)
#if !(MIN_VERSION_lens(4,0))
(&) :: a -> (a -> b) -> b
(&) x f = f x
#endif
#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'

#if !MIN_VERSION_base(4,7,0)
-- | See
-- [here](http://hackage.haskell.org/package/base-4.11.1.0/docs/Data-Bool.html#v:bool)
-- for docs.
bool :: a -> a -> Bool -> a
bool x _ False = x
bool _ x True  = x
#endif

both :: (a -> b) -> (a, a) -> (b, b)
both = join (***)

-- | Backwards function
(-$) :: (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)

#if defined(MIN_VERSION_lens)
#if !MIN_VERSION_lens(3,0)
(<&>) :: Functor f => f a -> (a -> b) -> f b
x <&> f = fmap f x
#endif
#elif defined(MIN_VERSION_microlens)
#if !MIN_VERSION_microlens(4,5)
#endif
#else
(<&>) :: Functor f => f a -> (a -> b) -> f b
x <&> f = fmap f x
#endif

{-# 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 #-}