Re: [Haskell-cafe] Alternative name for return

2013-08-18 Thread Nikolaos Bezirgiannis
Dag Odenhall dag.odenh...@gmail.com writes:

 I particularly like she's (her?) syntax for Alternative. Not sure
 whether or not Idris has that. Applicative tuples would be nice too,
 something like (|a,b,c|) translating to liftA3 (,,) a b c. And
 operators too, liftA2 (+) a b as (| a + b |)?

I patched she and did applicative tuples. Check my recent blog post on
it:

http://blog.bezirg.net/posts/2013-08-03-enhancement-to-the-strathclyde-haskell-enhancement.html


She already does lifting of binary operators, AFAIK.

Cheers




 On Thu, Aug 15, 2013 at 11:08 AM, Erik Hesselink hessel...@gmail.com
 wrote:

 On Thu, Aug 15, 2013 at 5:39 AM, Jason Dagit dag...@gmail.com
 wrote:
  Also, if anyone wants to look at prior art first, Idris
 supports applicative
  brackets.

 As does she [0].

 Erik

 [0] https://personal.cis.strath.ac.uk/conor.mcbride/pub/she/
 idiom.html

 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-15 Thread Erik Hesselink
On Thu, Aug 15, 2013 at 5:39 AM, Jason Dagit dag...@gmail.com wrote:
 Also, if anyone wants to look at prior art first, Idris supports applicative
 brackets.

As does she [0].

Erik

[0] https://personal.cis.strath.ac.uk/conor.mcbride/pub/she/idiom.html

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


Re: [Haskell-cafe] Alternative name for return

2013-08-15 Thread Dag Odenhall
I particularly like she's (her?) syntax for Alternative. Not sure whether
or not Idris has that. Applicative tuples would be nice too, something like
(|a,b,c|) translating to liftA3 (,,) a b c. And operators too, liftA2 (+) a
b as (| a + b |)?


On Thu, Aug 15, 2013 at 11:08 AM, Erik Hesselink hessel...@gmail.comwrote:

 On Thu, Aug 15, 2013 at 5:39 AM, Jason Dagit dag...@gmail.com wrote:
  Also, if anyone wants to look at prior art first, Idris supports
 applicative
  brackets.

 As does she [0].

 Erik

 [0] https://personal.cis.strath.ac.uk/conor.mcbride/pub/she/idiom.html

 ___
 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] Alternative name for return

2013-08-15 Thread Anton Nikishaev
Simon Peyton-Jones simo...@microsoft.com writes:

 |  Indeed, I wished the 0-ary case would be more alike to the unary
 |  and binary case, cf.
 |  
 | return f0
 | f1 $ a1
 | f2 $ a1 * a2
 |  
 |  What is needed is a nice syntax for idiom brackets.

 Indeed.  I'm quite open to adding idiom brackets to GHC, if everyone
 can agree on their syntax, and someone would like to offer a patch.

 Something like
   (| f a1 a2 |)
 perhaps?

I can make a patch after people agree on everything.

There's also http://hackage.haskell.org/package/applicative-quoters with
its template haskell nastiness

h :m +Control.Applicative.QQ.Idiom
h :set -XQuasiQuotes
h [i| (,) THX BYE |]
[('T','B'),('T','Y'),('T','E'),('H','B'),('H','Y'),('H','E'),('X','B'),('X','Y'),('X','E')]



-- 
lelf


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


Re: [Haskell-cafe] Alternative name for return

2013-08-15 Thread Tikhon Jelvis
If we're adding applicative brackets, it would be nice to have something
like ⦇⦈ as options via UnicodeSyntax. When playing around with She, I found
it much easier to read than the ASCII version, especially when I needed to
combine them:

(|(|a + b|) + (|c * d|)|)
⦇⦇a + b⦈ + ⦇c * d⦈⦈

Coincidentally, She is the perfect way to experiment with idiom brackets
while thinking about a patch like this. I found it very illustrative just
to go through old code and see what could really be improved and what
couldn't. For me personally, I certainly found *some* code became more
readable, but not quite as much as I expected.


On Thu, Aug 15, 2013 at 10:44 AM, Anton Nikishaev m...@lelf.lu wrote:

 Simon Peyton-Jones simo...@microsoft.com writes:

  |  Indeed, I wished the 0-ary case would be more alike to the unary
  |  and binary case, cf.
  |
  | return f0
  | f1 $ a1
  | f2 $ a1 * a2
  |
  |  What is needed is a nice syntax for idiom brackets.
 
  Indeed.  I'm quite open to adding idiom brackets to GHC, if everyone
  can agree on their syntax, and someone would like to offer a patch.
 
  Something like
(| f a1 a2 |)
  perhaps?

 I can make a patch after people agree on everything.

 There's also http://hackage.haskell.org/package/applicative-quoters with
 its template haskell nastiness

 h :m +Control.Applicative.QQ.Idiom
 h :set -XQuasiQuotes
 h [i| (,) THX BYE |]

 [('T','B'),('T','Y'),('T','E'),('H','B'),('H','Y'),('H','E'),('X','B'),('X','Y'),('X','E')]



 --
 lelf


 ___
 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] Alternative name for return

2013-08-14 Thread Twan van Laarhoven

On 13/08/13 17:38, Andreas Abel wrote:

Indeed, I wished the 0-ary case would be more alike to the unary and binary
case, cf.

   return f0
   f1 $ a1
   f2 $ a1 * a2


You could always write the above as

pure f0
pure f1 * a1
pure f2 * a1 * a2


Twan

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


Re: [Haskell-cafe] Alternative name for return

2013-08-14 Thread Simon Peyton-Jones
|  Indeed, I wished the 0-ary case would be more alike to the unary and
|  binary case, cf.
|  
| return f0
| f1 $ a1
| f2 $ a1 * a2
|  
|  What is needed is a nice syntax for idiom brackets.

Indeed.  I'm quite open to adding idiom brackets to GHC, if everyone can agree 
on their syntax, and someone would like to offer a patch.

Something like
(| f a1 a2 |)
perhaps?

Simon

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


Re: [Haskell-cafe] Alternative name for return

2013-08-14 Thread Jason Dagit
On Wed, Aug 14, 2013 at 7:54 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

 |  Indeed, I wished the 0-ary case would be more alike to the unary and
 |  binary case, cf.
 |
 | return f0
 | f1 $ a1
 | f2 $ a1 * a2
 |
 |  What is needed is a nice syntax for idiom brackets.

 Indeed.  I'm quite open to adding idiom brackets to GHC, if everyone can
 agree on their syntax, and someone would like to offer a patch.

 Something like
 (| f a1 a2 |)


The last time I suggested this (on IRC), the first question someone asked
was: How should nested uses of applicative work with idiom brackets? I
think this question actually comes in two flavors:

  * Can you nest the brackets themselves?
  * How deeply do you traverse the expression to insert the applicative
combinators?

Also, if anyone wants to look at prior art first, Idris supports
applicative brackets.

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


Re: [Haskell-cafe] Alternative name for return

2013-08-13 Thread Andreas Abel

On 06.08.2013 10:46, Adam Gundry wrote:

On 06/08/13 06:14, J. Stutterheim wrote:

Suppose we now have the opportunity to change the name of the
`return` function in Monad, what would be a better  name for it?
(for some definition of better)


Rather than proposing a different name, I'm going to challenge the
premise of your question. Perhaps it would be better if `return` had no
name at all. Consider the following:

 return f `ap` s `ap` t

 f $ s * t

 do { sv - s
; tv - t
; return (f sv tv) }


Indeed, I wished the 0-ary case would be more alike to the unary and 
binary case, cf.


  return f0
  f1 $ a1
  f2 $ a1 * a2

What is needed is a nice syntax for idiom brackets.


These are all different ways of spelling

 f s t

plus the necessary applicative or monadic bureaucracy. But why couldn't
we write just the plain application, and let the type system deal with
the plumbing of effects?


I would not think this is practically possible.  For instance, if

  f :: a - b - c

then it could be a binary function or a unary function in the context 
monad reading from a, thus, application


  f x

is ambiguous or too sensitive, especially with type inference.


I realise that this may be too open a research area for your project...



