Reputation: 21
How do I add the elements of two tuples in Haskell to give me a third tuple. The signature is something like,
Add :: (Int,Int) -> (Int,Int) ->(Int,Int)
Add a b = ....
So far, I am only able to think of this:
Add a b = [(x, y) | a = (x1, y1), b = (x2, y2), x=x1+x2, y =y1+y2n]
I am very new to Haskell however, so is what I am doing even correct?
Upvotes: 1
Views: 3959
Reputation: 71119
The type of the finally produced value of your function starts with a (
but a list's type starts with a [
. They can't match, so your approach can't be right. But we can mend it.
You are correct in trying to pattern match the values with the tuples of variables, but actually the patterns go to the left and values go to the right of the equal sign. And it must be inside a let
:
add1 :: (Int,Int) -> (Int,Int) -> [(Int,Int)] -- NB: added brackets!
add1 a b = [(x, y) | let (x1, y1) = a ; (x2, y2) = b ;
x = x1 + x2 ; y = y1 + y2 ]
and actually we don't need that let
inside the list comprehension,
add2 :: (Int,Int) -> (Int,Int) -> [(Int,Int)]
add2 a b = let { (x1, y1) = a ; (x2, y2) = b ;
x = x1 + x2 ; y = y1 + y2 } in
[(x, y)]
and now we can just get rid of those brackets, to get the value and the type which you wanted.
There's another, a bit tricky way to make your original code work without changing anything in it (except fixing the wrong capitalization of add
and making it the proper let
syntax of course).
We just add one word and enable one extension, and it works:
{-# LANGUAGE MonadComprehensions #-}
import Data.Function.Identity
add :: (Int,Int) -> (Int,Int) -> (Int,Int)
add a b = magicWord
[(x, y) | let { (x1, y1) = a ; (x2, y2) = b ;
x = x1 + x2 ; y = y1 + y2 } ]
The magic word is
magicWord = runIdentity
With that extension, the inferred type for the definition is
add :: (Num t1, Num t, Monad m)
=> (t, t1) -> (t, t1) -> m (t, t1)
and since
runIdentity :: Identity a -> a
using it forces m ~ Identity
and it just works: the derived type is
(Num t1, Num t, Monad m)
=> (t, t1) -> (t, t1) -> m (t, t1)
Identity a -> a
--------------------------------------------
m ~ Identity , Monad Identity
(t,t1) ~ a
--------------------------------------------
(Num t1, Num t)
=> (t, t1) -> (t, t1) -> (t, t1)
which matches your given type signature
(Int, Int) -> (Int, Int) -> (Int, Int)
since Int
is in Num
,
and Identity
is indeed a monad, one that does nothing at all,
newtype Identity a = Identity {runIdentity :: a}
fmap f (Identity a) = Identity (f a)
join (Identity (Identity a)) = Identity a
except tagging the values with its tag, which even disappears right away because the type Identity a
is defined as newtype
, not data
.
Upvotes: 0
Reputation: 6828
What you are doing is not correct. List comprehensions are not the right way to do this.
Using pattern matching to extract the elements of the tuples:
add :: (Int, Int) -> (Int, Int) -> (Int, Int)
add (x, y) (u, v) = (x+u, y+v)
Extracting the elements of the tuples using fst
and snd
:
add2 :: (Int, Int) -> (Int, Int) -> (Int, Int)
add2 x y = (fst x + fst y, snd x + snd y)
Also keep in mind that functions can't start with capital letters in Haskell.
Upvotes: 7
Reputation: 28500
About your attempt, try running it in ghci
and you'll see an error. As to why, that syntax you're trying to use is know as list comprehension, and it is documented here; it is syntactic surgar to create lists, such as [1,2,3]
, so it's not the right tool for you, as the ability to sum to pairs, which have type (·,·)
, not [·]
(where by ·
I mean "any type").
Below is a non-basic (and probably overkill) way to write the function you want. But setting the target of understand it could be a way to force yourself going deeper in Haskell.
Here it is:
import Data.Bifunctor (bimap)
import Data.Tuple.Extra (both)
sumTwoTuples x y = uncurry bimap (both (+) x) y
How does this work? Let's see
> :t both
both :: (a -> b) -> (a, a) -> (b, b)
So both
takes a function and applies it to both elements of a pair; therefore both (+)
will apply (+)
to both sides of the first pair x
; if that's (3,4)
, you'll get ((3+), (4+))
(yeah, I'd write it as (3+,4+)
, but that's illegal syntax).
Now we have this pair of functions both (+) x
, and we want to apply each of them to one side of the pair y
.
Here's bimap
:
> :t bimap
bimap :: Bifunctor p => (a -> b) -> (c -> d) -> p a c -> p b d
So it takes 2 functions and applies it to each side of a Bifunctor
(in our case the Bifunctor
type p
is (,)
).
It's almost what we need, but it takes the two functions as two separate arguments, not a pair containing them.
uncurry
gives a way to adjust that:
> :t uncurry
uncurry :: (a -> b -> c) -> (a, b) -> c
Indeed, uncurry bimap
has this type:
> :t uncurry bimap
uncurry bimap :: Bifunctor p => (a -> b, c -> d) -> p a c -> p b d
so it takes a pair of functions and applies each to the corresponding side of the pair y
, which has type p b d
with p
being (,)
in our case.
Upvotes: 0