Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-20 Thread minh thu
 [snip]
 Not a hack, a solution. A consistent one. Look:

  (`foldl` 0)
  (`-` 2)

 Don't they look exactly the same?
 [snip]

These look the same too (and *are* consistent):
(f a b)
(+ a b)

But it's not Haskell..

IMO conflating binary minus and unary minus is not consistent.

Something I wonder from time to time if it would be a good thing or
not is to allow
  a `f g` b
to mean
  f g a b
(so map (`f g` b) as would legal too).

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


[Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-20 Thread oleg

 Something I wonder from time to time if it would be a good thing or
 not is to allow
   a `f g` b
 to mean
   f g a b

You don't have to wonder:
http://www.haskell.org/haskellwiki/Infix_expressions

Granted, you have to use different characters rather than the
backquote. On the other hand, you can play with infix expressions
right now, on any Haskell98 system.


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


[Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-20 Thread Will Ness
Jason Dagit dagit at codersbase.com writes:

 On Mon, Oct 19, 2009 at 5:53 PM, Will Ness will_n48 at yahoo.com wrote:
 
 You think of functions, where domain matters (for purists?). In syntax 
 only the result matter, does it read? Does it have an intended meaning?
 How is it a mistake if it expresses what I intended?
 Both 3 `-` 2 and curry fst `foldl` 0 are exactly the same - expressions with
 infix operator, read in the same way, interpreted in the same way. In 
 the first case the backticks are made superfluous by Haskell reader for 
 our convinience; but they shouldn't be made illegal. Why should they be? 
 

 Don't you mean 3 `(-)` 2?  I'm pretty sure -, without the parens is infix and 
 (-) is prefix.  So it seems to me that you need the brackets for this to be 
 consistent.Jason

You absolutely right, in current syntax that also would only be consistent, yet 
is illegal also.

But I propose to augment the syntax by allowing symbolic ops in backticks to 
stand for themselves.

When I see `op`, for me, it says: infix op. So `+` would also say, infix +. (`-
` 2) would finally become possible. It would read: treat - as infix binary and 
make a flip section out of it. Just as it does for an alphanumeric identifier 
in (`op` 2).

Without backticks, symbolic ops are also treated as infix by default, but 
that's just convinience.

Anyway I guess all the points in this discussion have been made, and it's just 
a matter of taste. 


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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-20 Thread Richard O'Keefe

It's worth remembering that APL and SML, amongst others,
distinguish between the sign used for a negative literal
(¯1 in APL, ~1 in SML) and the sign used for subtraction
(the hyphen/minus in both of them).  It doesn't seem to
be a hard thing to get your head around in practice.

From having worked on a Prolog system, I can tell you
that the fact that -1 is a single token except when it
isn't, yet -X is always two, caused headaches for implementors
and confusion for users.
In Smalltalk, -1 is a number, but x-1 is three tokens, not
two.  (You have to keep track of what the previous token
was to tell what to do.)

If I were making suggestions for Haskell' (other than
please, pretty please with knobs on, let me keep n+k),
one of them would be to introduce the character U+00AF
(chosen because it's 8859-1, -4, -8, -9, and -15 at
least) as a unary minus sign, allowing it to be used
for exponent signs as well, so that
¯x - ¯1.0e¯10
is allowed.

Then Haskell'' could remove the unary - .

In the mean time, the unary - / binary - issue is something
you run into hard ONCE, and then avoid easily enough, not
unlike forgetting the back-ticks in x `div` y.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-20 Thread wren ng thornton

minh thu wrote:

Something I wonder from time to time if it would be a good thing or
not is to allow
  a `f g` b
to mean
  f g a b


This comes up from time to time, though it is often met with stern 
disapproval because it can easily lead to loss of clarity. There is a 
valid alternative, though it's not quite as pretty:


($a) (f g...) b c... == f g... a b c...



With even less prettiness, this can also be generalized for other 
numbers of prefix arguments:


(($a) f) b c... == f a b c...
(  ($b) $($a) f) c d... == f a b c d...
(($c) $($b) $($a) f) d e... == f a b c d e...

And if anyone wanted to use this sort of pattern frequently, I'm sure 
there's some decent way to clean it up ala Matt Hellige's pointless 
trick[1] or ala Oleg's polyvariadic trick[2].



[1] http://matt.immute.net/content/pointless-fun
[2] http://okmij.org/ftp/Haskell/polyvariadic.html

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-19 Thread Will Ness
wren ng thornton wren at freegeek.org writes:

 
 Will Ness wrote:
 
  (`foldl`2) works.
  
  (`-`2) should too.
 
 The `` syntax is for converting lexical identifiers into infix 
 operators. Symbolic identifiers are already infix, which is why `` 


So it would be a no-op then. Why make it illegal? Just because it makes writing 
the scanner easier is no answer.

 doesn't work for them. If we introduced this then those striving for 
 consistency would be right in requesting that this pattern be allowed 
 for all symbolic operators. I for one am opposed to introducing 
 superfluous syntax for duplicating the current ability to write things 
 in the same ways.


This syntax already exists. The '`' symbol is non-collating already, so using 
it for symbol chars doesn't change anything (it's not that it can be a part of 
some name, right?). To turn an infix op into an infix op is an id operation, 
made illegal artificially at the scan phase after a successful lex (or 
whatever).

