Re: [Haskell-cafe] Re: Very crazy

2007-09-26 Thread Steven Fodstad
Andrew Coppin wrote:
 Chaddaï Fouché wrote:
 2007/9/25, Andrew Coppin [EMAIL PROTECTED]:
  
 This is why I found it so surprising - and annoying - that you can't
 use
 a 2-argument function in a point-free expression.

 For example, zipWith (*) expects two arguments, and yet

   sum . zipWith (*)

 fails to type-check. You just instead write

   \xs ys - sum $ zipWith(*) xs ys

 

 (sum . zipWith (*)) xs ys
 == (sum (zipWith (*) xs)) ys

 so you try to apply sum :: [a] - Int to a function (zipWith (*) xs)
 :: [a] - [b], it can't work !

 (sum.) . zipWith (*)
 works, but isn't the most pretty expression I have seen.
   

 I'm still puzzled as to why this breaks with my example, but works
 perfectly with other people's examples...

 So you're saying that

  (f3 . f2 . f1) x y z == f3 (f2 (f1 x) y) z

 ? In that case, that would mean that

  (map . map) f xss == map (map f) xss

 which *just happens* to be what we want. But in the general case where
 you want

  f3 (f2 (f1 x y z))

 there's nothing you can do except leave point-free.
Well, there's one thing.  You can change your three argument function
into a one argument function of a 3-tuple, and then change the composed
function back again:

let uncurry3 = \f (x,y,z) - f x y z
curry3 = \f x y z - f (x,y,z)
in curry3 $ f3 . f2 . uncurry3 f1

In your earlier example, this would have been:
curry $ sum . uncurry (zipWith (*))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-26 Thread Derek Elkins
On Wed, 2007-09-26 at 18:50 -0400, Steven Fodstad wrote:
 Andrew Coppin wrote:
  Chaddaï Fouché wrote:
  2007/9/25, Andrew Coppin [EMAIL PROTECTED]:
   
  This is why I found it so surprising - and annoying - that you can't
  use
  a 2-argument function in a point-free expression.
 
  For example, zipWith (*) expects two arguments, and yet
 
sum . zipWith (*)
 
  fails to type-check. You just instead write
 
\xs ys - sum $ zipWith(*) xs ys
 
  
 
  (sum . zipWith (*)) xs ys
  == (sum (zipWith (*) xs)) ys
 
  so you try to apply sum :: [a] - Int to a function (zipWith (*) xs)
  :: [a] - [b], it can't work !
 
  (sum.) . zipWith (*)
  works, but isn't the most pretty expression I have seen.

 
  I'm still puzzled as to why this breaks with my example, but works
  perfectly with other people's examples...
 
  So you're saying that
 
   (f3 . f2 . f1) x y z == f3 (f2 (f1 x) y) z
 
  ? In that case, that would mean that
 
   (map . map) f xss == map (map f) xss
 
  which *just happens* to be what we want. But in the general case where
  you want
 
   f3 (f2 (f1 x y z))
 
  there's nothing you can do except leave point-free.
 Well, there's one thing.  You can change your three argument function
 into a one argument function of a 3-tuple, and then change the composed
 function back again:
 
 let uncurry3 = \f (x,y,z) - f x y z
 curry3 = \f x y z - f (x,y,z)
 in curry3 $ f3 . f2 . uncurry3 f1
 
 In your earlier example, this would have been:
 curry $ sum . uncurry (zipWith (*))

As a side note, this is essentially how all higher order functions are
handled in category theory (well, in cartesian closed categories.)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:
 BTW, one *extremely* common function that I've never seen mentioned 
 anywhere is this one:

   map2 :: (a - b) - [[a]] - [[b]]
   map2 f = map (map f)

Because someone would have to think of a name for it, when (map . map)
is likely to be clearer.

-- 
Aaron Denney
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Andrew Coppin

Aaron Denney wrote:

On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:
  
BTW, one *extremely* common function that I've never seen mentioned 
anywhere is this one:


  map2 :: (a - b) - [[a]] - [[b]]
  map2 f = map (map f)



Because someone would have to think of a name for it, when (map . map)
is likely to be clearer.
  


OK, *now* I'm puzzled... Why does map . map type-check?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:
 Aaron Denney wrote:
 On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:
   
 BTW, one *extremely* common function that I've never seen mentioned 
 anywhere is this one:

   map2 :: (a - b) - [[a]] - [[b]]
   map2 f = map (map f)
 

 Because someone would have to think of a name for it, when (map . map)
 is likely to be clearer.
   

 OK, *now* I'm puzzled... Why does map . map type-check?

