Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Cale Gibbard
On 24/11/05, [EMAIL PROTECTED]
<[EMAIL PROTECTED]> wrote:
> Cale Gibbard:
>
> > x f does perhaps make more sense, especially with the current
> > categorical view of functions, but there would have to be a really
> > hugely good reason to change notation, as almost all current work puts
> > things the other way around.
>
> "Almost all"?
> Well, excluding the Smalltalkers, people using Forth, PostScript, etc.
>
Perhaps I should have qualified that: I meant in pure mathematics.
 - Cale
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread jerzy . karczmarczuk
Cale Gibbard: 


x f does perhaps make more sense, especially with the current
categorical view of functions, but there would have to be a really
hugely good reason to change notation, as almost all current work puts
things the other way around.


"Almost all"?
Well, excluding the Smalltalkers, people using Forth, PostScript, etc. 



Jerzy Karczmarczuk 



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


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Bill Wood
On Wed, 2005-11-23 at 21:21 -0500, Cale Gibbard wrote:
   . . .
> Hmm, which edition? My copy (5th ed.) uses the ordinary notation: f(x).
> 
> x f does perhaps make more sense, especially with the current
> categorical view of functions, but there would have to be a really
> hugely good reason to change notation, as almost all current work puts
> things the other way around.

My copy reads
   First published 1997 by
   Prentice Hall Europe
   (Address lines)
   Copyright Prentice Hall Europe 1997
   ...
   ISBN 0-13-507245-X

It's hardcover, white cover with red around the spine (standard for this
series edited by C.A.R. Hoare), black banner with "100th title" in red.
The lack of any edition information leads me to surmise it's a first
edition.

Do you (or anyone) know if the "diagrammatic notation" has any currency
among algebraists?

 -- Bill Wood


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


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Cale Gibbard
On 23/11/05, Scherrer, Chad <[EMAIL PROTECTED]> wrote:
> Bill Wood <[EMAIL PROTECTED]> writes:
>
> > Interesting note: in Richard Bird and Oege de Moor, _Algebra
> > of Programming_, pp. 2-3, the authors write
> >
> >As a departure from tradition, we write "f : A <- B" rather than
> >"f : B -> A" to indicate the source and target types associated
> >with a function "f". ... The reason for this choice has to do with
> >functional composition, whose definition now takes the smooth
> >form: if f : A <- B and g : B <- C, then f . g : A <- C is defined
> >by (f . g) x = f(g x).
> >
> > Further along the same paragraph they write:
> >
> >In the alternative, so-called diagrammatic forms, one writes
> >"x f" for application and "f ; g" for composition, where
> >x (f ; g) = (x f) g.
> >
> > I know I've read about the latter notation as one used by
> > some algebraists, but I can't put my hands on a source right now.
> >
> > I guess it's not even entirely clear what constitutes
> > "mathematical notation". :-)
> >
> >  -- Bill Wood
>
> Good point. One of my undergrad algebra books ("Contemporary Abstract
> Algebra", by Gallian) actually used notation like this. Function
> application was written (x f). Some people even write the function as an
> exponential. But (f x) is still far more common.

Hmm, which edition? My copy (5th ed.) uses the ordinary notation: f(x).

x f does perhaps make more sense, especially with the current
categorical view of functions, but there would have to be a really
hugely good reason to change notation, as almost all current work puts
things the other way around.

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


RE: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Scherrer, Chad
Bill Wood <[EMAIL PROTECTED]> writes:

> Interesting note: in Richard Bird and Oege de Moor, _Algebra 
> of Programming_, pp. 2-3, the authors write
> 
>As a departure from tradition, we write "f : A <- B" rather than
>"f : B -> A" to indicate the source and target types associated
>with a function "f". ... The reason for this choice has to do with
>functional composition, whose definition now takes the smooth
>form: if f : A <- B and g : B <- C, then f . g : A <- C is defined
>by (f . g) x = f(g x).
> 
> Further along the same paragraph they write:
> 
>In the alternative, so-called diagrammatic forms, one writes
>"x f" for application and "f ; g" for composition, where
>x (f ; g) = (x f) g.
> 
> I know I've read about the latter notation as one used by 
> some algebraists, but I can't put my hands on a source right now.
> 
> I guess it's not even entirely clear what constitutes 
> "mathematical notation". :-)
> 
>  -- Bill Wood

Good point. One of my undergrad algebra books ("Contemporary Abstract
Algebra", by Gallian) actually used notation like this. Function
application was written (x f). Some people even write the function as an
exponential. But (f x) is still far more common.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

"Time flies like an arrow; fruit flies like a banana." -- Groucho Marx 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Bill Wood
On Wed, 2005-11-23 at 17:47 +0100, Henning Thielemann wrote:
   . . .
>   Why is there no (<<) and why is (=<<) not the default? The order of 'do 
> {a;b;c}' is compatible with that of (>>). So we have the fundamental 
> conflict, that usually function application is from right to left, but 
> interpreting imperative statements is from left to right.
>   I think that's a similar conflict like that of little endian and big 
> endian.

There may be something to your functional/imperative conflict.

I had occasion to develop a computational model of a theoretical
state-transition machine that the inventors wanted to be able to
program.  My model used the standard trick of construing a parameterized
operation as a function f : Arg1 -> ... -> Argn -> State -> State.  By
writing the (ML) code for the instructions in the curried form and using
a reversed composition operator, I was able to provide a programmatic
interface which could be laid out one instruction per line with the
composition operators way off to the right in the comment column, just
like assembler code!  The inventors thought this was just wonderful
(there's no accounting for taste, I guess :-).

 -- Bill Wood


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


RE: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Bill Wood
On Wed, 2005-11-23 at 08:55 -0800, Scherrer, Chad wrote:
   . . .
> I see. I like the argument order also, since it so nicely reflects
> mathematical notation. But I do think there's a place for (flip ($)) and
> (flip (.)). The problem is that the assignment of fixities is much more
> subtle and requires a consideration of what should be considered "proper
> style".

Interesting note: in Richard Bird and Oege de Moor, _Algebra of
Programming_, pp. 2-3, the authors write

   As a departure from tradition, we write "f : A <- B" rather than
   "f : B -> A" to indicate the source and target types associated
   with a function "f". ... The reason for this choice has to do with
   functional composition, whose definition now takes the smooth
   form: if f : A <- B and g : B <- C, then f . g : A <- C is defined
   by (f . g) x = f(g x).

Further along the same paragraph they write:

   In the alternative, so-called diagrammatic forms, one writes
   "x f" for application and "f ; g" for composition, where
   x (f ; g) = (x f) g.

I know I've read about the latter notation as one used by some
algebraists, but I can't put my hands on a source right now.

I guess it's not even entirely clear what constitutes "mathematical
notation". :-)

 -- Bill Wood


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


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Tomasz Zielonka
On Wed, Nov 23, 2005 at 09:01:07AM -0800, Scherrer, Chad wrote:
> So I think of the types as being 
> grep "." *.hs :: String
> wc :: String -> Int  -- ok, not really, but it shows the point better.

Every unix program has a standard input, even if it doesn't use it, so
I would rather give this type to grep "." *.hs:

grep "." *.hs :: a -> String

You can run something like this

p | echo bla | grep "." *.hs | wc

even if it seems non-sensical.

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


RE: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Scherrer, Chad
Udo Stenzel <[EMAIL PROTECTED]> writes:

> The unix pipe is actually function composition.  Its argument 
> (standard
> input) isn't explicitly mentioned

Then it seems Unix must overload the "|" operator. I typically use it to
do things like
grep "." *.hs | wc

So I think of the types as being 
grep "." *.hs :: String
wc :: String -> Int  -- ok, not really, but it shows the point better.

So we'd have to have 
(|) :: a -> (a -> b) -> b

And (flip ($)) is the only thing that makes sense. Is it the case that a
Unix pipe is analagous to (flip ($)) or (flip (.)) depending on the
context?

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

"Time flies like an arrow; fruit flies like a banana." -- Groucho Marx 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Scherrer, Chad
Henning Thielemann <[EMAIL PROTECTED]> writes:

>   I want to say, that the order of symbols for ($), (.) and 
> function application is consistent. This is a fine thing. I 
> think that shall not be distroyed by giving ($) and (.) 
> reversed argument order.

I see. I like the argument order also, since it so nicely reflects
mathematical notation. But I do think there's a place for (flip ($)) and
(flip (.)). The problem is that the assignment of fixities is much more
subtle and requires a consideration of what should be considered "proper
style".

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

"Time flies like an arrow; fruit flies like a banana." -- Groucho Marx 

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


RE: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Henning Thielemann


On Wed, 23 Nov 2005, Scherrer, Chad wrote:


Henning Thielemann <[EMAIL PROTECTED]> writes:


Since
  (a . b) x
  a $ b x
  a (b x)

are equivalent, do you also want to reverse function and
argument in order to match argument order of . and $ ?

That is
  x (b . a)
  x b $ a
  (x b) a
?


I'm sorry, I'm not sure I understand your question. Are you asking
whether one should be allowed to write x f instead of f x? I don't think
anyone is advocating this, but is can be convenient to have an infix
operator for this purpose.


 I want to say, that the order of symbols for ($), (.) and function 
application is consistent. This is a fine thing. I think that shall not be 
distroyed by giving ($) and (.) reversed argument order.


 It's of course a good question, why (>>) and (>>=) have the opposite 
order of (.). Compare function application

 a b
  where a is applied to b with the monadic case
 b >>= a
  where a is applied to the result of b. This makes changing a non-monadic 
expression to a similar monadic expression more difficult.
 Why is there no (<<) and why is (=<<) not the default? The order of 'do 
{a;b;c}' is compatible with that of (>>). So we have the fundamental 
conflict, that usually function application is from right to left, but 
interpreting imperative statements is from left to right.
 I think that's a similar conflict like that of little endian and big 
endian.

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


RE: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Scherrer, Chad
Henning Thielemann <[EMAIL PROTECTED]> writes:

> Since
>   (a . b) x
>   a $ b x
>   a (b x)
> 
> are equivalent, do you also want to reverse function and 
> argument in order to match argument order of . and $ ?
> 
> That is
>   x (b . a)
>   x b $ a
>   (x b) a
> ?

I'm sorry, I'm not sure I understand your question. Are you asking
whether one should be allowed to write x f instead of f x? I don't think
anyone is advocating this, but is can be convenient to have an infix
operator for this purpose.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

"Time flies like an arrow; fruit flies like a banana." -- Groucho Marx 

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


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Henning Thielemann


On Wed, 23 Nov 2005, Udo Stenzel wrote:


Scherrer, Chad wrote:

Maybe my point wasn't clear. Of course this idea of comparing lazy
evaluation to Unix pipes is very old (long before July 2004, I'm sure).
The point I'm making is that there is an old idea that may be underused.


It is, and only because (.) is defined all wrong!


Since
 (a . b) x
 a $ b x
 a (b x)

are equivalent, do you also want to reverse function and argument in order 
to match argument order of . and $ ?


That is
 x (b . a)
 x b $ a
 (x b) a
?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Tomasz Zielonka
On Wed, Nov 23, 2005 at 11:17:25AM +0100, Udo Stenzel wrote:
> infixl 2 \|
> (\|)  = flip (.) -- though I'm using (&)
> 
> The unix pipe becomes (filter ("foo" `isPrefixOf`) \| sort \| nub) or
> something, which is rather neat, and (#) is used to call "member
> functions", as in

Why not use Control.Arrow.>>> ?
The instance for (->) is exactly what you want, and the syntax is quite
nice:

(filter ("foo" `isPrefixOf`) >>> sort >>> nub)

BTW, using sort before nub is a bit pointless. In fact, using nub for
longer lists is a bad idea.

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


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Udo Stenzel
Scherrer, Chad wrote:
> Maybe my point wasn't clear. Of course this idea of comparing lazy
> evaluation to Unix pipes is very old (long before July 2004, I'm sure).
> The point I'm making is that there is an old idea that may be underused.

It is, and only because (.) is defined all wrong!

The unix pipe is actually function composition.  Its argument (standard
input) isn't explicitly mentioned, so the analogous Haskell code should
do the same.  However, function composition reads backwards, which makes
code quite unreadable, especially when (.), (>>=) and `liftM` (which
also has an all wrong fixity) are mixed.

Im summary, I'd define

infixl 0 #
infixl 1 >>#
infixl 2 \|
(#)   = flip ($)
(>>#) = flip liftM
(\|)  = flip (.) -- though I'm using (&)

The unix pipe becomes (filter ("foo" `isPrefixOf`) \| sort \| nub) or
something, which is rather neat, and (#) is used to call "member
functions", as in

some_map # add key value
 # add something or_other
 # delete old_trash

which actually gives the result one expects when reading it top to bottom.
In summary, (.) is tremendously useful, but it would be even better if
it had the correct argument order.  Unfortunately, this cannot be
corrected any more.


Udo.
-- 
"God is real, unless declared as an Integer." - Unknown Source


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


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 02:09:40PM -0800, Scherrer, Chad wrote:
> (\|) = flip ($) -- (#) seems to me too pretty for other purposes to use
> it here.
> infixl 0 \| -- Again, why can't this be negative or Fractional??

I have a ? operator that does the same thing. Next time I use it I'll
check if \| looks better.

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


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-22 Thread Scherrer, Chad
"Albert Lai" <[EMAIL PROTECTED]> writes:

> I offer a simpler, more direct, and pre-existing correspondence
between a functional 
> programming construct and unix pipes:

Maybe my point wasn't clear. Of course this idea of comparing lazy
evaluation to Unix pipes is very old (long before July 2004, I'm sure).
The point I'm making is that there is an old idea that may be underused.
We use ($) all over the place, but if there are a lot of them (and
especially if they are spread over several lines) it becomes awkward to
read the whole thing backward to trace through the function from
beginning to end. In these cases, it's much simpler to use 

(\|) = flip ($) -- (#) seems to me too pretty for other purposes to use
it here.
infixl 0 \| -- Again, why can't this be negative or Fractional??

What I'm asking is really a question of pedagogy and style. This style
seems reasonable to me. OTOH, there are some reasons not to do things in
this way. Maybe any function big enough to benefit from writing it this
way should be broken up anyway. Or maybe getting used to this style
where the laziness is right in your face could make it more difficult
for people to learn to reason through less obvious laziness. I'm really
trying to figure out whether this approach is worth pursuing, rather
than imply that this is a completely original idea.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

"Time flies like an arrow; fruit flies like a banana." -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-21 Thread Albert Lai
I offer a simpler, more direct, and pre-existing correspondence
between a functional programming construct and unix pipes:

  http://www.vex.net/~trebla/weblog/pointfree.html

"Scherrer, Chad" <[EMAIL PROTECTED]> writes:

> I'm still trying to settle on a "feel" for good programming style in
> Haskell. One thing I've been making some use of lately is
> 
> (\|) = flip ($)
> infixl 0 \|
> 
> Then expressions like
> 
> f4 $ f3 $ f2 $ f1 $ x
> 
> become
> 
> x  \|
> f1 \|
> f2 \|
> f3 \|
> f4
> 
> I've seen something like this on haWiki using (#), but I prefer this
> notation because it looks like a Unix pipe, which is exactly how it's
> used. 

[...]

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