{-# LANGUAGE ScopedTypeVariables #-}
module Htcc.Utils.Tuple (
swap,
first3,
second3,
third3,
dropFst3,
dropSnd3,
dropThd3,
fst4,
snd4,
thd4,
fou4,
first4,
second4,
third4,
fourth4,
dropFst4,
dropSnd4,
dropThd4,
dropFourth4,
curry4,
uncurry4,
) where
import Data.Tuple.Extra (dupe, first, second)
{-# INLINE swap #-}
swap :: (a, b) -> (b, a)
swap :: (a, b) -> (b, a)
swap = ((a, b) -> b) -> ((a, b), a) -> (b, a)
forall a a' b. (a -> a') -> (a, b) -> (a', b)
first (a, b) -> b
forall a b. (a, b) -> b
snd (((a, b), a) -> (b, a))
-> ((a, b) -> ((a, b), a)) -> (a, b) -> (b, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b) -> a) -> ((a, b), (a, b)) -> ((a, b), a)
forall b b' a. (b -> b') -> (a, b) -> (a, b')
second (a, b) -> a
forall a b. (a, b) -> a
fst (((a, b), (a, b)) -> ((a, b), a))
-> ((a, b) -> ((a, b), (a, b))) -> (a, b) -> ((a, b), a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b) -> ((a, b), (a, b))
forall a. a -> (a, a)
dupe
{-# INLINE first3 #-}
first3 :: (a -> d) -> (a, b, c) -> (d, b, c)
first3 :: (a -> d) -> (a, b, c) -> (d, b, c)
first3 f :: a -> d
f (x :: a
x, y :: b
y, z :: c
z) = (a -> d
f a
x, b
y, c
z)
{-# INLINE second3 #-}
second3 :: (b -> d) -> (a, b, c) -> (a, d, c)
second3 :: (b -> d) -> (a, b, c) -> (a, d, c)
second3 f :: b -> d
f (x :: a
x, y :: b
y, z :: c
z) = (a
x, b -> d
f b
y, c
z)
{-# INLINE third3 #-}
third3 :: (c -> d) -> (a, b, c) -> (a, b, d)
third3 :: (c -> d) -> (a, b, c) -> (a, b, d)
third3 f :: c -> d
f (x :: a
x, y :: b
y, z :: c
z) = (a
x, b
y, c -> d
f c
z)
{-# INLINE dropFst3 #-}
dropFst3 :: (a, b, c) -> (b, c)
dropFst3 :: (a, b, c) -> (b, c)
dropFst3 (_, y :: b
y, z :: c
z) = (b
y, c
z)
{-# INLINE dropSnd3 #-}
dropSnd3 :: (a, b, c) -> (a, c)
dropSnd3 :: (a, b, c) -> (a, c)
dropSnd3 (x :: a
x, _, z :: c
z) = (a
x, c
z)
{-# INLINE dropThd3 #-}
dropThd3 :: (a, b, c) -> (a, b)
dropThd3 :: (a, b, c) -> (a, b)
dropThd3 (x :: a
x, y :: b
y, _) = (a
x, b
y)
{-# INLINE dropFst4 #-}
dropFst4 :: (a, b, c, d) -> (b, c, d)
dropFst4 :: (a, b, c, d) -> (b, c, d)
dropFst4 (_, b :: b
b, c :: c
c, d :: d
d) = (b
b, c
c, d
d)
{-# INLINE dropSnd4 #-}
dropSnd4 :: (a, b, c, d) -> (a, c, d)
dropSnd4 :: (a, b, c, d) -> (a, c, d)
dropSnd4 (a :: a
a, _, c :: c
c, d :: d
d) = (a
a, c
c, d
d)
{-# INLINE dropThd4 #-}
dropThd4 :: (a, b, c, d) -> (a, b, d)
dropThd4 :: (a, b, c, d) -> (a, b, d)
dropThd4 (a :: a
a, b :: b
b, _, d :: d
d) = (a
a, b
b, d
d)
{-# INLINE dropFourth4 #-}
dropFourth4 :: (a, b, c, d) -> (a, b, c)
dropFourth4 :: (a, b, c, d) -> (a, b, c)
dropFourth4 (a :: a
a, b :: b
b, c :: c
c, _) = (a
a, b
b, c
c)
{-# INLINE fst4 #-}
fst4 :: (a, b, c, d) -> a
fst4 :: (a, b, c, d) -> a
fst4 (a :: a
a, _, _, _) = a
a
{-# INLINE snd4 #-}
snd4 :: (a, b, c, d) -> b
snd4 :: (a, b, c, d) -> b
snd4 (_, b :: b
b, _, _) = b
b
{-# INLINE thd4 #-}
thd4 :: (a, b, c, d) -> c
thd4 :: (a, b, c, d) -> c
thd4 (_, _, c :: c
c, _) = c
c
{-# INLINE fou4 #-}
fou4 :: (a, b, c, d) -> d
fou4 :: (a, b, c, d) -> d
fou4 (_, _, _, d :: d
d) = d
d
{-# INLINE first4 #-}
first4 :: (a -> e) -> (a, b, c, d) -> (e, b, c, d)
first4 :: (a -> e) -> (a, b, c, d) -> (e, b, c, d)
first4 f :: a -> e
f (a :: a
a, b :: b
b, c :: c
c, d :: d
d) = (a -> e
f a
a, b
b, c
c, d
d)
{-# INLINE second4 #-}
second4 :: (b -> e) -> (a, b, c, d) -> (a, e, c, d)
second4 :: (b -> e) -> (a, b, c, d) -> (a, e, c, d)
second4 f :: b -> e
f (a :: a
a, b :: b
b, c :: c
c, d :: d
d) = (a
a, b -> e
f b
b, c
c, d
d)
{-# INLINE third4 #-}
third4 :: (c -> e) -> (a, b, c, d) -> (a, b, e, d)
third4 :: (c -> e) -> (a, b, c, d) -> (a, b, e, d)
third4 f :: c -> e
f (a :: a
a, b :: b
b, c :: c
c, d :: d
d) = (a
a, b
b, c -> e
f c
c, d
d)
{-# INLINE fourth4 #-}
fourth4 :: (d -> e) -> (a, b, c, d) -> (a, b, c, e)
fourth4 :: (d -> e) -> (a, b, c, d) -> (a, b, c, e)
fourth4 f :: d -> e
f (a :: a
a, b :: b
b, c :: c
c, d :: d
d) = (a
a, b
b, c
c, d -> e
f d
d)
{-# INLINE curry4 #-}
curry4 :: ((a, b, c, d) -> e) -> a -> b -> c -> d -> e
curry4 :: ((a, b, c, d) -> e) -> a -> b -> c -> d -> e
curry4 f :: (a, b, c, d) -> e
f a :: a
a b :: b
b c :: c
c d :: d
d = (a, b, c, d) -> e
f (a
a, b
b, c
c, d
d)
{-# INLINE uncurry4 #-}
uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 f :: a -> b -> c -> d -> e
f (a :: a
a, b :: b
b, c :: c
c, d :: d
d) = a -> b -> c -> d -> e
f a
a b
b c
c d
d