--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Alternative name for return

2013-08-09 Thread Kim-Ee Yeoh
On Thu, Aug 8, 2013 at 7:40 AM, Timon Gehr timon.g...@gmx.ch wrote:

  You make the distinction between evaluate,


 Which essentially means applying reduction rules to an expression until
 the result is a value.

  and  execute or run, etc. This is not functional.


 How would you know?


I think Jerzy is alluding to the fact that we don't have a denotational
semantics for IO. So I'm not sure I understand your response. Are you
pointing out that some subspace of IO programs admit such a semantics via
an easy inspection?

'putStr c' is a pure value.


This is the crux of the matter: pure value means different things to
different people.

Some employ it to mean an effectful monadic expression to distinguish
between getLine and (return Hello), both of type IO String.

Others use it to distinguish between an ordinary Haskell expression and,
say, C.

So when you write:

 'unsafePerformIO (putStr c)' is not a pure value.

I infer you're in the latter camp.

Would you then speak of 'effectful' values vs 'null-effectful' ones? What
oral syntax would you actually use?

-- Kim-Ee


On Thu, Aug 8, 2013 at 7:40 AM, Timon Gehr timon.g...@gmx.ch wrote:

 On 08/08/2013 01:19 AM, Jerzy Karczmarczuk wrote:

 Bardur Arantsson comments the comment of Joe Quinn:

 On 8/7/2013 11:00 AM, David Thomas wrote:

 twice :: IO () - IO ()
 twice x = x  x
 
 I would call that evaluating x twice (incidentally creating two
 separate evaluations of one pure action description), but I'd like to
 better see your perspective here.

 
 x is only evaluated once, but/executed/  twice. For IO, that means

 magic. For other types, it means different things. For Identity, twice
 =
 id!
 

 Your point being? x is the same thing regardless of how many times you
 run it.


 What do you mean by the same thing? You cannot compare 'them' in any
 reasonable sense.
 ...


 http://en.wikipedia.org/wiki/**Identity_of_indiscernibleshttp://en.wikipedia.org/wiki/Identity_of_indiscernibles

 (He is reasoning _about_ the language and not _within_ the language
 because Haskell does not support very powerful reasoning internally.)

  ...

 You make the distinction between evaluate,


 Which essentially means applying reduction rules to an expression until
 the result is a value.


  and  execute or run, etc. This is not functional.


 How would you know?

  Your program doesn't run anything, it
 applies (=) (or equivalent) to an IO (...) object. This is the only
 practical evaluation of it, otherwise it can  be passed (or duplicated
 as above). But you cannot apply bind twice to the same instance of it
 (in fact, as I said above, the same instance  is a bit suspicious
 concept...).
 ...


 Indeed, but you didn't say that above.


  The running or execution takes place outside of your program. In
 such a way Richard O'Keefe and I converge... That's why I say that the
 concept of purity is meaningless in the discussed context.


 Not meaningless, but redundant. The point of having a purely functional
 programming language is to have reasoning based on purity be universally
 applicable.

  It is a kind of counterfeit notion, inherited from pure functions to
 something
 which belongs to two different worlds.
 ...


 'putStr c' is a pure value.

 On the other hand:

 'unsafePerformIO (putStr c)' is not a pure value.

 (But this expression does not exist in standard Haskell. unsafePerformIO
 unquotes the action. You may be confusing the quoted and unquoted
 versions.)



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] Alternative name for return

2013-08-08 Thread Tom Ellis
On Thu, Aug 08, 2013 at 01:19:27AM +0200, Jerzy Karczmarczuk wrote:
 Bardur Arantsson comments the comment of Joe Quinn:
 On 8/7/2013 11:00 AM, David Thomas wrote:
 twice :: IO () - IO ()
 twice x = x  x
 
 I would call that evaluating x twice (incidentally creating two
 separate evaluations of one pure action description), but I'd like to
 better see your perspective here.
 
 x is only evaluated once, but/executed/  twice. For IO, that means
 magic. For other types, it means different things. For Identity, twice =
 id!
 
 Your point being? x is the same thing regardless of how many times you
 run it.
 
 What do you mean by the same thing? You cannot compare 'them' in
 any reasonable sense.
 
 This, the impossibility to check putStr c == putStr c, is btw, a
 refutation of the claim by Tom Ellis that you can do even less with
 (). The void object is an instance of the Eq and Ord classes. And of
 Show as well.

If I were writing a Haskell compiler I could certainly define 'IO' to be a
datatype that would allow me to compare 'putStr c' to itself.  The
comparison could not be of operational equivalence, but it would still be
possible to compare values in IO in a reasonable sense.

Tom

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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Richard A. O'Keefe

On 7/08/2013, at 2:10 PM, damodar kulkarni wrote:

 I bet you can find an abundance of C programmers who think that
 strcmp is an intuitive name for string comparison (rather than compression, 
 say).
 
 But at least, 'strcmp' is not a common English language term, to have 
 acquired some unintentional 'intuition' by being familiar with it even in our 
 daily life. The Haskell terms, say, 'return' and 'lift', on the other hand, 
 do have usage in common English, so even a person with _no_ programming 
 background would have acquired some unintentional 'intuition' by being 
 familiar with them.

Lift is - a brand of soft drink, the thing Americans call an elevator, 
a thing put in your shoes seem taller, and a free ride, amongst other things.
As a verb, it can mean to kick something.

To find lift intuitive, you have to be familiar with the *mathematical*
idiom of lifting a value from one space to another via some sort of
injection.  Fair enough, but this *still* counts as an example of
intuitive = familiar, because this is *not* a sense of lift that is
familiar to undergraduate and masters computing students unless they have
taken rather more mathematics papers than most of them have.

If you're familiar with *English* rather than, say, the C family of
programming languages, return isn't _that_ bad, there is certainly
nothing about the word that suggests providing a value.  I once tried
to propose a C-style 'return' statement to some people who were
designing a programming language, before I or they had ever heard of
C, and they flatly rejected it.  Months later I found out that this
was because they were looking for something that did not just resume
the caller but also provided a value, and when I protested that that's
exactly what 'return' did in the languages I proposed stealing from,
they -- being familiar with Fortran -- said that it had never occurred
to them that 'return' could have anything to with providing a value.

It is intuitive has no other discernable meaning than *I* am familiar with 
it,
or something very much like it.

_That's_ the point I want to make.  *Whatever* anyone uses for Haskell's
return, many people are bound to find it unintuitive.  Choose a name
on any grounds but that.



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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Jerzy Karczmarczuk

Richard A. O'Keefe :

Haskell has*trained*  my intuition to
see 'putStrLn Hi' as a pure value; it's not the thing itself that has effects,
but its interpretation by an outer engine, just as my magnetic card key has by
itself no power to open doors, but the magnetic reader that looks at the card
_does_.
I am the last here who would quarrel with Richard O'K., but I firmly 
believe that such reasoning is a Pandora box.


The King, the government, the Pope, etc. have no power, only the 
interpretation of their decrees by outer agents _does_ things.


Saying that the Justice of the country X is lousy is a harmful abuse. 
Our Justice is good, only its interpretation by some incompetent 
traitors gave rise to all these calamitous events.


You see what I mean?... Are we going to switch now to the Mind-Body dilemma?

==

BTW. Saying that 5 is a pure value means only that the whole of the 
underlying system treats it as such. The object 5 couldn't care less. 
It even doesn't know that in some programming language it is equivalent 
to an action which puts it on the evaluation stack.


That's why for me the purity (while teaching I try to avoid this word) 
means simply that whatever you do with the object, it won't fire a 
magic process. As Richard, I do not claim that this is right, but it 
surely facilitated my teaching of Haskell. My students have already more 
than enough of my /philosophie de pacotille/...


Jerzy Karczmarczuk

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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Alberto G. Corona
One of the surprising things of Haskell is how little effort is done in
order to confer meaning to the names. That happens also in the case of the
mathematical language. Often they have a single letter. The reason is that
their meaning is completely defined by their signature and their
properties. And this is possible because Haskell has a strong and
polymorphic type system. In other languages, either this is not possible or
the libraries have little polymorphism, so the names can be more concrete.


return :: (Monad m) = a - m a

