tuple component functions

trb@eastpac.com.au trb@eastpac.com.au
Sat, 18 Sep 1999 07:08:35 +0000 (/etc/localtime)


S.D.Mechveliani writes:
 > As Haskell has the standard functions  fst, snd  to decompose  (a,b),
 > maybe, it worths to provide also
 >                           tuple31, tuple31, tuple31,
 >                           ...
 >                           tuple51, tuple52, tuple53, tuple54, tuple55
 > 
 > for the tuples of  n = 3,4,5 ?

I've found some of these useful, except I named them differently:

> fst3 :: (a,b,c) -> a
> fst3 (x,_,_) = x

> snd3 :: (a,b,c) -> b
> snd3 (_,x,_) = x

> thd3 :: (a,b,c) -> c
> thd3 (_,_,x) = x     

.... never got around to quadruples etc.

I also defined (some of these may be untested):

> tripl :: a -> (a,a,a)
> tripl x = (x,x,x)

> curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
> curry3 f x y z =  f (x, y, z)

> uncurry3 :: (a -> b -> c -> d) -> ((a, b, c) -> d)
> uncurry3 f t = f (fst3 t) (snd3 t) (thd3 t)

> applyTriple :: (a -> b, a -> c, a -> d) -> a -> (b,c,d)
> applyTriple (f,g,h) x = (f x, g x, h x)

> cross3 :: (a -> b, c -> d, e -> f) -> (a,c,e) -> (b,d,f)
> cross3 (f,g,h) (x,y,z) = (f x, g y, h z)

> mapTriple :: (a -> b) -> (a, a, a) -> (b, b, b)
> mapTriple = cross3 . tripl	  

> applyFst3 :: (a -> b) -> (a, c, d) -> (b, c, d)
> applyFst3 f = applyTriple (f . fst3, snd3, thd3)

> applySnd3 :: (a -> b) -> (c, a, d) -> (c, b, d)
> applySnd3 f = applyTriple (fst3, f . snd3, thd3)

> applyThd3 :: (a -> b) -> (c, d, a) -> (c, d, b)
> applyThd3 f = applyTriple (fst3, snd3, f . thd3)

> applyArgs3 :: (a -> b) -> (c -> d) -> (e -> f) -> (b -> d -> f -> g) -> (a -> c -> e -> g)
> applyArgs3 af1 af2 af3 f = \x y z -> f (af1 x) (af2 y) (af3 z)

> rotl :: (a -> b -> c -> d) -> (b -> c -> a -> d)
> rotl f y z x = f x y z

> rotr :: (a -> b -> c -> d) -> (c -> a -> b -> d)
> rotr f z x y = f x y z

> rotl4 :: (a -> b -> c -> d -> e) -> (b -> c -> d -> a -> e)
> rotl4 f y z t x = f x y z t

> rotr4 :: (a -> b -> c -> d -> e) -> (d -> a -> b -> c -> e)
> rotr4 f t x y z = f x y z t


Some more combinators (only for pairs so far):

> twin :: a -> (a,a)
> twin x = (x,x)

> swap :: (a,b) -> (b,a)
> swap (x,y) = (y,x)

-- apply a pair of functions to one argument
> applyPair :: (a -> b, a -> c) -> a -> (b, c)
> applyPair (f, g) x = (f x, g x)

-- apply a pair of functions to a pair
> cross :: (a -> b, c -> d) -> (a, c) -> (b, d)
> cross (f, g) = applyPair (f . fst, g . snd)

-- compose a pair of functions onto one function
> dotPair :: (a -> b, a -> c) -> (d -> a) -> (d -> b, d -> c)
> dotPair (f, g) h = (f . h, g . h)	

-- compose a pair of functions onto a pair of functions
> dotCross :: (a -> b, c -> d) -> (e -> a, f -> c) -> (e -> b, f -> d)
> dotCross (f, g) (h, i) = (f . h, g . i)

> mapPair :: (a -> b) -> (a, a) -> (b, b)
> mapPair = cross . twin

> applyFst :: (a -> b) -> (a, c) -> (b, c)
> applyFst f = applyPair (f . fst, snd)

> applySnd :: (a -> b) -> (c, a) -> (c, b)
> applySnd f = applyPair (fst, f . snd)

> applyArgs :: (a -> b) -> (c -> d) -> (b -> d -> e) -> (a -> c -> e)
> applyArgs af1 af2 f = \x y -> f (af1 x) (af2 y)

> betweenFst :: (a -> b -> c) -> (a, d) -> (b, e) -> c
> betweenFst = applyArgs fst fst

> betweenSnd :: (a -> b -> c) -> (d, a) -> (e, b) -> c
> betweenSnd = applyArgs snd snd


I find these combinators useful, and probably other people have their own
versions - it would be nice to get them standardised, so we all speak the same
language. By standardised, I mean a prominent version that will be adopted by
users, not necessarily a committee process.

Tim