extra-1.8: 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
  • data Solo a where
  • uncurry :: (a -> b -> c) -> (a, b) -> c
  • getSolo :: Solo a -> a
  • fst :: (a, b) -> a
  • snd :: (a, b) -> b
  • curry :: ((a, b) -> c) -> a -> b -> c
  • swap :: (a, b) -> (b, a)
  • 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

data Solo a where #

Solo is the canonical lifted 1-tuple, just like (,) is the canonical lifted 2-tuple (pair) and (,,) is the canonical lifted 3-tuple (triple).

The most important feature of Solo is that it is possible to force its "outside" (usually by pattern matching) without forcing its "inside", because it is defined as a datatype rather than a newtype. One situation where this can be useful is when writing a function to extract a value from a data structure. Suppose you write an implementation of arrays and offer only this function to index into them:

index :: Array a -> Int -> a

Now imagine that someone wants to extract a value from an array and store it in a lazy-valued finite map/dictionary:

insert "hello" (arr index 12) m

This can actually lead to a space leak. The value is not actually extracted from the array until that value (now buried in a map) is forced. That means the entire array may be kept live by just that value! Often, the solution is to use a strict map, or to force the value before storing it, but for some purposes that's undesirable.

One common solution is to include an indexing function that can produce its result in an arbitrary Applicative context:

indexA :: Applicative f => Array a -> Int -> f a

When using indexA in a pure context, Solo serves as a handy Applicative functor to hold the result. You could write a non-leaky version of the above example thus:

case arr indexA 12 of
  Solo a -> insert "hello" a m

While such simple extraction functions are the most common uses for unary tuples, they can also be useful for fine-grained control of strict-spined data structure traversals, and for unifying the implementations of lazy and strict mapping functions.

Bundled Patterns

pattern Solo :: a -> Solo a 

Instances

Instances details
MonadFix Solo

Since: base-4.15

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Solo a) -> Solo a #

MonadZip Solo

Since: base-4.15.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Solo a -> Solo b -> Solo (a, b) #

mzipWith :: (a -> b -> c) -> Solo a -> Solo b -> Solo c #

munzip :: Solo (a, b) -> (Solo a, Solo b) #

Foldable Solo

Since: base-4.15

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Solo m -> m #

foldMap :: Monoid m => (a -> m) -> Solo a -> m #

foldMap' :: Monoid m => (a -> m) -> Solo a -> m #

foldr :: (a -> b -> b) -> b -> Solo a -> b #

foldr' :: (a -> b -> b) -> b -> Solo a -> b #

foldl :: (b -> a -> b) -> b -> Solo a -> b #

foldl' :: (b -> a -> b) -> b -> Solo a -> b #

foldr1 :: (a -> a -> a) -> Solo a -> a #

foldl1 :: (a -> a -> a) -> Solo a -> a #

toList :: Solo a -> [a] #

null :: Solo a -> Bool #

length :: Solo a -> Int #

elem :: Eq a => a -> Solo a -> Bool #

maximum :: Ord a => Solo a -> a #

minimum :: Ord a => Solo a -> a #

sum :: Num a => Solo a -> a #

product :: Num a => Solo a -> a #

Foldable1 Solo

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => Solo m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Solo a -> m #

foldMap1' :: Semigroup m => (a -> m) -> Solo a -> m #

toNonEmpty :: Solo a -> NonEmpty a #

maximum :: Ord a => Solo a -> a #

minimum :: Ord a => Solo a -> a #

head :: Solo a -> a #

last :: Solo a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Solo a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Solo a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Solo a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Solo a -> b #

Eq1 Solo

Since: base-4.15

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Solo a -> Solo b -> Bool #

Ord1 Solo

Since: base-4.15

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Solo a -> Solo b -> Ordering #

Read1 Solo

Since: base-4.15

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Solo a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Solo a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Solo a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Solo a] #

Show1 Solo

Since: base-4.15

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Solo a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Solo a] -> ShowS #

Traversable Solo

Since: base-4.15

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Solo a -> f (Solo b) #

sequenceA :: Applicative f => Solo (f a) -> f (Solo a) #

mapM :: Monad m => (a -> m b) -> Solo a -> m (Solo b) #

sequence :: Monad m => Solo (m a) -> m (Solo a) #

Applicative Solo

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

pure :: a -> Solo a #

(<*>) :: Solo (a -> b) -> Solo a -> Solo b #

liftA2 :: (a -> b -> c) -> Solo a -> Solo b -> Solo c #

(*>) :: Solo a -> Solo b -> Solo b #

(<*) :: Solo a -> Solo b -> Solo a #

Functor Solo

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> Solo a -> Solo b #

(<$) :: a -> Solo b -> Solo a #

Monad Solo

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

(>>=) :: Solo a -> (a -> Solo b) -> Solo b #

(>>) :: Solo a -> Solo b -> Solo b #

return :: a -> Solo a #

NFData1 Solo