Finally enabling the missing functionality which is a common stumbling block 
for every beginner is hardly duplicating.

 Attack the underlying problem, don't introduce hacks to cover up broken 
 hacks. This isn't C++.


The underlying problem is a broken scanner where it can't distinguish between a 
binary op and a number read syntax. Op names are collated symbol chars, and one 
of the symbols, -, is also a valid number prefix. So, allow for a clues from 
programmer to detach it from the number: backticks separate it from the 
following numeric chars, preventing it from sticking to them. And by itself, 
it forms an op, a binary one.

Not a hack, a solution. A consistent one. Look:

  (`foldl` 0)
  (`-` 2)

Don't they look exactly the same?

Why wouldn't it be made legal? Show me one inconsistency it introduces.


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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-19 Thread Tom Tobin
On Mon, Oct 19, 2009 at 5:34 PM, Will Ness will_...@yahoo.com wrote:
 This syntax already exists. The '`' symbol is non-collating already, so using
 it for symbol chars doesn't change anything (it's not that it can be a part of
 some name, right?). To turn an infix op into an infix op is an id operation,
 made illegal artificially at the scan phase after a successful lex (or
 whatever).

If I've accidentally applied syntax meant for a prefix operator to an
infix operator, *I want the compiler to tell me*, and not to silently
accept my mistake.


 Not a hack, a solution. A consistent one. Look:

  (`foldl` 0)
  (`-` 2)

 Don't they look exactly the same?

No, because the latter is applying prefix-to-infix syntax to an infix
operator.  It's understood that non-alphanumerics are infix by
default, and I want the compiler to scream at me if I try to use one
where it expected a prefix op.


 Why wouldn't it be made legal? Show me one inconsistency it introduces.

You've said that you want to be able to do this for the sole case of
the - (minus-sign) operator:

 Operators are great because they make our intent visible, immediately
 apparent. Long words' meaning, like subtract's, is not immediately apparent,
 and they break consistency. Not everyone's first language in life was English,
 you see.

I don't buy this rationale.  Haskell has plenty of English words as
function names all over the place; if you can't handle subtract, how
are you handling Haskell at all?  Sure, the minus-sign issue is a
wart, but it's less awkward than the solution you propose for a
problem I doubt you really have.  :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-19 Thread Will Ness
Tom Tobin korpios at korpios.com writes:

 On Mon, Oct 19, 2009 at 5:34 PM, Will Ness will_n48 at yahoo.com wrote:
  This syntax already exists. The '`' symbol is non-collating already, so 
  using it for symbol chars doesn't change anything (it's not that it 
  can be a part of some name, right?). To turn an infix op into an infix op 
  is an id operation, made illegal artificially at the scan phase after a 
  successful lex (or whatever).
 
 If I've accidentally applied syntax meant for a prefix operator to an
 infix operator, *I want the compiler to tell me*, and not to silently
 accept my mistake.

You don't apply sytax, you write it.

You think of functions, where domain matters (for purists?). In syntax only the 
result matter, does it read? Does it have an intended meaning? 

How is it a mistake if it expresses what I intended?

Both 3 `-` 2 and curry fst `foldl` 0 are exactly the same - expressions with 
infix operator, read in the same way, interpreted in the same way. In the first 
case the backticks are made superfluous by Haskell reader for our convinience; 
but they shouldn't be made illegal. Why should they be? I truly don't 
understand the resistance to this idea. :)


  Why wouldn't it be made legal? Show me one inconsistency it introduces.
 
 You've said that you want to be able to do this for the sole case of
 the - (minus-sign) operator:

