module Data.Tuple.HT where -- * Pair -- | '(Control.Arrow.***)' {-# INLINE mapPair #-} mapPair :: (a -> c, b -> d) -> (a,b) -> (c,d) mapPair ~(f,g) ~(x,y) = (f x, g y) -- | '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 swap #-} swap :: (a,b) -> (b,a) swap ~(x,y) = (y,x) -- * Triple {-# INLINE fst3 #-} fst3 :: (a,b,c) -> a fst3 ~(x,_,_) = x {-# INLINE snd3 #-} snd3 :: (a,b,c) -> b snd3 ~(_,x,_) = x {-# INLINE thd3 #-} thd3 :: (a,b,c) -> c thd3 ~(_,_,x) = x {-# INLINE curry3 #-} curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d curry3 f a b c = f (a,b,c) {-# INLINE uncurry3 #-} uncurry3 :: (a -> b -> c -> d) -> ((a, b, c) -> d) uncurry3 f ~(a,b,c) = f a b c