Since: deepseq-1.4.6.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Solo a -> () #

Generic1 Solo 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Solo

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Solo a -> Rep1 Solo a #

to1 :: Rep1 Solo a -> Solo a #

Data a => Data (Solo a)

Since: base-4.15

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Solo a -> c (Solo a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Solo a) #

toConstr :: Solo a -> Constr #

dataTypeOf :: Solo a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Solo a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Solo a)) #

gmapT :: (forall b. Data b => b -> b) -> Solo a -> Solo a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Solo a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Solo a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Solo a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Solo a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Solo a -> m (Solo a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Solo a -> m (Solo a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Solo a -> m (Solo a) #

Monoid a => Monoid (Solo a)

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

mempty :: Solo a #

mappend :: Solo a -> Solo a -> Solo a #

mconcat :: [Solo a] -> Solo a #

Semigroup a => Semigroup (Solo a)

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

(<>) :: Solo a -> Solo a -> Solo a #

sconcat :: NonEmpty (Solo a) -> Solo a #

stimes :: Integral b => b -> Solo a -> Solo a #

Bounded a => Bounded (Solo a) 
Instance details

Defined in GHC.Enum

Methods

minBound :: Solo a #

maxBound :: Solo a #

Enum a => Enum (Solo a) 
Instance details

Defined in GHC.Enum

Methods

succ :: Solo a -> Solo a #

pred :: Solo a -> Solo a #

toEnum :: Int -> Solo a #

fromEnum :: Solo a -> Int #

enumFrom :: Solo a -> [Solo a] #

enumFromThen :: Solo a -> Solo a -> [Solo a] #

enumFromTo :: Solo a -> Solo a -> [Solo a] #

enumFromThenTo :: Solo a -> Solo a -> Solo a -> [Solo a] #

Generic (Solo a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Solo a)

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep (Solo a) = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Solo a -> Rep (Solo a) x #

to :: Rep (Solo a) x -> Solo a #

Ix a => Ix (Solo a) 
Instance details

Defined in GHC.Ix

Methods

range :: (Solo a, Solo a) -> [Solo a] #

index :: (Solo a, Solo a) -> Solo a -> Int #

unsafeIndex :: (Solo a, Solo a) -> Solo a -> Int #

inRange :: (Solo a, Solo a) -> Solo a -> Bool #

rangeSize :: (Solo a, Solo a) -> Int #

unsafeRangeSize :: (Solo a, Solo a) -> Int #

Read a => Read (Solo a)

Since: base-4.15

Instance details

Defined in GHC.Read

Show a => Show (Solo a)

Since: base-4.15

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Solo a -> ShowS #

show :: Solo a -> String #

showList :: [Solo a] -> ShowS #

NFData a => NFData (Solo a)

Since: deepseq-1.4.6.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Solo a -> () #

Eq a => Eq (Solo a) 
Instance details

Defined in GHC.Classes

Methods

(==) :: Solo a -> Solo a -> Bool #

(/=) :: Solo a -> Solo a -> Bool #

Ord a => Ord (Solo a) 
Instance details

Defined in GHC.Classes

Methods

compare :: Solo a -> Solo a -> Ordering #

(<) :: Solo a -> Solo a -> Bool #

(<=) :: Solo a -> Solo a -> Bool #

(>) :: Solo a -> Solo a -> Bool #

(>=) :: Solo a -> Solo a -> Bool #

max :: Solo a -> Solo a -> Solo a #

min :: Solo a -> Solo a -> Solo a #

type Rep1 Solo

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Solo a)

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep (Solo a) = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

uncurry :: (a -> b -> c) -> (a, b) -> c #

uncurry converts a curried function to a function on pairs.

Examples

Expand
>>> uncurry (+) (1,2)
3
>>> uncurry ($) (show, 1)
"1"
>>> map (uncurry max) [(1,2), (3,4), (6,8)]
[2,4,8]

getSolo :: Solo a -> a #

Extract the value from a Solo. Very often, values should be extracted directly using pattern matching, to control just what gets evaluated when. getSolo is for convenience in situations where that is not the case:

When the result is passed to a strict function, it makes no difference whether the pattern matching is done on the "outside" or on the "inside":

Data.Set.insert (getSolo sol) set === case sol of Solo v -> Data.Set.insert v set

A traversal may be performed in Solo in order to control evaluation internally, while using getSolo to extract the final result. A strict mapping function, for example, could be defined

map' :: Traversable t => (a -> b) -> t a -> t b
map' f = getSolo . traverse ((Solo $!) . f)

fst :: (a, b) -> a #

Extract the first component of a pair.

snd :: (a, b) -> b #

Extract the second component of a pair.

curry :: ((a, b) -> c) -> a -> b -> c #

curry converts an uncurried function to a curried function.

Examples

Expand
>>> curry fst 1 2
1

swap :: (a, b) -> (b, a) #

Swap the components of a pair.

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.