This is not an inconsistence. 

Plus, if we were to take this idea of using backticks as names delimeters to 
the extreme, it could even allow us to use such identifiers as `left-fold` or 
`right-fold` in infix position, and (`left-fold`) by itself. Although that 
seems not such a good idea.


  Operators are great because they make our intent visible, immediately
  apparent. Long words' meaning, like subtract's, is not immediately apparent,
  and they break consistency. Not everyone's first language in life was 
  English, you see.
 
 I don't buy this rationale.  Haskell has plenty of English words as
 function names all over the place; if you can't handle subtract, how
 are you handling Haskell at all?  Sure, the minus-sign issue is a
 wart, but it's less awkward than the solution you propose for a
 problem I doubt you really have.  

When I see `++` I don't need to think _at_all_. When I see `concatenate` or 
some such, I do - even if for a briefest of moments. It is _less_ convinient 
both to read and _write_, don't you agree? 

I don't see my proposal as awkward at all. On the contrary, to me it looks 
natural and consistent with the other uses of this device in the language. It 
is this asymmetry that bothers me with the (-) issue, I just want the balance 
restored. But it is a matter of taste of course. Or obsessing over minutiae. :)

Oh well.

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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-19 Thread wren ng thornton

Will Ness wrote:

wren ng thornton writes:
Attack the underlying problem, don't introduce hacks to cover up broken 
hacks. This isn't C++.


The underlying problem is a broken scanner where it can't distinguish between a 
binary op and a number read syntax.


The underlying problem is that (1) people don't want normal whitespace 
to change the meaning of code, (2) they don't want to disallow negative 
literals, and (3) they want to use the same symbolic operator for 
negation and subtraction, but these three goals cannot all be satisfied 
simultaneously.


The current resolution is to hack at the parser in order to make things 
mostly work. But this hack is insufficient, as argued by the OP. The 
proposed solution was to introduce new syntax complicating the language 
by explaining how 1-2 and 1`-`2 are the same thing (either repeated for 
all other symbolic operators, or exceptional to the subtraction 
operator, and ugly by either approach). But why should we introduce all 
this syntactic complexity which needs explaining to newbies and only 
makes the wart more visible?


The proper solution is not to introduce syntactic hackery on top of the 
parser hackery, the proper solution is to either come up with a better 
parser hack or to sacrifice one of the three incompatible goals.




Not a hack, a solution. A consistent one. Look:

  (`foldl` 0)
  (`-` 2)

Don't they look exactly the same?


Not to me they don't. Symbolic and lexical operators are treated 
differently in Haskell. Considering all the places where they're treated 
differently, I see no compelling reason to think they should be 
considered similar here.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-19 Thread Jason Dagit
On Mon, Oct 19, 2009 at 5:53 PM, Will Ness will_...@yahoo.com wrote:

 Tom Tobin korpios at korpios.com writes:

  On Mon, Oct 19, 2009 at 5:34 PM, Will Ness will_n48 at yahoo.com
 wrote:
   This syntax already exists. The '`' symbol is non-collating already, so
   using it for symbol chars doesn't change anything (it's not that it
   can be a part of some name, right?). To turn an infix op into an infix
 op
   is an id operation, made illegal artificially at the scan phase after a
   successful lex (or whatever).
 
  If I've accidentally applied syntax meant for a prefix operator to an
  infix operator, *I want the compiler to tell me*, and not to silently
  accept my mistake.

 You don't apply sytax, you write it.

 You think of functions, where domain matters (for purists?). In syntax only
 the
 result matter, does it read? Does it have an intended meaning?

 How is it a mistake if it expresses what I intended?

 Both 3 `-` 2 and curry fst `foldl` 0 are exactly the same - expressions
 with
 infix operator, read in the same way, interpreted in the same way. In the
 first
 case the backticks are made superfluous by Haskell reader for our
 convinience;
 but they shouldn't be made illegal. Why should they be? I truly don't
 understand the resistance to this idea. :)


Don't you mean 3 `(-)` 2?  I'm pretty sure -, without the parens is infix
and (-) is prefix.  So it seems to me that you need the brackets for this to
be consistent.

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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-19 Thread Luke Palmer
On Sun, Oct 18, 2009 at 5:31 PM, Will Ness will_...@yahoo.com wrote:
 Luke Palmer lrpalmer at gmail.com writes:


 Or you could use the subtract function.

    map (subtract 2) [3,4,5]
   [1,2,3]

 I don't want to.