The meaning is in the signature. We can opt between keeping the name as a
short mnemonic of the signature or else we can adhere to the C tradition:

return === monad_m___a__m_a

or the Java Tradition

return
=MonadFactory.liftSomethingSometimesPureButInSomeCasesTheResultIsAlsoPure


2013/8/7 Richard A. O'Keefe o...@cs.otago.ac.nz


 On 7/08/2013, at 2:10 PM, damodar kulkarni wrote:

  I bet you can find an abundance of C programmers who think that
  strcmp is an intuitive name for string comparison (rather than
 compression, say).
 
  But at least, 'strcmp' is not a common English language term, to have
 acquired some unintentional 'intuition' by being familiar with it even in
 our daily life. The Haskell terms, say, 'return' and 'lift', on the other
 hand, do have usage in common English, so even a person with _no_
 programming background would have acquired some unintentional 'intuition'
 by being familiar with them.

 Lift is - a brand of soft drink, the thing Americans call an elevator,
 a thing put in your shoes seem taller, and a free ride, amongst other
 things.
 As a verb, it can mean to kick something.

 To find lift intuitive, you have to be familiar with the *mathematical*
 idiom of lifting a value from one space to another via some sort of
 injection.  Fair enough, but this *still* counts as an example of
 intuitive = familiar, because this is *not* a sense of lift that is
 familiar to undergraduate and masters computing students unless they have
 taken rather more mathematics papers than most of them have.

 If you're familiar with *English* rather than, say, the C family of
 programming languages, return isn't _that_ bad, there is certainly
 nothing about the word that suggests providing a value.  I once tried
 to propose a C-style 'return' statement to some people who were
 designing a programming language, before I or they had ever heard of
 C, and they flatly rejected it.  Months later I found out that this
 was because they were looking for something that did not just resume
 the caller but also provided a value, and when I protested that that's
 exactly what 'return' did in the languages I proposed stealing from,
 they -- being familiar with Fortran -- said that it had never occurred
 to them that 'return' could have anything to with providing a value.

 It is intuitive has no other discernable meaning than *I* am familiar
 with it,
 or something very much like it.

 _That's_ the point I want to make.  *Whatever* anyone uses for Haskell's
 return, many people are bound to find it unintuitive.  Choose a name
 on any grounds but that.



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




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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Alberto G. Corona
Fine reasoning.

Pure means incorruptible. It means that a pure result can be reused again
and again -like the gold or silver- while an impure result must be
re-created whenever it must be used. The metaphor is natural and I guess
that the use of pure (rather than referential transparent) is informal, but
as unavoidable as useful.  By the way, there are deeper considerations
here: To deal with pure values, like incorruptible stuff, like gold implies
lower information costs and that´s one of the reasons why they are valuable.

In this sense, we can give a positive meaning to unsafePerformIO and change
its name to  purify or  even pasteurize or lyophilize ;)






2013/8/7 Jerzy Karczmarczuk jerzy.karczmarc...@unicaen.fr

  Richard A. O'Keefe :

 Haskell has **trained** my intuition to
 see 'putStrLn Hi' as a pure value; it's not the thing itself that has 
 effects,
 but its interpretation by an outer engine, just as my magnetic card key has by
 itself no power to open doors, but the magnetic reader that looks at the 
 card_does_.

  I am the last here who would quarrel with Richard O'K., but I firmly
 believe that such reasoning is a Pandora box.

 The King, the government, the Pope, etc. have no power, only the
 interpretation of their decrees by outer agents _does_ things.

 Saying that the Justice of the country X is lousy is a harmful abuse. Our
 Justice is good, only its interpretation by some incompetent traitors gave
 rise to all these calamitous events.

 You see what I mean?... Are we going to switch now to the Mind-Body
 dilemma?

 ==

 BTW. Saying that 5 is a pure value means only that the whole of the
 underlying system treats it as such. The object 5 couldn't care less. It
 even doesn't know that in some programming language it is equivalent to an
 action which puts it on the evaluation stack.

 That's why for me the purity (while teaching I try to avoid this word)
 means simply that whatever you do with the object, it won't fire a magic
 process. As Richard, I do not claim that this is right, but it surely
 facilitated my teaching of Haskell. My students have already more than
 enough of my /philosophie de pacotille/...

 Jerzy Karczmarczuk


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




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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread damodar kulkarni
 It is intuitive has no other discernable meaning than *I* am familiar
 with it, or something very much like it.


Thanks for pointing this out, I was not able to point my thoughts in this
direction.

But I still have a doubt: if my familiarity doesn't come in the form of
some analogy, then my acquired intuition about it would be of little
use. In fact, it may well be misleading. Am I correct?

If so, the best we can hope is the name-giver to describe, as explicitly as
possible, the analogy (sort of a thought process) he/she had had in
his/her mind while giving a particular name to a given concept?
It will help others to share *at least some amount of* of intuition
(analogy) the originator had had.

Are such thoughts documented in this case?

Thanks and regards,
-Damodar Kulkarni


On Wed, Aug 7, 2013 at 11:37 AM, Richard A. O'Keefe o...@cs.otago.ac.nzwrote:


 On 7/08/2013, at 2:10 PM, damodar kulkarni wrote:

  I bet you can find an abundance of C programmers who think that
  strcmp is an intuitive name for string comparison (rather than
 compression, say).
 
  But at least, 'strcmp' is not a common English language term, to have
 acquired some unintentional 'intuition' by being familiar with it even in
 our daily life. The Haskell terms, say, 'return' and 'lift', on the other
 hand, do have usage in common English, so even a person with _no_
 programming background would have acquired some unintentional 'intuition'
 by being familiar with them.

 Lift is - a brand of soft drink, the thing Americans call an elevator,
 a thing put in your shoes seem taller, and a free ride, amongst other
 things.
 As a verb, it can mean to kick something.

 To find lift intuitive, you have to be familiar with the *mathematical*
 idiom of lifting a value from one space to another via some sort of
 injection.  Fair enough, but this *still* counts as an example of
 intuitive = familiar, because this is *not* a sense of lift that is
 familiar to undergraduate and masters computing students unless they have
 taken rather more mathematics papers than most of them have.

 If you're familiar with *English* rather than, say, the C family of
 programming languages, return isn't _that_ bad, there is certainly
 nothing about the word that suggests providing a value.  I once tried
 to propose a C-style 'return' statement to some people who were
 designing a programming language, before I or they had ever heard of
 C, and they flatly rejected it.  Months later I found out that this
 was because they were looking for something that did not just resume
 the caller but also provided a value, and when I protested that that's
 exactly what 'return' did in the languages I proposed stealing from,
 they -- being familiar with Fortran -- said that it had never occurred
 to them that 'return' could have anything to with providing a value.

 It is intuitive has no other discernable meaning than *I* am familiar
 with it,
 or something very much like it.

 _That's_ the point I want to make.  *Whatever* anyone uses for Haskell's
 return, many people are bound to find it unintuitive.  Choose a name
 on any grounds but that.



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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Donn Cave
quoth Richard A. O'Keefe,
...
 If you're familiar with *English* rather than, say, the C family of
 programming languages, return isn't _that_ bad, there is certainly
 nothing about the word that suggests providing a value.

The RFC822 headers of your email suggest that you use a Macintosh computer,
so apart from the apparently disputable question of whether you're familiar
with English, you have the same online dictionary as mine.  Second definition:
give, put, or send (something) back to a place or person, with examples
she returned his kiss, usage from tennis and football, verdicts, etc.
Third definition:  yield or make a profit, fourth (re)elect a person or party.
Return is all about providing a value, in English.

When a term like return is used in a computer programming language in
a sense that confounds any prior expectation based on English or other
programming languages, that's the opposite of intuitive.  It is what
it is, and it's silly to talk about changing it at this point, but that
doesn't mean that we have to turn the notion of intuitive on its head.

Donn

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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread David Thomas
 2. This is the only way you can evaluate your pure value, and because of
 the monadic chaining, you cannot do it twice, you cannot re-evaluate it.


I'm sure there is a sense in which this is true, but I'm not seeing it.
How would you describe what's going on here?

twice :: IO () - IO ()
twice x = x  x

