extra-1.7.14: Extra functions I use.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Tuple.Extra

Description

Extra functions for working with pairs and triples. Some of these functions are available in the Control.Arrow module, but here are available specialised to pairs. Some operations work on triples.

Synopsis
  • module Data.Tuple
  • first :: (a -> a') -> (a, b) -> (a', b)
  • second :: (b -> b') -> (a, b) -> (a, b')
  • (***) :: (a -> a') -> (b -> b') -> (a, b) -> (a', b')
  • (&&&) :: (a -> b) -> (a -> c) -> a -> (b, c)
  • dupe :: a -> (a, a)
  • both :: (a -> b) -> (a, a) -> (b, b)
  • firstM :: Functor m => (a -> m a') -> (a, b) -> m (a', b)
  • secondM :: Functor m => (b -> m b') -> (a, b) -> m (a, b')
  • fst3 :: (a, b, c) -> a
  • snd3 :: (a, b, c) -> b
  • thd3 :: (a, b, c) -> c
  • first3 :: (a -> a') -> (a, b, c) -> (a', b, c)
  • second3 :: (b -> b') -> (a, b, c) -> (a, b', c)
  • third3 :: (c -> c') -> (a, b, c) -> (a, b, c')
  • curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
  • uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d

Documentation

module Data.Tuple

Specialised Arrow functions

first :: (a -> a') -> (a, b) -> (a', b) Source #

Update the first component of a pair.

first succ (1,"test") == (2,"test")

second :: (b -> b') -> (a, b) -> (a, b') Source #

Update the second component of a pair.

second reverse (1,"test") == (1,"tset")

(***) :: (a -> a') -> (b -> b') -> (a, b) -> (a', b') infixr 3 Source #

Given two functions, apply one to the first component and one to the second. A specialised version of ***.

(succ *** reverse) (1,"test") == (2,"tset")

(&&&) :: (a -> b) -> (a -> c) -> a -> (b, c) infixr 3 Source #

Given two functions, apply both to a single argument to form a pair. A specialised version of &&&.

(succ &&& pred) 1 == (2,0)

More pair operations

dupe :: a -> (a, a) Source #

Duplicate a single value into a pair.

dupe 12 == (12, 12)

both :: (a -> b) -> (a, a) -> (b, b) Source #

Apply a single function to both components of a pair.

both succ (1,2) == (2,3)

Monadic versions

firstM :: Functor m => (a -> m a') -> (a, b) -> m (a', b) Source #

Update the first component of a pair.

firstM (\x -> [x-1, x+1]) (1,"test") == [(0,"test"),(2,"test")]

secondM :: Functor m => (b -> m b') -> (a, b) -> m (a, b') Source #

Update the second component of a pair.

secondM (\x -> [reverse x, x]) (1,"test") == [(1,"tset"),(1,"test")]

Operations on triple

fst3 :: (a, b, c) -> a Source #

Extract the fst of a triple.

snd3 :: (a, b, c) -> b Source #

Extract the snd of a triple.

thd3 :: (a, b, c) -> c Source #

Extract the final element of a triple.

first3 :: (a -> a') -> (a, b, c) -> (a', b, c) Source #

Update the first component of a triple.

first3 succ (1,1,1) == (2,1,1)

second3 :: (b -> b') -> (a, b, c) -> (a, b', c) Source #

Update the second component of a triple.

second3 succ (1,1,1) == (1,2,1)

third3 :: (c -> c') -> (a, b, c) -> (a, b, c') Source #

Update the third component of a triple.

third3 succ (1,1,1) == (1,1,2)

curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d Source #

Converts an uncurried function to a curried function.

uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d Source #

Converts a curried function to a function on a triple.