(map . map) = (.) map map

(.) :: (a - b) - (b - c) - a - c
= (a - b) - (b - c) - (a - c)

The first two arguments of (.) are 1-argument functions.

map :: (d - e) - [d] - [e]
=  (d - e) - ([d] - [e])

map is either a two argument function _or_ a function that takes one
argument (a function) and returns a function.

In this latter view, for the first argument, of (.), we need:

a = d - e
b = [d] - [e]

And for the second we know
b = [d] - [e]
so 
c = [[d]] - [[e]]

for everything to be consistent.  

It's much clearer when you think of map not as running this function
over this list, but rather turning this function that operates on
elements into a function that operates on lists.  Doing that twice (by
composing) turns a function that operates on elements into a function
that operates on lists of lists.

-- 
Aaron Denney
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Andrew Coppin

Aaron Denney wrote:

On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:
  

OK, *now* I'm puzzled... Why does map . map type-check?



(map . map) = (.) map map

(.) :: (a - b) - (b - c) - a - c
= (a - b) - (b - c) - (a - c)

The first two arguments of (.) are 1-argument functions.

map :: (d - e) - [d] - [e]
=  (d - e) - ([d] - [e])

map is either a two argument function _or_ a function that takes one
argument (a function) and returns a function.

In this latter view, for the first argument, of (.), we need:

a = d - e
b = [d] - [e]

And for the second we know
b = [d] - [e]
so 
c = [[d]] - [[e]]


for everything to be consistent.  


It's much clearer when you think of map not as running this function
over this list, but rather turning this function that operates on
elements into a function that operates on lists.  Doing that twice (by
composing) turns a function that operates on elements into a function
that operates on lists of lists.
  


I just found it rather surprising. Every time *I* try to compose with 
functions of more than 1 argument, the type checker complains. 
Specifically, suppose you have


 foo = f3 . f2 . f1

Assuming those are all 1-argument functions, it works great. But if f1 
is a *two* argument function (like map is), the type checker refuses to 
allow it, and I have to rewrite it as


 foo x y = f3 $ f2 $ f1 x y

which is really extremely annoying...

I'm just curiose as to why the type checker won't let *me* do it, but it 
will let *you* do it. (Maybe it hates me?)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:
 I just found it rather surprising. Every time *I* try to compose with 
 functions of more than 1 argument, the type checker complains. 
 Specifically, suppose you have

   foo = f3 . f2 . f1

 Assuming those are all 1-argument functions, it works great. But if f1 
 is a *two* argument function (like map is), the type checker refuses to 
 allow it, and I have to rewrite it as

   foo x y = f3 $ f2 $ f1 x y

 which is really extremely annoying...

 I'm just curiose as to why the type checker won't let *me* do it, but it 
 will let *you* do it. (Maybe it hates me?)

Don't anthropomorphize computers.  They hate it when you do that.

I'm guessing the problem is probably incorrect parenthesizing.

foo x y = f3 . f2 . f1 x y

won't typecheck, but 

foo x y = (f3 . f2 . f1) x y

should.  

Function application is the highest precedence, so 
the first definition is parsed as 

foo x y = f3 . f2 . (f1 x y)

which will only type-check if f1 has 3 or more arguments, as (f1 x y)
must be a function.

The trickier parts are more than 1 argument functions as the first
argument to (.).  Are you sure your failed attempts weren't of this
form?

-- 
Aaron Denney
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Andrew Coppin

Chaddaï Fouché wrote:

2007/9/25, Andrew Coppin [EMAIL PROTECTED]:

  

I just found it rather surprising. Every time *I* try to compose with
functions of more than 1 argument, the type checker complains.



There is no function that takes more than one argument in Haskell. ;-)
map _could_ be seen as a function with 2 arguments, but in this case
it's more useful to think of it as a function that take one argument
f, a function that turn 'a into 'b and turn it into a new function
that turn a list of 'a into a list of 'b.
  


This is why I found it so surprising - and annoying - that you can't use 
a 2-argument function in a point-free expression.


For example, zipWith (*) expects two arguments, and yet

 sum . zipWith (*)

fails to type-check. You just instead write

 \xs ys - sum $ zipWith(*) xs ys

which works as expected.

I can't figure out why map . map works, but sum . zipWith (*) doesn't 
work. As I say, the only reason I can see is that the type checker hates 
me and wants to force me to write everything the long way round...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Very crazy