main = twice $ putStrLn foo

I would call that evaluating x twice (incidentally creating two separate
evaluations of one pure action description), but I'd like to better see
your perspective here.



Regarding this issue generally, I feel like everyone's climbed on their
particular war horses when someone sounded the PURITY trumpet, when *I
don't think this is the kind of purity Applicative is talking about* -
different things can be pure in different ways.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread David Thomas
Return is all about providing a value *when used transitively*.  When used
intransitively, it's about moving yourself.  There's nothing about the
latter sense that implies providing a value.

Which is not to say Richard did not overstate the case - return needn't
necessarily (in English) suggest providing a value would be more correct,
but isn't that far from a charitable interpretation of what he'd said.


On Wed, Aug 7, 2013 at 7:56 AM, Donn Cave d...@avvanta.com wrote:

 quoth Richard A. O'Keefe,
 ...
  If you're familiar with *English* rather than, say, the C family of
  programming languages, return isn't _that_ bad, there is certainly
  nothing about the word that suggests providing a value.

 The RFC822 headers of your email suggest that you use a Macintosh computer,
 so apart from the apparently disputable question of whether you're familiar
 with English, you have the same online dictionary as mine.  Second
 definition:
 give, put, or send (something) back to a place or person, with examples
 she returned his kiss, usage from tennis and football, verdicts, etc.
 Third definition:  yield or make a profit, fourth (re)elect a person or
 party.
 Return is all about providing a value, in English.

 When a term like return is used in a computer programming language in
 a sense that confounds any prior expectation based on English or other
 programming languages, that's the opposite of intuitive.  It is what
 it is, and it's silly to talk about changing it at this point, but that
 doesn't mean that we have to turn the notion of intuitive on its head.

 Donn

 ___
 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] Alternative name for return

2013-08-07 Thread Joe Quinn

On 8/7/2013 11:00 AM, David Thomas wrote:

twice :: IO () - IO ()
twice x = x  x

I would call that evaluating x twice (incidentally creating two 
separate evaluations of one pure action description), but I'd like to 
better see your perspective here.


x is only evaluated once, but /executed/ twice. For IO, that means 
magic. For other types, it means different things. For Identity, twice = id!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Bardur Arantsson
On 2013-08-07 22:38, Joe Quinn wrote:
 On 8/7/2013 11:00 AM, David Thomas wrote:
 twice :: IO () - IO ()
 twice x = x  x

 I would call that evaluating x twice (incidentally creating two
 separate evaluations of one pure action description), but I'd like to
 better see your perspective here.
 
 x is only evaluated once, but /executed/ twice. For IO, that means
 magic. For other types, it means different things. For Identity, twice =
 id!
 

Your point being? x is the same thing regardless of how many times you
run it.




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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Jerzy Karczmarczuk

Bardur Arantsson comments the comment of Joe Quinn:

On 8/7/2013 11:00 AM, David Thomas wrote:

twice :: IO () - IO ()
twice x = x  x

I would call that evaluating x twice (incidentally creating two
separate evaluations of one pure action description), but I'd like to
better see your perspective here.


x is only evaluated once, but/executed/  twice. For IO, that means
magic. For other types, it means different things. For Identity, twice =
id!


Your point being? x is the same thing regardless of how many times you
run it.


What do you mean by the same thing? You cannot compare 'them' in any 
reasonable sense.


This, the impossibility to check putStr c == putStr c, is btw, a 
refutation of the claim by Tom Ellis that you can do even less with (). 
The void object is an instance of the Eq and Ord classes. And of Show as 
well.


You make the distinction between evaluate, and  execute or run, 
etc. This is not functional. Your program doesn't run anything, it 
applies (=) (or equivalent) to an IO (...) object. This is the only 
practical evaluation of it, otherwise it can  be passed (or duplicated 
as above). But you cannot apply bind twice to the same instance of it 
(in fact, as I said above, the same instance  is a bit suspicious 
concept...).


The running or execution takes place outside of your program. In 
such a way Richard O'Keefe and I converge... That's why I say that the 
concept of purity is meaningless in the discussed context. It is a kind 
of counterfeit notion, inherited from pure functions to something 
which belongs to two different worlds.


Jerzy Karczmarczuk

PS. I believe that some impure remarks about the familiarity of X or Y 
with English do not belong to this forum.



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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Richard A. O'Keefe

On 7/08/2013, at 9:17 PM, Jerzy Karczmarczuk wrote:
 I am the last here who would quarrel with Richard O'K., but I firmly believe 
 that such reasoning is a Pandora box. 
 
 The King, the government, the Pope, etc. have no power, only the 
 interpretation of their decrees by outer agents _does_ things.

I regard the analogy as flawed because my sovereign
[Her Majesty Elizabeth the Second, by the Grace of God Queen of New Zealand
 and Her Other Realms and Territories, Head of the Commonwealth, Defender
 of the Faith/Her Majesty Elizabeth the Second, by the Grace of God, Queen
 of Australia and Her other Realms and Territories, Head of the Commonwealth
 (I have dual citizenship, so she gets to be my Queen twice)
] is a moral agent, so is the Bishop of Rome, and so are my Prime Ministers
John Key and Kevin Rudd.  These people are agents in their own right; they
and the people who follow their orders are _things of the same kind_.

Maybe the analogy isn't that flawed. Julia Gillard found out that when
enough people stopped saying yes to her, her power disappeared like
morning dew.  The official teaching of the Roman church is that
contraception is not OK, yet the 2013 birth rates for Spain and Portugal
were about 1.5.  It really does look as though the Pope's power does rest
on the consent of the people: if people don't like what he tells them,
they don't do it.

I leave it to other readers with a misspent youth to supply the name and title
of the Science Fiction story in which FIW is the political key.

Analogies are helpful if they help.  Comparing IO 'actions' to plain old data
like a magnetic card key and the Haskell environment to the reader helped _me_;
if it helps no-one else, forget it.


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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Richard A. O'Keefe

On 8/08/2013, at 2:09 AM, damodar kulkarni wrote:
 Thanks for pointing this out, I was not able to point my thoughts in this 
 direction.
 
 But I still have a doubt: if my familiarity doesn't come in the form of some 
 analogy, then my acquired intuition about it would be of little use. In 
 fact, it may well be misleading. Am I correct?

Very much so.  This is why I despise, detest, and loathe as abominations
programming languages in which string concatenation is written +.
(If you want a binary operation which is associative and has an identity
but doesn't commute, the product lies ready to hand, and the repeated
product (exponentiation) is actually _useful_ for strings.  It's still
better to use a non-arithmetic operator, as PL/I, Fortran, Ada, and Haskell do.)

 If so, the best we can hope is the name-giver to describe, as explicitly as 
 possible, the analogy (sort of a thought process) he/she had had in his/her 
 mind while giving a particular name to a given concept?

Complete agreement from me.

For what it's worth, return can mean to shift back to a previous topic,
so it's not _that_ crazy for when you've switched from a monadic context
to a pure context and are now switching back.


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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Timon Gehr

On 08/08/2013 01:19 AM, Jerzy Karczmarczuk wrote:

Bardur Arantsson comments the comment of Joe Quinn:

On 8/7/2013 11:00 AM, David Thomas wrote:

twice :: IO () - IO ()
twice x = x  x

I would call that evaluating x twice (incidentally creating two
separate evaluations of one pure action description), but I'd like to
better see your perspective here.


x is only evaluated once, but/executed/  twice. For IO, that means
magic. For other types, it means different things. For Identity, twice =
id!


Your point being? x is the same thing regardless of how many times you
run it.


What do you mean by the same thing? You cannot compare 'them' in any
reasonable sense.
...


http://en.wikipedia.org/wiki/Identity_of_indiscernibles

(He is reasoning _about_ the language and not _within_ the language 
because Haskell does not support very powerful reasoning internally.)



...
You make the distinction between evaluate,


Which essentially means applying reduction rules to an expression until 
the result is a value.



and  execute or run, etc. This is not functional.


How would you know?


Your program doesn't run anything, it
applies (=) (or equivalent) to an IO (...) object. This is the only
practical evaluation of it, otherwise it can  be passed (or duplicated
as above). But you cannot apply bind twice to the same instance of it
(in fact, as I said above, the same instance  is a bit suspicious
concept...).
...


