pair (f,g) x = (f x, g x)?

I came across a haskell function on a book defined as following: pair :: (a -> b,a -> c) -> a -> (b,c) pair (f,g) x = (f x,g x) I thought x would only math a single argument like 'a', 1, etc....,but it turned out that it would match something else, for example, a pair as below: square x = x*x pair (square.fst,Char.toUpper.snd) (2,'a') (4,'A') The type declaration of pair is what confused me, pair :: (a -> b,a -> c) -> a -> (b,c),it says this function will take a pair of functions which have types of a->b,a->c,which I would take as these two functions must have argument of the same type, which is a,and I didn't think it would work on pairs as in the above instance,but surprisingly it did,can anybody enlighten me? -- X.W.D

'.' is not always a namespace-separator like '::','.','->' in c++ or '.' in java. it is used as an operator, too. (.) :: (b->c) -> (a->b) -> (a->c) (f . g) x = f (g x) remember the types of fst and snd: fst :: (a,b)->a snd :: (a,b)->b so the function (.) combines square :: Int -> Int with fst to (square . fst) :: (Int,b) -> Int the same with toUpper: (Char.toUpper . snd) :: (a,Char) -> Char so you have with 'pair (f,g) x = (f x,g x)': pair (square . fst,Char.toUpper . snd) (2,'a') ==> ((square . fst) (2,'a'), (Char.toUpper . snd) (2,'a')) ==> ( square (fst(2,'a')), Char.toUpper (snd(2,'a')) ) ==> ( square 2 , Char.toUpper 'a' ) ==> (4,'A') - marc Am Samstag, 2. Juli 2005 08:32 schrieb wenduan:
I came across a haskell function on a book defined as following:
pair :: (a -> b,a -> c) -> a -> (b,c) pair (f,g) x = (f x,g x)
I thought x would only math a single argument like 'a', 1, etc....,but it turned out that it would match something else, for example, a pair as below:
square x = x*x
pair (square.fst,Char.toUpper.snd) (2,'a') (4,'A')
The type declaration of pair is what confused me, pair :: (a -> b,a -> c) -> a -> (b,c),it says this function will take a pair of functions which have types of a->b,a->c,which I would take as these two functions must have argument of the same type, which is a,and I didn't think it would work on pairs as in the above instance,but surprisingly it did,can anybody enlighten me?
-- X.W.D
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Marc A. Ziegert wrote:
'.' is not always a namespace-separator like '::','.','->' in c++ or '.' in java. it is used as an operator, too. (.) :: (b->c) -> (a->b) -> (a->c) (f . g) x = f (g x)
remember the types of fst and snd: fst :: (a,b)->a snd :: (a,b)->b so the function (.) combines square :: Int -> Int with fst to (square . fst) :: (Int,b) -> Int
the same with toUpper: (Char.toUpper . snd) :: (a,Char) -> Char
so you have with 'pair (f,g) x = (f x,g x)':
pair (square . fst,Char.toUpper . snd) (2,'a') ==> ((square . fst) (2,'a'), (Char.toUpper . snd) (2,'a')) ==> ( square (fst(2,'a')), Char.toUpper (snd(2,'a')) ) ==> ( square 2 , Char.toUpper 'a' ) ==> (4,'A')
- marc
Am Samstag, 2. Juli 2005 08:32 schrieb wenduan:
I came across a haskell function on a book defined as following:
pair :: (a -> b,a -> c) -> a -> (b,c) pair (f,g) x = (f x,g x)
I thought x would only math a single argument like 'a', 1, etc....,but it turned out that it would match something else, for example, a pair as below:
square x = x*x
pair (square.fst,Char.toUpper.snd) (2,'a') (4,'A')
The type declaration of pair is what confused me, pair :: (a -> b,a -> c) -> a -> (b,c),it says this function will take a pair of functions which have types of a->b,a->c,which I would take as these two functions must have argument of the same type, which is a,and I didn't think it would work on pairs as in the above instance,but surprisingly it did,can anybody enlighten me?
-- X.W.D
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
you are correct,but as in the following,
(square . fst) :: (Int,b) -> Int
(Char.toUpper . snd) :: (a,Char) -> Char
you get a Int and Char out of the two composed functions, namely square.fst, Char.toUpper.snd.But in the type declaration of pair, which appeared to me,it meant its arguments must be two functions which are of the same type namely a,whereas Int and Char passed to as arguments are of different types here, and that's the reason I thought it wouldn't work. Thank you, regards. -- X.W.D

you are correct,but as in the following,
(square . fst) :: (Int,b) -> Int
(Char.toUpper . snd) :: (a,Char) -> Char
you get a Int and Char out of the two composed functions, namely square.fst, Char.toUpper.snd.But in the type declaration of pair, which appeared to me,it meant its arguments must be two functions which are of the same type namely a,whereas Int and Char passed to as arguments are of different types here, and that's the reason I thought it wouldn't work.
The signature says it takes two functions, which take the same type to *different* types ((a->b), (a->c)). In your case, 'a' is guaranteed the same type because you're applying it to the same value (in this case its type is (Int, Char)). So you are not passing Int or Char but (Int, Char) to 'fst' and 'snd'. The Int -> Int and Char -> Char functions never see the type they don't understand because the selectors 'fst' and 'snd' have stripped those values off.

Wenduan,
you get a Int and Char out of the two composed functions, namely square.fst, Char.toUpper.snd.But in the type declaration of pair, which appeared to me,it meant its arguments must be two functions which are of the same type namely a,whereas Int and Char passed to as arguments are of different types here, and that's the reason I thought it wouldn't work.
Well, actually the two argument functions are not required to be of exactly the same type. The only restriction is that the types of their parameters match: pair :: (a -> b) -> (a -> c) -> a -> (b, c) So, in pair (square . fst) (toUpper . snd) a matches the type of the parameters of (square . fst) and (toUpper . snd), i.e., (Int, Char), b matches the result type of (square . fst), i.e., Int, and c matches the result type of (toUpper . snd), i.e., Char; so the type of pair get instantiated with ((Int, Char) -> Int) -> ((Int, Char) -> Char) -> (Int, Char) -> (Int, Char) You might also want to use (***) :: (a -> c) -> (b -> d) -> (a, b) -> (c, d) (f *** g) (a, b) = (f a, g b) HTH, Stefan
participants (4)
-
Evan Laforge
-
Marc A. Ziegert
-
Stefan Holdermans
-
wenduan