{-# LANGUAGE TupleSections #-}

-- | Extra functions for working with pairs and triples.
--   Some of these functions are available in the "Control.Arrow" module,
--   but here are available specialised to pairs. Some operations work on triples.
module Data.Tuple.Extra(
    module Data.Tuple,
    -- * Specialised 'Arrow' functions
    first, second, (***), (&&&),
    -- * More pair operations
    dupe, both,
    -- * Monadic versions
    firstM, secondM,
    -- * Operations on triple
    fst3, snd3, thd3,
    first3, second3, third3,
    curry3, uncurry3
    ) where

import Data.Tuple
import qualified Control.Arrow as Arrow

infixr 3 ***, &&&

-- | Update the first component of a pair.
--
-- > first succ (1,"test") == (2,"test")
first :: (a -> a') -> (a, b) -> (a', b)
first :: forall a a' b. (a -> a') -> (a, b) -> (a', b)
first = forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
Arrow.first

-- | Update the second component of a pair.
--
-- > second reverse (1,"test") == (1,"tset")
second :: (b -> b') -> (a, b) -> (a, b')
second :: forall b b' a. (b -> b') -> (a, b) -> (a, b')
second = forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
Arrow.second

-- | Update the first component of a pair.
--
-- > firstM (\x -> [x-1, x+1]) (1,"test") == [(0,"test"),(2,"test")]
firstM :: Functor m => (a -> m a') -> (a, b) -> m (a', b)
firstM :: forall (m :: * -> *) a a' b.
Functor m =>
(a -> m a') -> (a, b) -> m (a', b)
firstM a -> m a'
f ~(a
a,b
b) = (,b
b) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> m a'
f a
a

-- | Update the second component of a pair.
--
-- > secondM (\x -> [reverse x, x]) (1,"test") == [(1,"tset"),(1,"test")]
secondM :: Functor m => (b -> m b') -> (a, b) -> m (a, b')
secondM :: forall (m :: * -> *) b b' a.
Functor m =>
(b -> m b') -> (a, b) -> m (a, b')
secondM b -> m b'
f ~(a
a,b
b) = (a
a,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> b -> m b'
f b
b

-- | Given two functions, apply one to the first component and one to the second.
--   A specialised version of 'Control.Arrow.***'.
--
-- > (succ *** reverse) (1,"test") == (2,"tset")
(***) :: (a -> a') -> (b -> b') -> (a, b) -> (a', b')
*** :: forall a a' b b'. (a -> a') -> (b -> b') -> (a, b) -> (a', b')
(***) = forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
(Arrow.***)

-- | Given two functions, apply both to a single argument to form a pair.
--   A specialised version of 'Control.Arrow.&&&'.
--
-- > (succ &&& pred) 1 == (2,0)
(&&&) :: (a -> b) -> (a -> c) -> a -> (b, c)
&&& :: forall a b c. (a -> b) -> (a -> c) -> a -> (b, c)
(&&&) = forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
(Arrow.&&&)

-- | Duplicate a single value into a pair.
--
-- > dupe 12 == (12, 12)
dupe :: a -> (a,a)
dupe :: forall a. a -> (a, a)
dupe a
x = (a
x,a
x)

-- | Apply a single function to both components of a pair.
--
-- > both succ (1,2) == (2,3)
both :: (a -> b) -> (a, a) -> (b, b)
both :: forall a b. (a -> b) -> (a, a) -> (b, b)
both a -> b
f ~(a
x,a
y) = (a -> b
f a
x, a -> b
f a
y)

-- | Extract the 'fst' of a triple.
fst3 :: (a,b,c) -> a
fst3 :: forall a b c. (a, b, c) -> a
fst3 (a
a,b
b,c
c) = a
a

-- | Extract the 'snd' of a triple.
snd3 :: (a,b,c) -> b
snd3 :: forall a b c. (a, b, c) -> b
snd3 (a
a,b
b,c
c) = b
b

-- | Extract the final element of a triple.
thd3 :: (a,b,c) -> c
thd3 :: forall a b c. (a, b, c) -> c
thd3 (a
a,b
b,c
c) = c
c

-- | Converts an uncurried function to a curried function.
curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
curry3 :: forall a b c d. ((a, b, c) -> d) -> a -> b -> c -> d
curry3 (a, b, c) -> d
f a
a b
b c
c = (a, b, c) -> d
f (a
a,b
b,c
c)

-- | Converts a curried function to a function on a triple.
uncurry3 :: (a -> b -> c -> d) -> ((a, b, c) -> d)
uncurry3 :: forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 a -> b -> c -> d
f ~(a
a,b
b,c
c) = a -> b -> c -> d
f a
a b
b c
c


-- | Update the first component of a triple.
--
-- > first3 succ (1,1,1) == (2,1,1)
first3 :: (a -> a') -> (a, b, c) -> (a', b, c)
first3 :: forall a a' b c. (a -> a') -> (a, b, c) -> (a', b, c)
first3 a -> a'
f ~(a
a,b
b,c
c) = (a -> a'
f a
a,b
b,c
c)

-- | Update the second component of a triple.
--
-- > second3 succ (1,1,1) == (1,2,1)
second3 :: (b -> b') -> (a, b, c) -> (a, b', c)
second3 :: forall b b' a c. (b -> b') -> (a, b, c) -> (a, b', c)
second3 b -> b'
f ~(a
a,b
b,c
c) = (a
a,b -> b'
f b
b,c
c)

-- | Update the third component of a triple.
--
-- > third3 succ (1,1,1) == (1,1,2)
third3 :: (c -> c') -> (a, b, c) -> (a, b, c')
third3 :: forall c c' a b. (c -> c') -> (a, b, c) -> (a, b, c')
third3 c -> c'
f ~(a
a,b
b,c
c) = (a
a,b
b,c -> c'
f c
c)