Indeed, but you didn't say that above.


The running or execution takes place outside of your program. In
such a way Richard O'Keefe and I converge... That's why I say that the
concept of purity is meaningless in the discussed context.


Not meaningless, but redundant. The point of having a purely functional 
programming language is to have reasoning based on purity be universally 
applicable.



It is a kind of counterfeit notion, inherited from pure functions to something
which belongs to two different worlds.
...


'putStr c' is a pure value.

On the other hand:

'unsafePerformIO (putStr c)' is not a pure value.

(But this expression does not exist in standard Haskell. unsafePerformIO 
unquotes the action. You may be confusing the quoted and unquoted 
versions.)



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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Richard A. O'Keefe

On 8/08/2013, at 2:56 AM, Donn Cave wrote:
 The RFC822 headers of your email suggest that you use a Macintosh computer,
 so apart from the apparently disputable question of whether you're familiar
 with English, you have the same online dictionary as mine.

My department has an electronic subscription to the OED.

 Second definition:
 give, put, or send (something) back to a place or person, with examples
 she returned his kiss, usage from tennis and football, verdicts, etc.
 Third definition:  yield or make a profit, fourth (re)elect a person or 
 party.
 Return is all about providing a value, in English.

Check the OED.  Most of its meaning are about _turning back_,
_resuming_, _reverting_.  Yielding or making a profit is not at
all about providing a value, but about money going out AND
COMING BACK.  It's the coming back part that makes it a return.

value occurs twice in OED 'return, v.1, in neither case
referring to providing a value.
OED re-turn, v.2 has value once, again not referring to
providing a value (in fact, to detecting possible theft).
OED return, n has the fact or an instance of bringing value
in exchange for effort or investment, where the salient part
is IN EXCHANGE FOR:  effort going out, value COMING BACK.
There are two other similar senses, out of I don't know how
many senses (because I lost count after 80).

A return can be a reply, answer or retort (as in the Fool's
Marry, it was a sharp retort in one of the Discworld novels,
when an alchemist's vessel exploded), a summary of a [cricket]
play's bowling or batting performance, a response to a demand,
a wing or side of a building, or a side street, among many
other things.

In all of the senses, the underlying idea is not provision of a
value, but going, turning, or bending back.

 When a term like return is used in a computer programming language in
 a sense that confounds any prior expectation based on English or other
 programming languages, that's the opposite of intuitive.

OK, so when in the past someone met RETURN in their second programming
language, what had their experience taught them to expect?

ISO/IEC 1989:20xx CD 1.2 (E)

14.9.32 RETURN statement

The RETURN statement obtains either sorted records from the final
phase of a sort operation or merged records during a merge operation.

14.9.32.1 General format

RETURN file-name-1 RECORD [ INTO identifier-1 ]
   AT END imperative-statement-1
[ NOT AT END imperative-statement-2 ]
  [ END-RETURN ]

This is a somewhat more elaborate form of a statement which has been
present in COBOL since at least 1974 and probably longer.  The latest
estimate I've seen is that four thousand million lines of new COBOL
are added every year.

Operationally, the COBOL RETURN statement is more like a READ than
anything else.




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


Re: [Haskell-cafe] Alternative name for return

2013-08-07 Thread Donn Cave
quoth Richard A. O'Keefe

 Check the OED.  Most of its meaning are about _turning back_,
 _resuming_, _reverting_.  Yielding or making a profit is not at
 all about providing a value, but about money going out AND
 COMING BACK.  It's the coming back part that makes it a return.

Yes.  Return means 'go/come back';  used transitively, it means
'go/come back with _'.

 value occurs twice in OED 'return, v.1, in neither case
 referring to providing a value.

But of course, the word value as we use it is specific to our
application, i.e. it's computer jargon, with an English meaning
that's more like thing, object, datum.  Wouldn't look for
value to convey this meaning in an OED definition of return.

 In all of the senses, the underlying idea is not provision of a
 value, but going, turning, or bending back.

[Which is actually what the Haskell return fails to do.]

What goes/turns/bends back?  When used intransitively, the subject;
used transitively, the object, our value.

I'll give you the COBOL example, it's no better the Haskell
return.  FORTRAN makes a good deal more sense for an English
speaker but uses indirect object semantically - RETURN 2
means return to the second alternate return specified by the
caller.  (I never used that feature, so don't take my word
for it, check your manual before using it!)

Donn

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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Tarik ÖZKANLI
next, carry, feed, roll



On 6 August 2013 08:37, KC kc1...@gmail.com wrote:

 I thought a pure value was being returned from the monad. :)


 On Mon, Aug 5, 2013 at 10:32 PM, Christian Sternagel 
 c.sterna...@gmail.com wrote:

 Dear Jurriën.

 personally, I like lift (which is of course already occupied in
 Haskell), since an arbitrary value is lifted into a monad. (The
 literature sometimes uses unit.)

 cheers

 chris


 On 08/06/2013 02:14 PM, J. Stutterheim wrote:

 Dear Cafe,


 Suppose we now have the opportunity to change the name of the `return`
 function in Monad, what would be a better  name for it? (for some
 definition of better)

 N.B. I am _not_ proposing that we actually change the name of `return`.
 I do currently have the opportunity to pick names for common functions in a
 non-Haskell related project, so I was wondering if there perhaps is a
 better name for `return`.


 - Jurriën
 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




 --
 --
 Regards,
 KC

 ___
 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] Alternative name for return

2013-08-06 Thread J. Stutterheim
Thanks Chris. Yes, I like lift as well, because I find it a rather intuitive 
name. Unfortunately, as you say, it is already a commonly used name as well, 
which might make it slightly confusing.

When I hear `unit` I immediately think about generic programming, not so much 
about monads. Can you perhaps explain the intuition behind `unit` as an 
alternative to `return` in the context of monads?

- Jurriën

On 6 Aug 2013, at 07:32, Christian Sternagel c.sterna...@gmail.com wrote:

 Dear Jurriën.
 
 personally, I like lift (which is of course already occupied in Haskell), 
 since an arbitrary value is lifted into a monad. (The literature sometimes 
 uses unit.)
 
 cheers
 
 chris
 
 On 08/06/2013 02:14 PM, J. Stutterheim wrote:
 Dear Cafe,
 
 
 Suppose we now have the opportunity to change the name of the `return` 
 function in Monad, what would be a better  name for it? (for some 
 definition of better)
 
 N.B. I am _not_ proposing that we actually change the name of `return`. I do 
 currently have the opportunity to pick names for common functions in a 
 non-Haskell related project, so I was wondering if there perhaps is a better 
 name for `return`.
 
 
 - Jurriën
 ___
 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



signature.asc
Description: Message signed with OpenPGP using GPGMail
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread J. Stutterheim
Hi Tarik,

Could you motivate the choice for these names? Thanks!

On 6 Aug 2013, at 08:14, Tarik ÖZKANLI tozkanli2...@gmail.com wrote:

 next, carry, feed, roll
 
 
 
 On 6 August 2013 08:37, KC kc1...@gmail.com wrote:
 I thought a pure value was being returned from the monad. :)
 
 
 On Mon, Aug 5, 2013 at 10:32 PM, Christian Sternagel c.sterna...@gmail.com 
 wrote:
 Dear Jurriën.
 
 personally, I like lift (which is of course already occupied in Haskell), 
 since an arbitrary value is lifted into a monad. (The literature sometimes 
 uses unit.)
 
 cheers
 
 chris
 
 
 On 08/06/2013 02:14 PM, J. Stutterheim wrote:
 Dear Cafe,
 
 
 Suppose we now have the opportunity to change the name of the `return` 
 function in Monad, what would be a better  name for it? (for some 
 definition of better)
 
 N.B. I am _not_ proposing that we actually change the name of `return`. I do 
 currently have the opportunity to pick names for common functions in a 
 non-Haskell related project, so I was wondering if there perhaps is a better 
 name for `return`.
 
 
 - Jurriën
 ___
 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
 
 
 
 -- 
 --
 Regards,
 KC
 
 ___
 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