2007-09-25 Thread jerzy . karczmarczuk
Andrew Coppin writes: 

...I found it so surprising - and annoying - that you can't use a 
2-argument function in a point-free expression. 
For example, zipWith (*) expects two arguments, and yet 

 sum . zipWith (*) 
fails to type-check. You just instead write 

 \xs ys - sum $ zipWith(*) xs ys 

which works as expected. 

I can't figure out why map . map works, but sum . zipWith (*) doesn't 
work. As I say, the only reason I can see is that the type checker hates 
me and wants to force me to write everything the long way round...


I suspect that it is you who hates the Haskell type-checker, forcing it
to work on expressions which go against the rules: precedence, and
normal order.
The transformation to combinators is doable, but one has to be careful.
Let's see: 


res p q = sum (zipWith (*) p q) = (sum . (zipWith (*) p)) q
res p = (sum .) (zipWith (*) p) = ((sum .) . (zipWith (*)) p 

res = (sum .) . (zipWith (*)) 


Certainly it is a kind of madness, since is hardly readable, but it
is correct. 

Jerzy Karczmarczuk 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Andrew Coppin

Chaddaï Fouché wrote:

2007/9/25, Andrew Coppin [EMAIL PROTECTED]:
  

This is why I found it so surprising - and annoying - that you can't use
a 2-argument function in a point-free expression.

For example, zipWith (*) expects two arguments, and yet

  sum . zipWith (*)

fails to type-check. You just instead write

  \xs ys - sum $ zipWith(*) xs ys




(sum . zipWith (*)) xs ys
== (sum (zipWith (*) xs)) ys

so you try to apply sum :: [a] - Int to a function (zipWith (*) xs)
:: [a] - [b], it can't work !

(sum.) . zipWith (*)
works, but isn't the most pretty expression I have seen.
  


I'm still puzzled as to why this breaks with my example, but works 
perfectly with other people's examples...


So you're saying that

 (f3 . f2 . f1) x y z == f3 (f2 (f1 x) y) z

? In that case, that would mean that

 (map . map) f xss == map (map f) xss

which *just happens* to be what we want. But in the general case where 
you want


 f3 (f2 (f1 x y z))

there's nothing you can do except leave point-free.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Dominic Steinitz
Andrew Coppin andrewcoppin at btinternet.com writes:

 I just found it rather surprising. Every time *I* try to compose with 
 functions of more than 1 argument, the type checker complains. 
 Specifically, suppose you have
 
   foo = f3 . f2 . f1
 
 Assuming those are all 1-argument functions, it works great. But if f1 
 is a *two* argument function (like map is), the type checker refuses to 
 allow it, and I have to rewrite it as
 
   foo x y = f3 $ f2 $ f1 x y
 
Look at the type of (.).(.) which should tell you how to compose functions 
with more than one variable. Mind you, I don't think it improves readability.

Dominic.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Claus Reinke
This is why I found it so surprising - and annoying - that you can't use 
a 2-argument function in a point-free expression.


For example, zipWith (*) expects two arguments, and yet

 sum . zipWith (*)

fails to type-check. You just instead write

 \xs ys - sum $ zipWith(*) xs ys

which works as expected.


   Prelude :t \xs ys-sum $ zipWith (*) xs ys
   \xs ys-sum $ zipWith (*) xs ys :: (Num a) = [a] - [a] - a

   Prelude :t \xs-sum . zipWith (*) xs
   \xs-sum . zipWith (*) xs :: (Num a) = [a] - [a] - a

   Prelude :t (sum .) . zipWith (*)
   (sum .) . zipWith (*) :: (Num a) = [a] - [a] - a

   Prelude :t (\g-sum . g) . zipWith (*)
   (\g-sum . g) . zipWith (*) :: (Num a) = [a] - [a] - a

(.) composes single-parameter functions, so in (f . g) x y,
g only gets the first parameter, x. but by adding further
levels of composition to f, we can let g consume more 
parameters.


claus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Martin Lütke

Dominic Steinitz schrieb:

Andrew Coppin andrewcoppin at btinternet.com writes:

  
I just found it rather surprising. Every time *I* try to compose with 
functions of more than 1 argument, the type checker complains. 
Specifically, suppose you have


  foo = f3 . f2 . f1

Assuming those are all 1-argument functions, it works great. But if f1 
is a *two* argument function (like map is), the type checker refuses to 
allow it, and I have to rewrite it as


  foo x y = f3 $ f2 $ f1 x y


Look at the type of (.).(.) which should tell you how to compose functions 
with more than one variable. Mind you, I don't think it improves readability.


Dominic.
  
Interesting function. It got a sibling: (.)(.) :: (a1 - b - c) - a1 
- (a - b) - a - c


Anybody knows how to intepret that? I tried to call it with (++) t 
(++s) it but suddenly got distracted.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH


On Sep 25, 2007, at 6:55 , Andrew Coppin wrote:

This is why I found it so surprising - and annoying - that you  
can't use a 2-argument function in a point-free expression.


You can, it just requires more juggling.  Play around with  
lambdabot's @pl for a bit.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Andrew Coppin

Martin Lütke wrote:

Dominic Steinitz schrieb:

Look at the type of (.).(.) which should tell you how to compose functions 
with more than one variable. Mind you, I don't think it improves readability.


Dominic.
  
Interesting function. It got a sibling: (.)(.) :: (a1 - b - c) - a1 
- (a - b) - a - c


Anybody knows how to intepret that? I tried to call it with (++) t 
(++s) it but suddenly got distracted.


All I know is that most of this stuff looks like ASCII art - and perhaps 
I need to see a doctor...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH


On Sep 25, 2007, at 7:24 , Andrew Coppin wrote:

which *just happens* to be what we want. But in the general case  
where you want


 f3 (f2 (f1 x y z))

there's nothing you can do except leave point-free.


You mean leave point-ful.

And the point-free version of that is (((f3 . f2) .) .) . f1

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Jonathan Cast
On Tue, 2007-09-25 at 11:40 +0100, Andrew Coppin wrote:
 Aaron Denney wrote:
  On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:

  OK, *now* I'm puzzled... Why does map . map type-check?
  
 
  (map . map) = (.) map map
 
  (.) :: (a - b) - (b - c) - a - c
  = (a - b) - (b - c) - (a - c)
 
  The first two arguments of (.) are 1-argument functions.
 
  map :: (d - e) - [d] - [e]
  =  (d - e) - ([d] - [e])
 
  map is either a two argument function _or_ a function that takes one
  argument (a function) and returns a function.
 
  In this latter view, for the first argument, of (.), we need:
 
  a = d - e
  b = [d] - [e]
 
  And for the second we know
  b = [d] - [e]
  so 
  c = [[d]] - [[e]]
 
  for everything to be consistent.  
 
  It's much clearer when you think of map not as running this function
  over this list, but rather turning this function that operates on
  elements into a function that operates on lists.  Doing that twice (by
  composing) turns a function that operates on elements into a function
  that operates on lists of lists.

 
 I just found it rather surprising. Every time *I* try to compose with 
 functions of more than 1 argument, the type checker complains. 
 Specifically, suppose you have
 
   foo = f3 . f2 . f1
 
 Assuming those are all 1-argument functions, it works great. But if f1 
 is a *two* argument function (like map is), the type checker refuses to 
 allow it, and I have to rewrite it as
 
   foo x y = f3 $ f2 $ f1 x y
 
 which is really extremely annoying...
 
 I'm just curiose as to why the type checker won't let *me* do it, but it 
 will let *you* do it. (Maybe it hates me?)

In f . g, if g takes two arguments, f has to take a function as the
first argument (because that's what g returns).

jcc


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Jonathan Cast
On Tue, 2007-09-25 at 12:24 +0100, Andrew Coppin wrote:
 Chaddaï Fouché wrote:
  2007/9/25, Andrew Coppin [EMAIL PROTECTED]:

  This is why I found it so surprising - and annoying - that you can't use
  a 2-argument function in a point-free expression.
 
  For example, zipWith (*) expects two arguments, and yet
 
sum . zipWith (*)
 
  fails to type-check. You just instead write
 
\xs ys - sum $ zipWith(*) xs ys
 
  
 
  (sum . zipWith (*)) xs ys
  == (sum (zipWith (*) xs)) ys
 
  so you try to apply sum :: [a] - Int to a function (zipWith (*) xs)
  :: [a] - [b], it can't work !
 
  (sum.) . zipWith (*)
  works, but isn't the most pretty expression I have seen.

 
 I'm still puzzled as to why this breaks with my example, but works 
 perfectly with other people's examples...
 
 So you're saying that
 
   (f3 . f2 . f1) x y z == f3 (f2 (f1 x) y) z
 
 ? In that case, that would mean that
 
   (map . map) f xss == map (map f) xss
 
 which *just happens* to be what we want. But in the general case where 
 you want
 
   f3 (f2 (f1 x y z))
 
 there's nothing you can do except leave point-free.

In effect, yes.  As many others have pointed out, you *can* do this
point-free (all of lambda calculus can be re-written using the functions

s f g x = f x (g x)
k x y = x
 
(1)), but it's not a good idea.  Good style in Haskell as in any other
language is a matter of taste, not rules.

jcc

(1) http://www.madore.org/~david/programs/unlambda/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Bulat Ziganshin
Hello Andrew,

Tuesday, September 25, 2007, 5:21:35 PM, you wrote:

 Interesting function. It got a sibling: (.)(.) :: (a1 - b - c) - a1
 - (a - b) - a - c

sexy function with sexy type :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Philippa Cowderoy [EMAIL PROTECTED] wrote:
 On Tue, 25 Sep 2007, Lennart Augustsson wrote:

 It's reasonably easy to read.
 But you could make it more readable.  Type signatures, naming the first
 lambda...
 

 It might be reasonable to define something like mapMatrix that happens to 
 be map . map, too. Along with at least a type synonym for matrices.

Yes, that's a good idea.  Because it lets you change from the often
annoying list-of-lists implementation to something more reasonable for
e.g. transpose, as recently mentioned.

 Name domain constructs rather than expecting people to reconstruct
 them from their implementations, in other words.

Right.  But a list-of-lists isn't a terribly specific domain construct.
When it's used without further semantics, I think map . map is the best
translation of intent.

-- 
Aaron Denney
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Derek Elkins
On Tue, 2007-09-25 at 12:24 +0100, Andrew Coppin wrote:
 Chaddaï Fouché wrote:
  2007/9/25, Andrew Coppin [EMAIL PROTECTED]:

  This is why I found it so surprising - and annoying - that you can't use
  a 2-argument function in a point-free expression.
 
  For example, zipWith (*) expects two arguments, and yet
 
sum . zipWith (*)
 
  fails to type-check. You just instead write
 
\xs ys - sum $ zipWith(*) xs ys
 
  
 
  (sum . zipWith (*)) xs ys
  == (sum (zipWith (*) xs)) ys
 
  so you try to apply sum :: [a] - Int to a function (zipWith (*) xs)
  :: [a] - [b], it can't work !
 
  (sum.) . zipWith (*)
  works, but isn't the most pretty expression I have seen.

 
 I'm still puzzled as to why this breaks with my example, but works 
 perfectly with other people's examples...
 
 So you're saying that
 
   (f3 . f2 . f1) x y z == f3 (f2 (f1 x) y) z
 
 ? In that case, that would mean that
 
   (map . map) f xss == map (map f) xss
 
 which *just happens* to be what we want. But in the general case where 
 you want

   f3 (f2 (f1 x y z))
 
 there's nothing you can do except leave point-free.

As people have pointed out, you can do this, and in fact, can -always-
do this, i.e. always write things point-free.  lambdabot's @pl
command, as mentioned elsewhere, is a constructive proof of this.
However, I'm composing this email to point out a historical fact:
Essentially, writing everything point-free was Haskell Curry's
research programme.  See the field of combinatory logic of which he is
one of the fathers.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread David Menendez
On 9/25/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 This is why I found it so surprising - and annoying - that you can't use
 a 2-argument function in a point-free expression.
[...]
 I can't figure out why map . map works, but sum . zipWith (*) doesn't
 work. As I say, the only reason I can see is that the type checker hates
 me and wants to force me to write everything the long way round...

I suspect you're getting confused by the way Haskell treats
multi-parameter functions. Specifically, as far as function
composition is concerned, all Haskell functions have one parameter.

It may help to fully parenthesize function applications.

For example,
\xs ys - sum (zipWith f xs ys)
is
\xs ys - sum (((zipWith f) xs) ys)

The rule is that you can replace f (g x) with (f . g) x. If you
apply that above, you get
\xs ys - (sum . ((zipWith f) xs)) ys
or
\xs - sum . zipWith f xs

Removing 'xs' takes a little more work, because it's nested more
deeply. We can rewrite the above as,

\xs - ((.) sum) ((zipWith f) xs)

Applying the rule f (g x) = (f . g) x gets us,

\xs - (((.) sum) . (zipWith f)) xs
or
((.) sum) . zipWith f
or
(sum .) . zipWith f

The reason map . map is acceptible is that you can write map (map f).

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe