Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-27 Thread Brian Hulley

Sam Hughes wrote:

Brian Hulley wrote:

... For example, with the prefix definition of a function with 
multiple clauses, the function name at the start of each clause is 
already lined up since it must appear at the margin of the current 
layout block ...


Or you could have everything be backwards, and use an editor that 
right aligns things.



   (a - b) - [a] - [b] ::  map
[] = [] _ map
x f : xs f map = (x:xs) f map



There is still a reversal here between the order of arguments in the 
type signature and the order in the clauses.


Henning Thielemann wrote:



Curried functions like

f :: a - b - c

suggest a swapped order of arguments for (-), since 'f' must be 
called this way


b a f

Maybe it should be

f :: c - b - a




Which would fix this reversal. However there are 2 other kinds of 
reversal with postfix notation:
1) Declarations start with a keyword followed by some content whereas 
function definitions start with the args followed by the function name
2) Special constructs like case or let have to start with the 
keyword (so the parser knows what kind of thing it is supposed to parse 
next and so that the editor knows how to highlight what the user is 
typing before the user has finished typing the whole construct), again 
making a reversal between built-in constructs and constructs you can 
define using higher order functions (eg consider if as a user-defined 
construct in a postfix language)


I've come to the conclusion that whereas postfix notation is extremely 
neat for simple stack-based languages like Forth and PostScript it would 
not play well with languages which have a structured syntax since 
structured syntax + left to right reading order implies each syntactic 
element must start with a head followed by content appropriate to that 
element, or else recursive descent parsing and/or as-you-type 
grammatical highlighting would be impossible, and therefore in terms of 
function application, the head must of course be the function itself 
hence Prefix is the only solution.


Jonathan's comparison to natural languages made me think of it this way:

   x `plus` y   ===  [Subject] [Verb] [Object]

   x .plus(y) === [Subject] [Verb Object]

   plus y x === [Verb Object] [Subject]

   plus x y === [Verb Subject] [Object]

which illustrates why infix notation feels natural (corresponds to SVO 
in English etc), why OOP notation feels natural, why prefix notation is 
natural for a functional language (since we are interested primarily in 
the transformation not the things being transformed hence we put [VO] 
first), and why the desuraging of infix in Haskell/ML is quite simply 
just wrong, since the object is now separated from the verb.


ok wrote:

Binary operators have two arguments.  That's why sections are needed.


What's wrong with just using (flip)?




I am a bear of very little brain, and I would find it VERY confusing
if the order of arguments in an operator application did not match
the order of arguments in a function call.  I can live with
x @ y = (op @)(x, y)(* SML *)
x @ y = (@) x y-- Haskell
but making the orders different would guarantee that I would *always*
be in a muddle about which argument was which.  Living with
inconvenient argument orders is vastly easier than with inconsistent 
ones.


If you inwardly parse x @ y as [x] [@ y] then the prefix notation is 
naturally formed just by putting the specialized verb before the 
subject instead of after it ie [@ y] [x].
Therefore I think this desugaring, though different from the usual one, 
would seem natural as soon as the reason for it was understood (of 
course, only if you agree with the reason ;-) ), and the great advantage 
of it is that we could write library functions without having to decide 
in advance whether or not they should be used with infix sugar.


(Regarding Henning's point about ((-) a) being needed for Reader monads 
we could define type Fun a b = a - b and then use (Fun a))


In any case, thanks to all who replied. I've found the discussion very 
illuminating and it's certainly helped a lot to clarify the issues for me,


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


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread Henning Thielemann


On Tue, 25 Sep 2007, Brian Hulley wrote:


Jonathan Cast wrote:


Of course, this is all a consequence of the well-known failure of
natural language: verbs come before their objects.  It is thus natural
to write f(x), when in fact it is the object that should come first, not
the function.  Switching to a (natural) language where (finite) verbs
come at the end of sentences, where they belong, should fix this issue
in time.  Doing the same in a functional language would be ideal as
well, but might limit its use among those who speak inferior natural
languages.

Thanks, I must look into using postfix notation. It's used in Forth and 
Postscript and I seem to dimly recall that there is a natural language 
somewhere that also uses it but I can't remember which one.


Reverse Polish! Ah no, it's only the Reverse Polish Notation which is in 
this style. ;-)


Yes, PostScript is nice, does also allow higher order functions and 
partial application.

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


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread Henning Thielemann


On Tue, 25 Sep 2007, Brian Hulley wrote:

To be consistent this would also have to apply to the use of (-) in types to 
get:


  a - b === (-) b a


Since there are many type class instances for the Reader Monad, in this 
case the order of argument seems to be appropriate.


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


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread Henning Thielemann


On Tue, 25 Sep 2007, Dan Piponi wrote:


It's not so clear to me what the syntax for types should be in a postfix 
language.


Postfix, of course! So you'd write

data a Tree = Leaf | a a Tree

Confusingly, ocaml does something like this, with postfix notation for
types and prefix notation for function application.


I have seen the same mixing in Isabelle proof assistant.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread Henning Thielemann


On Tue, 25 Sep 2007, Brian Hulley wrote:

Of course the problem disappears if you just discard multiple clause syntax 
and use:


 (list :: a List) (f :: a - b) map :: b List =
  case list of
  Empty - Empty
  h t PushF - (h f) (t f map) PushF


This would also have the advantage, that there is a name assigned to each 
parameter, which is nice for documentation purposes. However we would also 
have to assign a name to the parameter of 'f', and the (-) type 
constructor becomes somehow special, at least more special than it is now.



Curried functions like

f :: a - b - c

suggest a swapped order of arguments for (-), since 'f' must be called 
this way


b a f

Maybe it should be

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


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread Henning Thielemann


On Tue, 25 Sep 2007, Brian Hulley wrote:


Ryan Ingram wrote:


A couple off the top of my head:

(:) :: a - [a] - [a]


Yes that's one that had totally slipped my mind ;-)


I like to add 'div' and 'mod' as examples for wrong argument order.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread ok

On 26 Sep 2007, at 8:32 am, Brian Hulley wrote:
Aha! but this is using section syntax which is yet another  
complication. Hypothesis: section syntax would not be needed if the  
desugaring order was reversed.


Binary operators have two arguments.  That's why sections are needed.

This is one of the reasons why the combination of
  - sections
  - ordinary names as `operators`
is so nice.  Given a function f :: X - Y - Z.
Currying means that we have (f x) :: Y - Z.
With sections, we also have (`f`y) :: X - Z.

It doesn't matter *which* argument you put first,
people will sometimes need to partially apply to one of them,
and sometimes to the other.

My old ML library includes

fun ap1 f x = fn y = f (x,y)   (* == (x `f`) *)
fun ap2 f y = fn x = f (x,y)   (* == (`f` y) *)

Both are needed because the SML convention for operators passes a tuple.
The point is that BOTH are needed.

I am a bear of very little brain, and I would find it VERY confusing
if the order of arguments in an operator application did not match
the order of arguments in a function call.  I can live with
x @ y = (op @)(x, y)(* SML *)
x @ y = (@) x y -- Haskell
but making the orders different would guarantee that I would *always*
be in a muddle about which argument was which.  Living with
inconvenient argument orders is vastly easier than with inconsistent  
ones.


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


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley

Brian Hulley wrote:

I'm wondering if anyone can shed light on the reason why

   x # y

gets desugared to

  (#) x y

and not

  (#) y x



Can anyone think of an example where the current desugaring of infix 
arguments gives the correct order when the function is used in a 
postfix application? (apart from commutative functions of course!)



Sorry I meant to write *prefix* application
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Jonathan Cast
On Tue, 2007-09-25 at 19:18 +0100, Brian Hulley wrote:
 Brian Hulley wrote:
  I'm wondering if anyone can shed light on the reason why
 
 x # y
 
  gets desugared to
 
(#) x y
 
  and not
 
(#) y x
 
 
  Can anyone think of an example where the current desugaring of infix 
  arguments gives the correct order when the function is used in a 
  postfix application? (apart from commutative functions of course!)
 
 Sorry I meant to write *prefix* application

Of course, this is all a consequence of the well-known failure of
natural language: verbs come before their objects.  It is thus natural
to write f(x), when in fact it is the object that should come first, not
the function.  Switching to a (natural) language where (finite) verbs
come at the end of sentences, where they belong, should fix this issue
in time.  Doing the same in a functional language would be ideal as
well, but might limit its use among those who speak inferior natural
languages.

jcc


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


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Dan Weston
Wise your proposal is. Too long the desugaring I of languages functional 
not understanding have labored. Anastrophe the rule should be. Working 
have I been on a language Yoda that these rules implements it aspires to.


If the lojban/loglan schism is any precedent, Yoda will split soon 
enough into prefix and postfix camps!


Jonathan Cast wrote:

On Tue, 2007-09-25 at 19:18 +0100, Brian Hulley wrote:

Brian Hulley wrote:

I'm wondering if anyone can shed light on the reason why

   x # y

gets desugared to

  (#) x y

and not

  (#) y x

Can anyone think of an example where the current desugaring of infix 
arguments gives the correct order when the function is used in a 
postfix application? (apart from commutative functions of course!)



Sorry I meant to write *prefix* application


Of course, this is all a consequence of the well-known failure of
natural language: verbs come before their objects.  It is thus natural
to write f(x), when in fact it is the object that should come first, not
the function.  Switching to a (natural) language where (finite) verbs
come at the end of sentences, where they belong, should fix this issue
in time.  Doing the same in a functional language would be ideal as
well, but might limit its use among those who speak inferior natural
languages.

jcc


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





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


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Ryan Ingram
My comments inlined below...

On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote:
   let
shiftLeftByThree = shiftL' 3
   in
   map shiftLeftByThree  [10, 78, 99, 102]

let shiftLeftByThree = (`shiftL` 3) in ...

 Can anyone think of an example where the current desugaring of infix
 arguments gives the correct order when the function is used in a postfix
 application? (apart from commutative functions of course!)

A couple off the top of my head:

(:) :: a - [a] - [a]

| :: MonadPlus m = m a - m a - m a
(how do you define correct in this case, anyways?)

Even for shift I can think of several reasons to want to use it both
ways; for example, unpacking a bitfield from a Word16:

unpack v = (getM 0 255, getM 8 1, getM 9 31, getM 14 3)
where getM = (..) . (shiftR v)

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


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley

Jonathan Cast wrote:

On Tue, 2007-09-25 at 19:18 +0100, Brian Hulley wrote:
  

Brian Hulley wrote:


I'm wondering if anyone can shed light on the reason why

   x # y

gets desugared to

  (#) x y

and not

  (#) y x

  

Of course, this is all a consequence of the well-known failure of
natural language: verbs come before their objects.  It is thus natural
to write f(x), when in fact it is the object that should come first, not
the function.  Switching to a (natural) language where (finite) verbs
come at the end of sentences, where they belong, should fix this issue
in time.  Doing the same in a functional language would be ideal as
well, but might limit its use among those who speak inferior natural
languages.
  
Thanks, I must look into using postfix notation. It's used in Forth and 
Postscript and I seem to dimly recall that there is a natural language 
somewhere that also uses it but I can't remember which one.


Not only would it solve the infix/prefix dilemma, but it would also be 
consistent with a sugar for an object oriented syntax for application:


   a b c f
   a .f(b, c)

(Using a dot glued on its right and a left paren glued left to avoid 
ambiguity with unglued dot (function composition) and unglued left paren 
(unit/tuple/bracketing))


It's not so clear to me what the syntax for types should be in a postfix 
language.
Also, a problem might be that it is not so easy to use the 
multiple-clause style of function definition eg compare:


   map _ [] = []
   map f (h : t) = f h : map f t

with

   [] f map = []
   (h : t) f map = h f : t f map

since the function name is no longer conveniently at the margin of 
whatever layout block we are in so extra efforts would need to be made 
to line them up, though this is a minor issue.


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


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Dan Piponi
On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote:

 ...I seem to dimly recall that there is a natural language
 somewhere that also uses it but I can't remember which one.

Every permutation of [S,V,O] appears in 'nature':
http://en.wikipedia.org/wiki/Word_order.

 Also, a problem might be that it is not so easy to use the
multiple-clause style of function definition

I disagree, it's easier with postfix functions. With prefix functions,
to get line-up you insert space in the middle of the line. With
postfix notation you would often insert space at the beginning of a
line, a much easier place to insert text, because there is a
keystroke, in most text editors, to take you to the beginning of a
line.

 It's not so clear to me what the syntax for types should be in a postfix 
 language.

Postfix, of course! So you'd write

data a Tree = Leaf | a a Tree

Confusingly, ocaml does something like this, with postfix notation for
types and prefix notation for function application.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley

Ryan Ingram wrote:

My comments inlined below...

On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote:
  

  let
   shiftLeftByThree = shiftL' 3
  in
  map shiftLeftByThree  [10, 78, 99, 102]



let shiftLeftByThree = (`shiftL` 3) in ...

  
Aha! but this is using section syntax which is yet another complication. 
Hypothesis: section syntax would not be needed if the desugaring order 
was reversed.

Can anyone think of an example where the current desugaring of infix
arguments gives the correct order when the function is used in a postfix
application? (apart from commutative functions of course!)



A couple off the top of my head:

(:) :: a - [a] - [a]
  


Yes that's one that had totally slipped my mind ;-)

| :: MonadPlus m = m a - m a - m a
(how do you define correct in this case, anyways?)
  


I'm not so sure about this one eg:

first | second
(trychoice second) first

because (trychoice second) encapsulates what to do when its argument 
action fails.

Even for shift I can think of several reasons to want to use it both
ways; for example, unpacking a bitfield from a Word16:

unpack v = (getM 0 255, getM 8 1, getM 9 31, getM 14 3)
where getM = (..) . (shiftR v)

  
I suppose with some ops perhaps there is no most common way of wanting 
to use them and hence no one-true-way argument order for those ops.


Thanks for the examples,
Brian.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley

Dan Piponi wrote:

On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote:

..I seem to dimly recall that there is a natural language
somewhere that also uses it but I can't remember which one.



Every permutation of [S,V,O] appears in 'nature':
http://en.wikipedia.org/wiki/Word_order.
  


Thanks for the link - I see [Subject, Object, Verb] is actually the most 
common word order.
  
Also, a problem might be that it is not so easy to use the 
multiple-clause style of function definition 


I disagree, it's easier with postfix functions. With prefix functions,
to get line-up you insert space in the middle of the line. With
postfix notation you would often insert space at the beginning of a
line, a much easier place to insert text, because there is a
keystroke, in most text editors, to take you to the beginning of a
line.

  


I don't understand what you mean. For example, with the prefix 
definition of a function with multiple clauses, the function name at the 
start of each clause is already lined up since it must appear at the 
margin of the current layout block (especially if you follow the simple 
rule of always following a layout starter token by a newline rather than 
starting a new multi-line layout block in the middle of a line), whereas 
with the postfix notation you'd need to manually line up the function 
names if you wanted the same neat look.



It's not so clear to me what the syntax for types should be in a postfix 
language.



Postfix, of course! So you'd write

data a Tree = Leaf | a a Tree
  


Sorry I meant what should the syntax of type declarations for functions 
be? For example, with prefix map (writing lists without sugar for 
clarity) we have:


   map :: (a - b) - List a - List b
   map _ Empty = Empty
   map f (PushF h t) = PushF (f h) (map f t)

The occurrence of map in the type decl lines up with the 2 occurrences 
of map in the clauses, and the types of the arguments are in the same 
order in the type as in the patterns in the clauses.


A postfix version could be:

   map :: (a - b) - a List - b List
   Empty _ map = Empty
   (h t PushF) f map = (h f) (t f map) PushF

but now the occurrences of map no longer line up and the argument 
order is reversed between the type and the value syntax.


Of course the problem disappears if you just discard multiple clause 
syntax and use:


  (list :: a List) (f :: a - b) map :: b List =
   case list of
   Empty - Empty
   h t PushF - (h f) (t f map) PushF


Confusingly, ocaml does something like this, with postfix notation for
types and prefix notation for function application.


I've never understood why {Oca, S}ML's creators decided to make life so 
difficult and confusing by introducing an arbitrary reversal between 
type and value syntax. ;-)


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


Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Sam Hughes

Brian Hulley wrote:

Dan Piponi wrote:

On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote:

..


I don't understand what you mean. For example, with the prefix 
definition of a function with multiple clauses, the function name at the 
start of each clause is already lined up since it must appear at the 
margin of the current layout block (especially if you follow the simple 
rule of always following a layout starter token by a newline rather than 
starting a new multi-line layout block in the middle of a line), whereas 
with the postfix notation you'd need to manually line up the function 
names if you wanted the same neat look.


Or you could have everything be backwards, and use an editor that right 
aligns things.


It's not so clear to me what the syntax for types should be in a 
postfix language.



Postfix, of course! So you'd write

data a Tree = Leaf | a a Tree


 data
a a Tree |
Leaf = a Tree


A postfix version could be:

   map :: (a - b) - a List - b List
   Empty _ map = Empty
   (h t PushF) f map = (h f) (t f map) PushF



   (a - b) - [a] - [b] ::  map
[] = [] _ map
x f : xs f map = (x:xs) f map


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