signature.asc
Description: Message signed with OpenPGP using GPGMail
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Erik Hesselink
What about `pure`? It's already used in applicative, and has the
motivation that it's embedding a pure value in some context. Since I
don't know the details of your project, I don't know if you need two
names (one for the applicative version, and one for the monadic
version).

Erik

On Tue, Aug 6, 2013 at 7:14 AM, J. Stutterheim j.stutterh...@me.com wrote:
 Dear Cafe,


 Suppose we now have the opportunity to change the name of the `return` 
 function in Monad, what would be a better  name for it? (for some 
 definition of better)

 N.B. I am _not_ proposing that we actually change the name of `return`. I do 
 currently have the opportunity to pick names for common functions in a 
 non-Haskell related project, so I was wondering if there perhaps is a better 
 name for `return`.


 - Jurriën
 ___
 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] Alternative name for return

2013-08-06 Thread J. Stutterheim
I have to admit that I am a bit torn about using `pure`. On the one hand, if 
you actually have a pure value, it feels pretty intuitive to me. But what about

  pure (putStrLn Hi)

`putStrLn Hi` is not a pure value... Or is there another way to interpret the 
word pure in this context?

As for Applicative, I can add (and have added) the Applicative constraint in 
the Monad definition for my project, so I will also have to write an 
Applicative instance for my monads.


- Jurriën

On 6 Aug 2013, at 09:50, Erik Hesselink hessel...@gmail.com wrote:

 What about `pure`? It's already used in applicative, and has the
 motivation that it's embedding a pure value in some context. Since I
 don't know the details of your project, I don't know if you need two
 names (one for the applicative version, and one for the monadic
 version).
 
 Erik
 
 On Tue, Aug 6, 2013 at 7:14 AM, J. Stutterheim j.stutterh...@me.com wrote:
 Dear Cafe,
 
 
 Suppose we now have the opportunity to change the name of the `return` 
 function in Monad, what would be a better  name for it? (for some 
 definition of better)
 
 N.B. I am _not_ proposing that we actually change the name of `return`. I do 
 currently have the opportunity to pick names for common functions in a 
 non-Haskell related project, so I was wondering if there perhaps is a better 
 name for `return`.
 
 
 - Jurriën
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



signature.asc
Description: Message signed with OpenPGP using GPGMail
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Karol Samborski
What about 'pack'?

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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Colin Adams
What about 'inject'?


On 6 August 2013 09:09, Karol Samborski edv.ka...@gmail.com wrote:

 What about 'pack'?

 Best,
 Karol

 ___
 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] Alternative name for return

2013-08-06 Thread Tom Ellis
On Tue, Aug 06, 2013 at 10:03:04AM +0200, J. Stutterheim wrote:
 `putStrLn Hi` is not a pure value...

Why not?

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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Tobias Dammers
It is a pure value in the context of the outer monad (the one you wrap it
in). I'd say pure is still appropriate.
On Aug 6, 2013 10:14 AM, Tom Ellis 
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:

 On Tue, Aug 06, 2013 at 10:03:04AM +0200, J. Stutterheim wrote:
  `putStrLn Hi` is not a pure value...

 Why not?

 ___
 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] Alternative name for return

2013-08-06 Thread Lyndon Maydwell
What about promote ?


On Tue, Aug 6, 2013 at 6:15 PM, Tom Ellis 
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:

 On Tue, Aug 06, 2013 at 10:03:04AM +0200, J. Stutterheim wrote:
  `putStrLn Hi` is not a pure value...

 Why not?

 ___
 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] Alternative name for return

2013-08-06 Thread Christian Sternagel

On 08/06/2013 04:30 PM, J. Stutterheim wrote:

Thanks Chris. Yes, I like lift as well, because I find it a rather intuitive 
name. Unfortunately, as you say, it is already a commonly used name as well, 
which might make it slightly confusing.

When I hear `unit` I immediately think about generic programming, not so much 
about monads. Can you perhaps explain the intuition behind `unit` as an 
alternative to `return` in the context of monads?
Probably because of the monad laws, where `return` is a unit (in the 
mathematical sense) for the `bind` operation. - chris


- Jurriën

On 6 Aug 2013, at 07:32, Christian Sternagel c.sterna...@gmail.com wrote:


Dear Jurriën.

personally, I like lift (which is of course already occupied in Haskell), since an arbitrary 
value is lifted into a monad. (The literature sometimes uses unit.)

cheers

chris

On 08/06/2013 02:14 PM, J. Stutterheim wrote:

Dear Cafe,


Suppose we now have the opportunity to change the name of the `return` function in Monad, 
what would be a better  name for it? (for some definition of better)

N.B. I am _not_ proposing that we actually change the name of `return`. I do 
currently have the opportunity to pick names for common functions in a 
non-Haskell related project, so I was wondering if there perhaps is a better 
name for `return`.


- Jurriën
___
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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Jerzy Karczmarczuk

What about X, Y, Z, ...

We have seen this discussion already a long time ago. The terms unit 
and result have been proposed. And others. Somebody (I forgot who) 
advocated even the name monad in this context. And this might have 
continued forever...


With all my respect, I see that Haskell reached finally the Noble Domain 
of Philosophy. I mean, instead of discussing concepts, people begin to 
discuss names.
And since for some, even IO () is a pure value, I suspect that the 
next round will rekindle the discussion on the word pure...


Jerzy Karczmarczuk



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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Adam Gundry
Hi,

On 06/08/13 06:14, J. Stutterheim wrote:
 Suppose we now have the opportunity to change the name of the
 `return` function in Monad, what would be a better  name for it?
 (for some definition of better)

Rather than proposing a different name, I'm going to challenge the
premise of your question. Perhaps it would be better if `return` had no
name at all. Consider the following:

return f `ap` s `ap` t

f $ s * t

do { sv - s
   ; tv - t
   ; return (f sv tv) }

These are all different ways of spelling

f s t

plus the necessary applicative or monadic bureaucracy. But why couldn't
we write just the plain application, and let the type system deal with
the plumbing of effects?

I realise that this may be too open a research area for your project...


 N.B. I am _not_ proposing that we actually change the name of
 `return`. I do currently have the opportunity to pick names for
 common functions in a non-Haskell related project, so I was wondering
 if there perhaps is a better name for `return`.

I don't think the choice of name matters. I do think it should be short.
Preferably invisible.

Adam

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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread J. Stutterheim
Hi Adam,

Thank you for an interesting thought; an invisible name might actually be on of 
the better solutions, although you are right in that your suggestion is a bit 
too open for my current project.

Actually, I believe that naming is very important. My goal is to have the 
average programmer (i.e. someone without a post-bachelor degree) look at the 
code and get an intuitive feel of what is going on. So in reply to Jerzy, I do 
want to encourage the discussion in the Noble Domain of Philosophy and I also 
want to repeat that I am not proposing to change Haskell or Haskell libraries 
(I am working with another language altogether), so don't fear ;)


- Jurriën

On 6 Aug 2013, at 10:46, Adam Gundry adam.gun...@strath.ac.uk wrote:

 Hi,
 
 On 06/08/13 06:14, J. Stutterheim wrote:
 Suppose we now have the opportunity to change the name of the
 `return` function in Monad, what would be a better  name for it?
 (for some definition of better)
 
 Rather than proposing a different name, I'm going to challenge the
 premise of your question. Perhaps it would be better if `return` had no
 name at all. Consider the following:
 
return f `ap` s `ap` t
 
f $ s * t
 
do { sv - s
   ; tv - t
   ; return (f sv tv) }
 
 These are all different ways of spelling
 
f s t
 
 plus the necessary applicative or monadic bureaucracy. But why couldn't
 we write just the plain application, and let the type system deal with
 the plumbing of effects?
 
 I realise that this may be too open a research area for your project...
 
 
 N.B. I am _not_ proposing that we actually change the name of
 `return`. I do currently have the opportunity to pick names for
 common functions in a non-Haskell related project, so I was wondering
 if there perhaps is a better name for `return`.
 
 I don't think the choice of name matters. I do think it should be short.
 Preferably invisible.
 
 Adam



signature.asc
Description: Message signed with OpenPGP using GPGMail
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread J. Stutterheim
That argument makes sense, although I find it a bit counter-intuitive still. If 
I saw the function `pure` for the first time, my first impression (however 
wrong it may be) would be that it takes a pure value (regardless of context) 
and does something with it. Applying `pure` to an IO operation goes against 
that intuition.

Looking at the type of `return :: a - m a, there are several slightly more 
intuitive (to me) options in this discussion already:

lift: the value `a` is lifted into the monad `m`
pack: the value `a` is packed into the monad `m`
wrap: the value `a` is wrapped in the monad `m`
inject: the value `a` is injected into the monad `m`
promote: the value `a` is promoted to a monad `m a`


On 6 Aug 2013, at 10:16, Tobias Dammers tdamm...@gmail.com wrote:

 It is a pure value in the context of the outer monad (the one you wrap it 
 in). I'd say pure is still appropriate.
 
 On Aug 6, 2013 10:14 AM, Tom Ellis 
 tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
 On Tue, Aug 06, 2013 at 10:03:04AM +0200, J. Stutterheim wrote:
  `putStrLn Hi` is not a pure value...
 
 Why not?
 
 ___
 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



signature.asc
Description: Message signed with OpenPGP using GPGMail
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Jerzy Karczmarczuk

Le 06/08/2013 11:01, J. Stutterheim a écrit :

... So in reply to Jerzy, I do want to encourage the discussion in the Noble Domain 
of Philosophy and I also want to repeat that I am not proposing to change Haskell 
or Haskell libraries


Jurriën, I taught Haskell for several years. I saw the disgraceful confusion in heads of 
my students whose previous programming experience was based on Python, and who learned 
Haskell and Java in parallel. So, I won't claim that names are irrelevant. And 
return in particular.

However, my personal philosophy is the following: accept the fact that words in one language -- formal or 
natural -- mean something different than in another one. [[In French the word file in computerese is 
queue in English; this is in fact a French word meaning tail in English, and I have several 
dozens of such examples... And so what?...]]

It is good to choose consciously some good names while elaborating a standard. But 
getting back to it after several years, is -- for me -- a waste of time. This, 
unfortunately, pollutes the true philosophy as well. I believe that at least 80% of the 
progress in the philosophy of religions belongs to the linguistic domain.

The anglosaxons corupted the word semantics, used in a pejorative sense: 
discussion about superficialities, the words, not the concepts, while the true 
semantics is about the true sense.

So, sorry for being sarcastic, or even cynical in my previous post, but I 
sincerely think that oldies are oldies, let them be, and work more on issues 
that are still evolving.

All the best.

Jerzy



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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Marc Ziegert
very insightful, thx Jerzy.

imho, this is a good reason not to use already known words like 
lift,return,inject,pure etc. while still using the word Monad. (this is 
something that bothered me for years.)
no one -of those who say no one- does understand Monads because it does not 
explain itself nor suggest its utility, while the other words probably tend to 
cause a very false sense of understanding.

so, long talk few suggestions

if it should be about Monads as a concept, i'd suggest
1) unit and counit for Monads and Comonads. (this is my personal favorite 
choice, probably because i did learn to understand Monads by reading a paper 
about Comonads.)

if it should be more selfexplaining for the average coder, then
2) let,set,put,be,:= or return allowed only at end of script - use let 
anywhere else for ScriptLike (aka Monad)

as a strict version of return, i'd suggest something that may somehow fit into 
1 and 2:
3) eval = Control.Exception.evaluate :: a - IO a


regards
- marc




 Gesendet: Dienstag, 06. August 2013 um 11:43 Uhr
 Von: Jerzy Karczmarczuk jerzy.karczmarc...@unicaen.fr
 An: haskell-cafe@haskell.org
 Betreff: Re: [Haskell-cafe] Alternative name for return

 Le 06/08/2013 11:01, J. Stutterheim a écrit :
  ... So in reply to Jerzy, I do want to encourage the discussion in the 
  Noble Domain of Philosophy and I also want to repeat that I am not 
  proposing to change Haskell or Haskell libraries
 
 Jurriën, I taught Haskell for several years. I saw the disgraceful confusion 
 in heads of my students whose previous programming experience was based on 
 Python, and who learned Haskell and Java in parallel. So, I won't claim that 
 names are irrelevant. And return in particular.
 
 However, my personal philosophy is the following: accept the fact that 
 words in one language -- formal or natural -- mean something different than 
 in another one. [[In French the word file in computerese is queue in 
 English; this is in fact a French word meaning tail in English, and I have 
 several dozens of such examples... And so what?...]]
 
 It is good to choose consciously some good names while elaborating a 
 standard. But getting back to it after several years, is -- for me -- a waste 
 of time. This, unfortunately, pollutes the true philosophy as well. I believe 
 that at least 80% of the progress in the philosophy of religions belongs to 
 the linguistic domain.
 
 The anglosaxons corupted the word semantics, used in a pejorative sense: 
 discussion about superficialities, the words, not the concepts, while the 
 true semantics is about the true sense.
 
 So, sorry for being sarcastic, or even cynical in my previous post, but I 
 sincerely think that oldies are oldies, let them be, and work more on issues 
 that are still evolving.
 
 All the best.
 
 Jerzy
 
 
 
 ___
 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] Alternative name for return

2013-08-06 Thread Jake McArthur
But IO actions *are* pure values. What side effects do they have? None! You
can do whatever you want with them with no harmful effects in any Haskell
expression. They only special thing about them is that they have a run
function that is not itself provided in Haskell. The run function is
actually not legal to expose in pure Haskell. Even if it were exposed,
*that function* would be the impure thing, not the IO actions you apply it
to. (This is why GHC has unsafePerformIO and not UnsafeIO).

- Jake
On Aug 6, 2013 5:29 AM, J. Stutterheim j.stutterh...@me.com wrote:

 That argument makes sense, although I find it a bit counter-intuitive
 still. If I saw the function `pure` for the first time, my first impression
 (however wrong it may be) would be that it takes a pure value (regardless
 of context) and does something with it. Applying `pure` to an IO operation
 goes against that intuition.

 Looking at the type of `return :: a - m a, there are several slightly
 more intuitive (to me) options in this discussion already:

 lift: the value `a` is lifted into the monad `m`
 pack: the value `a` is packed into the monad `m`
 wrap: the value `a` is wrapped in the monad `m`
 inject: the value `a` is injected into the monad `m`
 promote: the value `a` is promoted to a monad `m a`


 On 6 Aug 2013, at 10:16, Tobias Dammers tdamm...@gmail.com wrote:

  It is a pure value in the context of the outer monad (the one you wrap
 it in). I'd say pure is still appropriate.
 
  On Aug 6, 2013 10:14 AM, Tom Ellis 
 tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
  On Tue, Aug 06, 2013 at 10:03:04AM +0200, J. Stutterheim wrote:
   `putStrLn Hi` is not a pure value...
 
  Why not?
 
  ___
  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 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] Alternative name for return

2013-08-06 Thread Brandon Allbery
On Tue, Aug 6, 2013 at 4:03 AM, J. Stutterheim j.stutterh...@me.com wrote:

 I have to admit that I am a bit torn about using `pure`. On the one hand,
 if you actually have a pure value, it feels pretty intuitive to me. But
 what about

   pure (putStrLn Hi)

 `putStrLn Hi` is not a pure value... Or is there another way to
 interpret the word pure in this context?


I actually have the opposite problem: what's impure about lifting 5 into
Maybe or []? `pure` feels IO-targeted.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Jerzy Karczmarczuk

Le 06/08/2013 14:47, Jake McArthur a écrit :
... But IO actions *are* pure values. What side effects do they have? 
None! /You can do whatever you want with them/ with no harmful effects 
in any Haskell expression. They only special thing about them is that 
they have a run function


As I said,  --
*Now Is The Time*  --
[[choose your reference of this Original Expression; perhaps the albums 
of Alanis Morissette or that of Jeff Lorber...]]


... to discuss the Purity. Go ahead and good luck.

Unfortunately I belong to a Cretacean generation, for whom the 
Referential Transparency means something, so I don't believe you, Jake.  
I am not saying that you are wrong. I say that calling an action a pure 
/value/ is almost meaningless.