I think at about this point, this stopped being an intellectual
discussion.   Preparing for academic flame war...


 I don't think syntax sugar is worth it in this case.


 I do. Operators are great because they make our intent visible, immediately
 apparent. Long words' meaning, like subtract's, is not immediately apparent,
 and they break consistency. Not everyone's first language in life was English,
 you see.

 (`foldl`2) works.

 (`-`2) should too.

 I'll settle for (+(-2)) for now, but it ain't that pretty.


 ___
 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


[Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-18 Thread Will Ness
Gregory Propf gregorypropf at yahoo.com writes:

 
 
 I actually meant it as sort of a joke but maybe it's not after all.  

Seriously though, using anything non-ASCII in source code is a bad idea, 
because there are lots of fonts and editors in the world.

It seems natural to me to have (`-`2) stand for (flip (-) 2), if only that 
would be made legal syntax, just as (`foldl`0) stands for (flip (foldl) 0).

Supposedly there is no reason to write (`:`[]) since : is already an infix 
operator, but making it a no-op wouldn't hurt, and would give us a benefit of 
being able finally to write the binary-minus flip-section in a visually 
apparent way.



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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-18 Thread Luke Palmer
On Sun, Oct 18, 2009 at 4:47 PM, Will Ness will_...@yahoo.com wrote:
 Gregory Propf gregorypropf at yahoo.com writes:



 I actually meant it as sort of a joke but maybe it's not after all.

 Seriously though, using anything non-ASCII in source code is a bad idea,
 because there are lots of fonts and editors in the world.

 It seems natural to me to have (`-`2) stand for (flip (-) 2), if only that
 would be made legal syntax, just as (`foldl`0) stands for (flip (foldl) 0).

Or you could use the subtract function.

   map (subtract 2) [3,4,5]
  [1,2,3]

I don't think syntax sugar is worth it in this case.

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


[Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-18 Thread Will Ness
Luke Palmer lrpalmer at gmail.com writes:

 
 Or you could use the subtract function.
 
map (subtract 2) [3,4,5]
   [1,2,3]

I don't want to.

 
 I don't think syntax sugar is worth it in this case.


I do. Operators are great because they make our intent visible, immediately 
apparent. Long words' meaning, like subtract's, is not immediately apparent, 
and they break consistency. Not everyone's first language in life was English, 
you see.

(`foldl`2) works.

(`-`2) should too.

I'll settle for (+(-2)) for now, but it ain't that pretty.


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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-10-18 Thread wren ng thornton

Will Ness wrote:

Luke Palmer lrpalmer at gmail.com writes:

Or you could use the subtract function.

   map (subtract 2) [3,4,5]
  [1,2,3]


I don't want to.


I don't think syntax sugar is worth it in this case.


I do. Operators are great because they make our intent visible, immediately 
apparent. Long words' meaning, like subtract's, is not immediately apparent, 
and they break consistency. Not everyone's first language in life was English, 
you see.


I'm with Luke on this one. It's a shame that negation uses the same 
symbolic identifier as subtraction, but introducing this new sugar only 
serves to make things more complex than they already are. If anything, 
negation should be moved to using a different identifier to remove the 
current ambiguity (as is done in some other languages).




(`foldl`2) works.

(`-`2) should too.


The `` syntax is for converting lexical identifiers into infix 
operators. Symbolic identifiers are already infix, which is why `` 
doesn't work for them. If we introduced this then those striving for 
consistency would be right in requesting that this pattern be allowed 
for all symbolic operators. I for one am opposed to introducing 
superfluous syntax for duplicating the current ability to write things 
in the same ways.


Attack the underlying problem, don't introduce hacks to cover up broken 
hacks. This isn't C++.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-18 Thread Ketil Malde
Gregory Propf gregorypr...@yahoo.com writes:

 Heh, perhaps we should petition to have a new computer key and symbol
 added to the world's way of writing maths, something like maybe a
 downward angled slash to mean prefix (-)  

Or just use 'negate' and 'subtract'?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-18 Thread Jon Fairbairn
Ketil Malde ke...@malde.org writes:

 Gregory Propf gregorypr...@yahoo.com writes:

 Heh, perhaps we should petition to have a new computer key and symbol
 added to the world's way of writing maths, something like maybe a
 downward angled slash to mean prefix (-)  

 Or just use 'negate' and 'subtract'?

Well, now that ghc accepts unicode characters in programme source, we
could ask that ¬ (NOT SIGN, U+00AC) be recategorised as an identifier
character and use that (as a simple function name) for negation and lose
the wart altogether.

class Negatable t where
  ¬ :: t - t

(and as a side effect we could have identifiers like slightly¬dodgy).

Or, if we want to make things look even nicer, make ‐ (HYPHEN, U+2010)
an identifier character and use − (MINUS SIGN, U+2212) for the infix
operator. Now we could have hyphenated‐identifiers too.

I think this second option would be the ㊣ (CORRECT, U+32A3) thing to
do, though editors and so on would have to be changed to make the
distinction readily visible.

I think it's Friday, but I'm not entirely sure this is silly.

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk

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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-18 Thread Thomas Davie


On 18 Sep 2009, at 04:32, Gregory Propf wrote:

Heh, perhaps we should petition to have a new computer key and  
symbol added to the world's way of writing maths, something like  
maybe a downward angled slash to mean prefix (-)


Such a symbol already exists, but isn't in the ASCII set:

(-) (unicode 0x2D) hyphen minus
and
(‐) (unicode 0x2010) hyphen
are not the same as
(−) (unicode 0x2200) minus sign

notably also, not the same as ‒, –, — and ― (figure dash, en- 
dash, em-dash and horizontal bar).


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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-18 Thread Gregory Propf
I actually meant it as sort of a joke but maybe it's not after all.  Among the 
many benefits, think of all the delightful conspiracy theories such a change 
would spawn - even our math isn't safe now!, Save the minus sign!.

--- On Fri, 9/18/09, Jon Fairbairn jon.fairba...@cl.cam.ac.uk wrote:

From: Jon Fairbairn jon.fairba...@cl.cam.ac.uk
Subject: [Haskell-cafe] Re: [Haskell-beginners] map question
To: haskell-cafe@haskell.org
Date: Friday, September 18, 2009, 2:09 AM

Ketil Malde ke...@malde.org writes:

 Gregory Propf gregorypr...@yahoo.com writes:

 Heh, perhaps we should petition to have a new computer key and symbol
 added to the world's way of writing maths, something like maybe a
 downward angled slash to mean prefix (-)  

 Or just use 'negate' and 'subtract'?

Well, now that ghc accepts unicode characters in programme source, we
could ask that ¬ (NOT SIGN, U+00AC) be recategorised as an identifier
character and use that (as a simple function name) for negation and lose
the wart altogether.

class Negatable t where
      ¬ :: t - t

(and as a side effect we could have identifiers like slightly¬dodgy).

Or, if we want to make things look even nicer, make ‐ (HYPHEN, U+2010)
an identifier character and use − (MINUS SIGN, U+2212) for the infix
operator. Now we could have hyphenated‐identifiers too.

I think this second option would be the ㊣ (CORRECT, U+32A3) thing to
do, though editors and so on would have to be changed to make the
distinction readily visible.

I think it's Friday, but I'm not entirely sure this is silly.

-- 
Jón Fairbairn                                 jon.fairba...@cl.cam.ac.uk

___
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


[Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-17 Thread Gregory Propf
Remember that there is asymmetry between (+) and (-).  The former has the 
commutative property and the latter does not so:

(+) 3 4 = 7

and

(+) 4 3 = 7

but 

(-) 3 4 = -1

and

(-) 4 3 = 1

--- On Thu, 9/17/09, Tom Doris tomdo...@gmail.com wrote:

From: Tom Doris tomdo...@gmail.com
Subject: Re: [Haskell-beginners] map question
To: Joost Kremers joostkrem...@fastmail.fm
Cc: beginn...@haskell.org
Date: Thursday, September 17, 2009, 6:06 AM

This works:

map (+ (-1)) [1,2,3,4]


2009/9/17 Joost Kremers joostkrem...@fastmail.fm

Hi all,



I've just started learning Haskell and while experimenting with map a bit, I ran

into something I don't understand. The following commands do what I'd expect:



Prelude map (+ 1) [1,2,3,4]

[2,3,4,5]

Prelude map (* 2) [1,2,3,4]

[2,4,6,8]

Prelude map (/ 2) [1,2,3,4]

[0.5,1.0,1.5,2.0]

Prelude map (2 /) [1,2,3,4]

[2.0,1.0,0.,0.5]



But I can't seem to find a way to get map to substract 1 from all members of the

list. The following form is the only one that works, but it doesn't give the

result I'd expect:



Prelude map ((-) 1) [1,2,3,4]

[0,-1,-2,-3]



I know I can use an anonymous function, but I'm just trying to understand the

result here... I'd appreciate any hints to help me graps this.



TIA



Joost





--

Joost Kremers, PhD

University of Frankfurt

Institute for Cognitive Linguistics

Grüneburgplatz 1

60629 Frankfurt am Main, Germany

___

Beginners mailing list

beginn...@haskell.org

http://www.haskell.org/mailman/listinfo/beginners




-Inline Attachment Follows-

___
Beginners mailing list
beginn...@haskell.org
http://www.haskell.org/mailman/listinfo/beginners



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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-17 Thread Job Vranish
(-) happens to be the only prefix operator in haskell, it also an infix
operator.
so:
 4 - 2
2
 -3
-3

 ((-) 5) 3  -- note that in this case (-) is treated like any regular
function so 5 is the first parameter
2
 (5 - ) 3
2
 (-5 )
-5
 (flip (-) 5) 3
-2


It's a little wart brought about by the ambiguity in common mathematical
syntax.
If you play around in ghci you should get the hang of it pretty quick.

- Job



On Thu, Sep 17, 2009 at 11:08 AM, Gregory Propf gregorypr...@yahoo.comwrote:

 Remember that there is asymmetry between (+) and (-).  The former has the
 commutative property and the latter does not so:

 (+) 3 4 = 7

 and

 (+) 4 3 = 7

 but

 (-) 3 4 = -1

 and

 (-) 4 3 = 1

 --- On *Thu, 9/17/09, Tom Doris tomdo...@gmail.com* wrote:


 From: Tom Doris tomdo...@gmail.com
 Subject: Re: [Haskell-beginners] map question
 To: Joost Kremers joostkrem...@fastmail.fm
 Cc: beginn...@haskell.org
 Date: Thursday, September 17, 2009, 6:06 AM

 This works:

 map (+ (-1)) [1,2,3,4]


 2009/9/17 Joost Kremers 
 joostkrem...@fastmail.fmhttp://mc/compose?to=joostkrem...@fastmail.fm
 

 Hi all,

 I've just started learning Haskell and while experimenting with map a bit,
 I ran
 into something I don't understand. The following commands do what I'd
 expect:

 Prelude map (+ 1) [1,2,3,4]
 [2,3,4,5]
 Prelude map (* 2) [1,2,3,4]
 [2,4,6,8]
 Prelude map (/ 2) [1,2,3,4]
 [0.5,1.0,1.5,2.0]
 Prelude map (2 /) [1,2,3,4]
 [2.0,1.0,0.,0.5]

 But I can't seem to find a way to get map to substract 1 from all members
 of the
 list. The following form is the only one that works, but it doesn't give
 the
 result I'd expect:

 Prelude map ((-) 1) [1,2,3,4]
 [0,-1,-2,-3]

 I know I can use an anonymous function, but I'm just trying to understand
 the
 result here... I'd appreciate any hints to help me graps this.

 TIA

 Joost


 --
 Joost Kremers, PhD
 University of Frankfurt
 Institute for Cognitive Linguistics
 Grüneburgplatz 1
 60629 Frankfurt am Main, Germany
 ___
 Beginners mailing list
 beginn...@haskell.org http://mc/compose?to=beginn...@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



 -Inline Attachment Follows-

 ___
 Beginners mailing list
 beginn...@haskell.org http://mc/compose?to=beginn...@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



 ___
 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] Re: [Haskell-beginners] map question

2009-09-17 Thread Deniz Dogan
 2009/9/17 Joost Kremers joostkrem...@fastmail.fm

 Hi all,

 I've just started learning Haskell and while experimenting with map a bit, I 
 ran
 into something I don't understand. The following commands do what I'd expect:

 Prelude map (+ 1) [1,2,3,4]
 [2,3,4,5]
 Prelude map (* 2) [1,2,3,4]
 [2,4,6,8]
 Prelude map (/ 2) [1,2,3,4]
 [0.5,1.0,1.5,2.0]
 Prelude map (2 /) [1,2,3,4]
 [2.0,1.0,0.,0.5]

 But I can't seem to find a way to get map to substract 1 from all members of 
 the
 list. The following form is the only one that works, but it doesn't give the
 result I'd expect:

 Prelude map ((-) 1) [1,2,3,4]
 [0,-1,-2,-3]

 I know I can use an anonymous function, but I'm just trying to understand the
 result here... I'd appreciate any hints to help me graps this.

 TIA

 Joost

The reason that map (-1) [1,2,3,4] doesn't work as you'd expect it
to is that - is ambiguous in Haskell (some may disagree).

-1 means -1 in Haskell, i.e. negative 1, not the function that
subtracts 1 from its argument. (-) 1 is the function that subtracts
its argument from 1, which is not what you were looking for either!
You're looking for the function that subtracts 1 from its argument,
which is `subtract 1'.

Prelude map (subtract 1) [1..4]
[0,1,2,3]

Note that `subtract' is just another name for `flip (-)', i.e.
subtraction with its argument in reverse order.

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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-17 Thread Gregory Propf
Heh, perhaps we should petition to have a new computer key and symbol added to 
the world's way of writing maths, something like maybe a downward angled slash 
to mean prefix (-) 

:)

--- On Thu, 9/17/09, Job Vranish jvran...@gmail.com wrote:

From: Job Vranish jvran...@gmail.com
Subject: Re: [Haskell-cafe] Re: [Haskell-beginners] map question
To: Gregory Propf gregorypr...@yahoo.com
Cc: Tom Doris tomdo...@gmail.com, Haskell-Cafe 
haskell-cafe@haskell.org, joostkrem...@fastmail.fm
Date: Thursday, September 17, 2009, 9:04 AM

(-) happens to be the only prefix operator in haskell, it also an infix 
operator.
so:
 4 - 2 
2
 -3 
-3

 ((-) 5) 3  -- note that in this case (-) is treated like any regular function 
 so 5 is the first parameter

2
 (5 - ) 3
2
 (-5 )
-5
 (flip (-) 5) 3  
-2



It's a little wart brought about by the ambiguity in common mathematical 
syntax. 

If you play around in ghci you should get the hang of it pretty quick.

- Job



On Thu, Sep 17, 2009 at 11:08 AM, Gregory Propf gregorypr...@yahoo.com wrote:


Remember that there is asymmetry between (+) and (-).  The former has the 
commutative property and the latter does not so:

(+) 3 4 = 7

and

(+) 4 3 = 7

but 

(-) 3 4 = -1

and


(-) 4 3 = 1

--- On Thu, 9/17/09, Tom Doris tomdo...@gmail.com wrote:


From: Tom Doris tomdo...@gmail.com
Subject: Re: [Haskell-beginners] map question
To: Joost Kremers joostkrem...@fastmail.fm

Cc: beginn...@haskell.org
Date: Thursday, September 17, 2009, 6:06 AM

This works:

map (+ (-1)) [1,2,3,4]



2009/9/17 Joost Kremers joostkrem...@fastmail.fm


Hi all,



I've just started learning Haskell and while experimenting with map a bit, I ran

into something I don't understand. The following commands do what I'd expect:



Prelude map (+ 1) [1,2,3,4]

[2,3,4,5]

Prelude map (* 2) [1,2,3,4]

[2,4,6,8]

Prelude map (/ 2) [1,2,3,4]

[0.5,1.0,1.5,2.0]

Prelude map (2 /) [1,2,3,4]

[2.0,1.0,0.,0.5]



But I can't seem to find a way to get map to substract 1 from all members of the

list. The following form is the only one that works, but it doesn't give the

result I'd expect:



Prelude map ((-) 1) [1,2,3,4]

[0,-1,-2,-3]



I know I can use an anonymous function, but I'm just trying to understand the

result here... I'd appreciate any hints to help me graps this.



TIA



Joost





--

Joost Kremers, PhD

University of Frankfurt

Institute for Cognitive Linguistics

Grüneburgplatz 1

60629 Frankfurt am Main, Germany

___

Beginners mailing list

beginn...@haskell.org

http://www.haskell.org/mailman/listinfo/beginners




-Inline Attachment Follows-

___
Beginners mailing list
beginn...@haskell.org

http://www.haskell.org/mailman/listinfo/beginners



  
___

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