module Data.Tuple.HT (
mapPair,
mapFst,
mapSnd,
swap,
sortPair,
forcePair,
double,
fst3,
snd3,
thd3,
mapTriple,
mapFst3,
mapSnd3,
mapThd3,
curry3,
uncurry3,
triple,
) where
import Data.Tuple.Lazy
{-# INLINE double #-}
double :: a -> (a,a)
double a = (a,a)
{-# INLINE triple #-}
triple :: a -> (a,a,a)
triple a = (a,a,a)
{-# 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)
sortPair, _sortPairMinMax :: (Ord a) => (a,a) -> (a,a)
sortPair (x,y) = if x<=y then (x,y) else (y,x)
_sortPairMinMax (x,y) = (min x y, max x y)