module Data.Tuple.Lazy where

-- * Pair

{- | Cf. '(Control.Arrow.***)'.

Apply two functions on corresponding values in a pair,
where the pattern match on the pair constructor is lazy.
This is crucial in recursions such as the one of 'partition'.
One the other hand there are applications
where strict application is crucial,
e.g. @mapSnd f ab@ where the left pair member is a large lazy list.
With the lazy @mapSnd@ we make the application of @f@ depend on the whole pair @ab@.
See "Data.Tuple.Example" for two examples
where one variant is definitely better than the other one.
-}
{-
Instead of lazy pattern matching with \code{(a,b)}
we may use \function{fst} and \function{snd}.
-}
{-# INLINE mapPair #-}
mapPair :: (a -> c, b -> d) -> (a,b) -> (c,d)
mapPair ~(f,g) ~(a,b) = (f a, g b)

-- | 'Control.Arrow.first'
{-# INLINE mapFst #-}
mapFst :: (a -> c) -> (a,b) -> (c,b)
mapFst f ~(a,b) = (f a, b)

-- | 'Control.Arrow.second'
{-# INLINE mapSnd #-}
mapSnd :: (b -> c) -> (a,b) -> (a,c)
mapSnd f ~(a,b) = (a, f b)

{-# INLINE zipWithPair #-}
zipWithPair :: (a -> c -> e, b -> d -> f) -> (a,b) -> (c,d) -> (e,f)
zipWithPair ~(e,f) ~(a,b) ~(c,d) = (e a c, f b d)


{-# INLINE swap #-}
swap :: (a,b) -> (b,a)
swap ~(a,b) = (b,a)

{-# INLINE forcePair #-}
forcePair :: (a,b) -> (a,b)
forcePair ~(a,b) = (a,b)


-- * Triple

{-# INLINE mapTriple #-}
mapTriple :: (a -> d, b -> e, c -> f) -> (a,b,c) -> (d,e,f)
mapTriple ~(f,g,h) ~(a,b,c) = (f a, g b, h c)

{-# INLINE mapFst3 #-}
mapFst3 :: (a -> d) -> (a,b,c) -> (d,b,c)
mapFst3 f ~(a,b,c) = (f a, b, c)

{-# INLINE mapSnd3 #-}
mapSnd3 :: (b -> d) -> (a,b,c) -> (a,d,c)
mapSnd3 f ~(a,b,c) = (a, f b, c)

{-# INLINE mapThd3 #-}
mapThd3 :: (c -> d) -> (a,b,c) -> (a,b,d)
mapThd3 f ~(a,b,c) = (a, b, f c)

{-# INLINE zipWithTriple #-}
zipWithTriple ::
   (a -> d -> g, b -> e -> h, c -> f -> i) -> (a,b,c) -> (d,e,f) -> (g,h,i)
zipWithTriple ~(g,h,i) ~(a,b,c) ~(d,e,f) = (g a d, h b e, i c f)

{-# INLINE uncurry3 #-}
uncurry3 :: (a -> b -> c -> d) -> ((a, b, c) -> d)
uncurry3 f ~(a,b,c) = f a b c