-- |
-- Copyright  : (c) Ivan Perez and Manuel Baerenz, 2016
-- License    : BSD3
-- Maintainer : ivan.perez@keera.co.uk
--
-- Utility functions to work with 'Arrow's.
module Control.Arrow.Util where

-- External imports
import Control.Arrow (Arrow, arr, (&&&), (>>^), (^<<))

-- | Constantly produce the same output.
constantly :: Arrow a => b -> a c b
constantly :: b -> a c b
constantly = (c -> b) -> a c b
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr ((c -> b) -> a c b) -> (b -> c -> b) -> b -> a c b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> c -> b
forall a b. a -> b -> a
const
{-# INLINE constantly #-}

-- * Apply functions at the end

-- | Alternative name for '^<<'.
elementwise :: Arrow a => (c -> d) -> a b c -> a b d
elementwise :: (c -> d) -> a b c -> a b d
elementwise = (c -> d) -> a b c -> a b d
forall (a :: * -> * -> *) c d b.
Arrow a =>
(c -> d) -> a b c -> a b d
(^<<)

-- | Apply a curried function with two arguments to the outputs of two arrows.
elementwise2 :: Arrow a => (c -> d -> e) -> a b c -> a b d -> a b e
elementwise2 :: (c -> d -> e) -> a b c -> a b d -> a b e
elementwise2 c -> d -> e
op a b c
a1 a b d
a2 = (a b c
a1 a b c -> a b d -> a b (c, d)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& a b d
a2) a b (c, d) -> ((c, d) -> e) -> a b e
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> (c -> d) -> a b d
>>^ (c -> d -> e) -> (c, d) -> e
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry c -> d -> e
op