1. First, it is not true  that you can do with, say, (printStr Ho! ) 
whatever you want. In fact, you can do almost nothing with it. You can 
transport it as such, and you can use it as the argument of (=).


2. This is the only way you can evaluate your pure value, and because 
of the monadic chaining, you cannot do it twice, you cannot 
re-evaluate it. You know all this as well as I do, perhaps better. 
That's why the purity here is dubious (although, unless I am mistaken, 
all functional constructs are considered pure by Wadler...).


3. Brandon Albery is (in my eyes) right:

what's impure about lifting 5 into Maybe or []? `pure` feels IO-targeted.


A list, such as (return 5) in the List/Nondet Monad may be treated as a 
normal data item. But a IO action, or a IoRef mutable reference -- not 
really, they are Magic. If you claim that Magic is Pure, I abandon the 
ring. For me the Magical entities (i.e., the entities which are 
controlled by some layers UNDER the one YOU control) are impure, since 
there is no operational definition of purity for them. No side 
effects? Sure, if you don't do anything with it. Even the most horrible 
Devil is pure. Unless you call it...



Jerzy Karczmarczuk


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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Tom Ellis
On Tue, Aug 06, 2013 at 04:26:05PM +0200, Jerzy Karczmarczuk wrote:
 1. First, it is not true  that you can do with, say, (printStr Ho!
 ) whatever you want. In fact, you can do almost nothing with it. You
 can transport it as such, and you can use it as the argument of
 (=).

I don't think this argument holds much water.  You can do even less with ().

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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Albert Y. C. Lai

On 13-08-06 01:14 AM, J. Stutterheim wrote:

N.B. I am _not_ proposing that we actually change the name of `return`. I do 
currently have the opportunity to pick names for common functions in a 
non-Haskell related project, so I was wondering if there perhaps is a better 
name for `return`.


I suggest simply.

Having said that, I like all the other names too.

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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Dan Burton
Bikeshedding at its finest. I think if we are very lucky, then a long time
from now we will be able to deprecate return in favor of
Control.Applicative.pure

As for making it invisible, that's what idiom brackets and monad
comprehensions are for. But for those creating an *instance* of Monad,
well, we obviously need to be able to refer to which operation we are
implementing.

I like the idea of using lift, because this is the word used for
MonadTrans, which is the same operation, but in the category of Haskell
Monads instead of the category of Hask. However, it is convenient to have
both in scope unqualified, so maybe lift would not be the best choice.

-- Dan Burton
On Aug 6, 2013 7:38 AM, Tom Ellis 
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:

 On Tue, Aug 06, 2013 at 04:26:05PM +0200, Jerzy Karczmarczuk wrote:
  1. First, it is not true  that you can do with, say, (printStr Ho!
  ) whatever you want. In fact, you can do almost nothing with it. You
  can transport it as such, and you can use it as the argument of
  (=).

 I don't think this argument holds much water.  You can do even less with
 ().

 ___
 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] Alternative name for return

2013-08-06 Thread Richard A. O'Keefe

On 6/08/2013, at 9:28 PM, J. Stutterheim wrote:

 That argument makes sense, although I find it a bit counter-intuitive still.

In discussions like this, I have never been able to discover any meaning for
intuitive other than familiar.  Applying pure to an IO operation doesn't
go against *my* intuition because Haskell has *trained* my intuition to
see 'putStrLn Hi' as a pure value; it's not the thing itself that has effects,
but its interpretation by an outer engine, just as my magnetic card key has by
itself no power to open doors, but the magnetic reader that looks at the card
_does_.  I don't attribute agency to the card!  I'm not arguing that my
intuition is _right_, only that it is _different_.

In particular, for anyone who has much experience with Haskell, return is
almost the only name that could possibly be intuitive because that _is_ the
name that is familiar.  Haskell programmers who've got used to Applicative
will also find pure intuitive, *because it is familiar*.

I bet you can find an abundance of C programmers who think that
strcmp is an intuitive name for string comparison (rather than compression, 
say).



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


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread damodar kulkarni

 I bet you can find an abundance of C programmers who think that
 strcmp is an intuitive name for string comparison (rather than
 compression, say).


But at least, 'strcmp' is not a common English language term, to have
acquired some unintentional 'intuition' by being familiar with it even in
our daily life. The Haskell terms, say, 'return' and 'lift', on the other
hand, do have usage in common English, so even a person with _no_
programming background would have acquired some unintentional 'intuition'
by being familiar with them.

And in that light, _for_me_, 'lift' is more _intuitive_ than 'return' or
'pure'. It seems, to me, like the thing being 'lifted' from a given world
into a more 'abstract' world.

Of course, I recall reading somewhere: a poet is a person who uses the
different words to mean the same thing, while a mathematician is a person
who ascribes more meanings to the same word.

Haskell, being originated from _mathy_ people, we do get to _enjoy_ this
effect.
Having said this, it has actually helped me build a different type of
'intuition' for words and I do enjoy it.



Thanks and regards,
-Damodar Kulkarni


On Wed, Aug 7, 2013 at 6:40 AM, Richard A. O'Keefe o...@cs.otago.ac.nzwrote:


 On 6/08/2013, at 9:28 PM, J. Stutterheim wrote:

  That argument makes sense, although I find it a bit counter-intuitive
 still.

 In discussions like this, I have never been able to discover any meaning
 for
 intuitive other than familiar.  Applying pure to an IO operation
 doesn't
 go against *my* intuition because Haskell has *trained* my intuition to
 see 'putStrLn Hi' as a pure value; it's not the thing itself that has
 effects,
 but its interpretation by an outer engine, just as my magnetic card key
 has by
 itself no power to open doors, but the magnetic reader that looks at the
 card
 _does_.  I don't attribute agency to the card!  I'm not arguing that my
 intuition is _right_, only that it is _different_.

 In particular, for anyone who has much experience with Haskell, return is
 almost the only name that could possibly be intuitive because that _is_ the
 name that is familiar.  Haskell programmers who've got used to Applicative
 will also find pure intuitive, *because it is familiar*.

 I bet you can find an abundance of C programmers who think that
 strcmp is an intuitive name for string comparison (rather than
 compression, say).



 ___
 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] Alternative name for return

2013-08-06 Thread Brandon Allbery
On Tue, Aug 6, 2013 at 9:10 PM, Richard A. O'Keefe o...@cs.otago.ac.nzwrote:

 I bet you can find an abundance of C programmers who think that
 strcmp is an intuitive name for string comparison (rather than
 compression, say).


Them and a small and slowly shrinking group of folks who find it intuitive
because obviously only the first 6 characters of an imported function are
significant :)

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-05 Thread Christian Sternagel

Dear Jurriën.

personally, I like lift (which is of course already occupied in 
Haskell), since an arbitrary value is lifted into a monad. (The 
literature sometimes uses unit.)


cheers

chris

On 08/06/2013 02:14 PM, J. Stutterheim wrote:

Dear Cafe,


Suppose we now have the opportunity to change the name of the `return` function in Monad, 
what would be a better  name for it? (for some definition of better)

N.B. I am _not_ proposing that we actually change the name of `return`. I do 
currently have the opportunity to pick names for common functions in a 
non-Haskell related project, so I was wondering if there perhaps is a better 
name for `return`.


- Jurriën
___
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] Alternative name for return

2013-08-05 Thread KC
I thought a pure value was being returned from the monad. :)


On Mon, Aug 5, 2013 at 10:32 PM, Christian Sternagel
c.sterna...@gmail.comwrote:

 Dear Jurriën.

 personally, I like lift (which is of course already occupied in
 Haskell), since an arbitrary value is lifted into a monad. (The
 literature sometimes uses unit.)

 cheers

 chris


 On 08/06/2013 02:14 PM, J. Stutterheim wrote:

 Dear Cafe,


 Suppose we now have the opportunity to change the name of the `return`
 function in Monad, what would be a better  name for it? (for some
 definition of better)

 N.B. I am _not_ proposing that we actually change the name of `return`. I
 do currently have the opportunity to pick names for common functions in a
 non-Haskell related project, so I was wondering if there perhaps is a
 better name for `return`.


 - Jurriën
 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




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