[Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Ertugrul Soeylemez
Martijn van Steenbergen mart...@van.steenbergen.nl wrote:

 On 8/2/10 7:09, Ertugrul Soeylemez wrote:
  Given the definition of a Haskell function, Haskell is a pure
  language.  The notion of a function in other languages is not:
 
 int randomNumber();
 
  The result of this function is an integer.  You can't replace the
  function call by its result without changing the meaning of the
  program.

 I'm not sure this is fair. It's perfectly okay to replace a call
 randomNumber() by that method's *body* (1), which is what you argue
 is okay in Haskell.

This is not the same.  In Haskell you can replace the function call by
its /result/, not its body.  You can always do that.  But the result of
an IO-based random number generator is an IO computation, not a value.
It's not source code either, and it's not a function body.  It's a
computation, something abstract without a particular representation.

This is what referential transparency is about.  Not replacing function
calls by function bodies, but by their /results/.  In C you can't
replace

  putchar(33)

by

  33

because that changes the program.  Of course there are some exceptions
like many functions from math.h.  Unlike Haskell you don't write a
program by using a DSL (like the IO monad), but you encode it directly
as a series of statements and function calls.  C has no notion of a
computation the same way Haskell has.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Ertugrul Soeylemez
Edward Z. Yang ezy...@mit.edu wrote:

 Excerpts from Ertugrul Soeylemez's message of Tue Aug 10 03:40:02 -0400 2010:
  Then you can only run evalCont, if r = a, which makes that function
  quite pointless:
 
evalCont :: Cont r r - r
evalCont = runCont id

 Ah, yes, that was what I was imagining.  I don't think the function is
 useless (though it is pointless ;-); it lets you transform
 continuation-style code into normal code.  Also, r is usually not
 fixed (unless you use mapCont or similar), so it might be more
 accurately described as Cont a a - a.

My point was, I would just write 'runCont id'. ;)

The result type of the computation is fixed.  It cannot change between
(=).  Note that 'a' is the result of one subcomputation, i.e. the
result of one particular CPS-style function, while 'r' is the result of
the entire computation.  So runCont should give you an 'r', not an 'a'.
In this case, they just happen to be the same.  But of course this is
really a matter of taste. =)


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Thomas Davie

On 11 Aug 2010, at 12:39, Ertugrul Soeylemez wrote:

 Martijn van Steenbergen mart...@van.steenbergen.nl wrote:
 
 On 8/2/10 7:09, Ertugrul Soeylemez wrote:
 Given the definition of a Haskell function, Haskell is a pure
 language.  The notion of a function in other languages is not:
 
   int randomNumber();
 
 The result of this function is an integer.  You can't replace the
 function call by its result without changing the meaning of the
 program.
 
 I'm not sure this is fair. It's perfectly okay to replace a call
 randomNumber() by that method's *body* (1), which is what you argue
 is okay in Haskell.
 
 This is not the same.  In Haskell you can replace the function call by
 its /result/, not its body.  You can always do that.  But the result of
 an IO-based random number generator is an IO computation, not a value.
 It's not source code either, and it's not a function body.  It's a
 computation, something abstract without a particular representation.

It's still rather papering over the cracks to call this pure though.  The IO 
based computation itself still has a result that you *can't* replace the IO 
based computation with.  The fact that it's evaluated by the runtime and not 
strictly in haskell may give us a warm fuzzy feeling inside, but it still means 
we have to watch out for a lot of things we don't normally have to in a very 
pure[1] computation.

Bob

[1] Bob's arbitrary definition 1 – very pure computations are ones which can be 
replaced with their result without changing the behavior of the program *even* 
if said result is computed in the runtime and not by the Haskel 
program.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Ertugrul Soeylemez
Thomas Davie tom.da...@gmail.com wrote:

 On 11 Aug 2010, at 12:39, Ertugrul Soeylemez wrote:

  Martijn van Steenbergen mart...@van.steenbergen.nl wrote:
 
  On 8/2/10 7:09, Ertugrul Soeylemez wrote:
  Given the definition of a Haskell function, Haskell is a pure
  language.  The notion of a function in other languages is not:
 
int randomNumber();
 
  The result of this function is an integer.  You can't replace the
  function call by its result without changing the meaning of the
  program.
 
  I'm not sure this is fair. It's perfectly okay to replace a call
  randomNumber() by that method's *body* (1), which is what you
  argue is okay in Haskell.
 
  This is not the same.  In Haskell you can replace the function call
  by its /result/, not its body.  You can always do that.  But the
  result of an IO-based random number generator is an IO computation,
  not a value.  It's not source code either, and it's not a function
  body.  It's a computation, something abstract without a particular
  representation.

 It's still rather papering over the cracks to call this pure though.
 The IO based computation itself still has a result that you *can't*
 replace the IO based computation with.  The fact that it's evaluated
 by the runtime and not strictly in haskell may give us a warm fuzzy
 feeling inside, but it still means we have to watch out for a lot of
 things we don't normally have to in a very pure[1] computation.

You can always come up with the necessary transformations to replace a
function's call by its body.  But this is a trivial result and not
related to referential transparency.  It's like saying:  You can
replace every while loop by a label and a goto.  What a discovery!

A while loop would be referentially transparent, if it had some notion
of a result and you could replace the entire loop by that.  And a
function is referentially transparent, if you can replace the function's
call or equivalently (!) the function's body by the function's result.

Referntially transparent functions are inherently memoizable.  A C
function is definitely not.

There is a fundamental difference between an IO computation's result and
a Haskell function's result.  The IO computation is simply a value, not
a function.  Its result is something abstract with no concrete
representation in Haskell.  In fact you can come up with mental models,
which make even those computations referentially transparent.  For
example this one:

  type IO = State RealWorld

You can only use (=) to give such a result a name, so you can refer to
it.  But this is not a function's result.  It's a value constructed in
some unspecified way and only accessible while running the program.

Remember:  Referential transparency is a property of source code!


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Thomas Davie

On 11 Aug 2010, at 14:17, Ertugrul Soeylemez wrote:
 
 There is a fundamental difference between an IO computation's result and
 a Haskell function's result.  The IO computation is simply a value, not
 a function.

That's a rather odd distinction to make – a function is simply a value in a 
functional programming language.  You're simply wrapping up we're talking 
about haskell functions when we talk about referential transparency, not about 
IO actions in a way that maintains the warm fuzzy feeling.

Bob

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread mokus

 On 11 Aug 2010, at 14:17, Ertugrul Soeylemez wrote:

 There is a fundamental difference between an IO computation's result and
 a Haskell function's result.  The IO computation is simply a value, not
 a function.

 That's a rather odd distinction to make – a function is simply a value in
 a functional programming language.  You're simply wrapping up we're
 talking about haskell functions when we talk about referential
 transparency, not about IO actions in a way that maintains the warm fuzzy
 feeling.

 Bob

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


I don't know whether anyone is calling the execution of IO actions pure -
I would not, at any rate.  At some level, things MUST 'execute', or why
are we programming at all?  Philosophical points aside, there is still a
meaningful distinction between evaluating and executing a monadic action. 
While execution may not be pure, evaluation always is - and in the
examples given so far in this thread, there is (trivial) evaluation
occurring, which is the pure part that people have been referring to
(while ignoring the impure execution aspect).  Consider a variation on the
random integer theme, where the evaluation stage is made non-trivial. 
Assuming existence of some functions randomElement and greet of suitable
types:

 main = do
 putStr What names do you go by (separate them by spaces)? 
 names - fmap words getLine
 greetRandomName names

 greetRandomName [] = putStrLn Hello there!
 greetRandomName names = randomElement names = greet

The result of _evaluating_ greetRandomName name is either @putStrLn
Hello there!@ or @randomElement names = greet@, depending whether the
input list is empty.  This result absolutely can be substituted for the
original expression and potentially further pre-evaluated if names is a
known quantity, without changing the meaning of the program.  And, to
address an idea brought up elsewhere in this thread, it is absolutely true
as pointed out before that given the right (monadic) perspective a C
program shares exactly the same properties.

There is real additional purity in Haskell's case though, and it has
absolutely nothing to do with hand-waving about whether IO is pure, very
pure, extra-super-distilled-mountain-spring-water pure, or anything like
that.  As you rightly point out, executing IO actions at run-time is not
pure at all, and we don't want it to be.  The difference is that while in
Haskell you still have an IO monad that does what C does (if you look at C
in that way), you also have a pure component of the language that can be
(and regularly is, though people often don't realize it) freely mixed with
it.  The monadic exists within the pure and the pure within the monadic. 
'greetRandomName' is a pure function that returns an IO action.  That's
not hand-waving or warm fuzzies, it's fact.  greetRandomName always
returns the same action for the same inputs.  The same distinction is
present in every monad, although in monads that are already pure, such as
Maybe, [], Cont, etc., it's not as big a deal.

The mixture is not as free as some would like; the fact that Haskell has
this distinction between monadic actions and pure values (and the fact
that the former can be manipulated as an instance of the latter) means
that the programmer must specify whether to evaluate (=) or execute
(-) an action, which is a source of endless confusion for beginners and
debate over what pure means.  I don't expect I'll put an end to either,
but I would like to point out anyway that, if you accept that distinction
(the reality of which is attested by the existence of a computable
function - the type checker - for making the distinction), it's fairly
easy to see that evaluation is always pure, excepting abuse of
unsafePerformIO, et al., and execution is not.  Both occur in the context
of do-notation.  Functions returning monadic actions (whether the
resulting action is being evaluated or executed) are still always
evaluated to yield an action.  That evaluation is pure.  The execution of
the action yielded may not be, nor should it have to be - that's the whole
point of IO!  But we still have as much purity as is actually possible,
because we know exactly where _execution_ occurs and we don't pretend it
doesn't by confusing definition with assignment.  = always means = in
Haskell, and - doesn't.  In C, = always means -, even when the RHS
is a simple variable reference (consider x = x;).

-- James

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Dan Doel
On Wednesday 11 August 2010 9:49:07 am mo...@deepbondi.net wrote:
 The mixture is not as free as some would like; the fact that Haskell has
 this distinction between monadic actions and pure values (and the fact
 that the former can be manipulated as an instance of the latter) means
 that the programmer must specify whether to evaluate (=) or execute
 (-) an action, which is a source of endless confusion for beginners and
 debate over what pure means.  I don't expect I'll put an end to either,
 but I would like to point out anyway that, if you accept that distinction
 (the reality of which is attested by the existence of a computable
 function - the type checker - for making the distinction), it's fairly
 easy to see that evaluation is always pure, excepting abuse of
 unsafePerformIO, et al., and execution is not.  Both occur in the context
 of do-notation.  Functions returning monadic actions (whether the
 resulting action is being evaluated or executed) are still always
 evaluated to yield an action.  That evaluation is pure.  The execution of
 the action yielded may not be, nor should it have to be - that's the whole
 point of IO!  But we still have as much purity as is actually possible,
 because we know exactly where _execution_ occurs and we don't pretend it
 doesn't by confusing definition with assignment.  = always means = in
 Haskell, and - doesn't.  In C, = always means -, even when the RHS
 is a simple variable reference (consider x = x;).

This is the important point, I think. Some folks were arguing in #haskell the 
other day about whether BASIC could be viewed as 'pure,' since it's so simple, 
it's almost like writing a big IO block. If you go to Sabry's[1] definition of 
purity, then you could argue that independence of evaluation order is 
trivially satisfied, because there is no evaluation only execution as 
people call it.

But I think that side-steps something, in that pure on its own isn't 
interesting, certainly if it applies to BASIC that way. To be interesting, you 
have to look at the whole Sabry thesis, which is what is a pure *functional* 
language? For the second part of that, he identifies the requirement that 
your language have some sort of lambda calculus (possibly one enriched with 
datatypes, let, etc. as Haskell does) as a sublanguage.

It is only at that point that purity becomes interesting. A plain lambda 
calculus has certain nice, equational properties to its evaluation. We can 
inline or abstract out arbitrary expressions without changing the meaning of 
the program (at least, up to nontermination). The point of remaining pure, 
then, is to preserve this aspect of the lambda calculus portion of the 
language. This obviously means we can't just add rand :: () - Int, because 
then:

  let x = rand () in x + x  /=  rand () + rand ()

and that breaks the substitutional nature of the lambda calculus portion of 
the language (and it's why unsafePerformIO is clearly impure in this sense).

Instead, Haskell has a DSL for writing down the sort of effectful programs we 
want to write in practice, and the expressions in the DSL are first-class in 
the lambda calculus portion of the language. You can say that from the view 
internal to the DSL, inlining and abstraction are invalid, because:

  rand = \x - x + x  /=  rand = \x - rand = \y - x + y

but the important part (at least, for a lot of people) is that we've preserved 
the property we want for the lambda calculus, which can be used to write large 
portions of the program.

Now, I don't think that this is necessarily tied to functional programming and 
the lambda calculus. There are probably analogous calculi for logic 
programming, and one could attempt to preserve its nice properties while 
adding in a way to do effects for 'real programs', and so on. But, to get back 
to BASIC, or C, if the language you're extending is an empty language that 
does nothing, then remaining pure to it isn't interesting. I can't actually 
write significant portions of my program in such a language, so all I'm left 
with is the DSL, which doesn't (internally) have the nice properties.

(The same applies to the C preprocessor, if you want to try that route. It is 
not a fragment of the language (even granting that it's a fragment at all) 
useful for doing actual work in the program---writing actual programs in the 
preprocessor involves files #including themselves for recursion, and is well 
in the esoteric category; it is entirely for assembling 'DSL' terms which will 
do all the actual work.)

-- Dan

[1] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.27.7800
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Tillmann Rendel

Dan Doel wrote:
But, to get back 
to BASIC, or C, if the language you're extending is an empty language that 
does nothing, then remaining pure to it isn't interesting. I can't actually 
write significant portions of my program in such a language, so all I'm left 
with is the DSL, which doesn't (internally) have the nice properties.


I understand your argument to be the following: Functional languages are 
built upon the lambda calculus, so a *pure* functional language has to 
preserve the equational theory of the lambda calculus, including, for 
example, beta reduction. But since BASIC or C are not built upon any 
formal calculus with an equational theory, there is not notion of purity 
for these languages.


I like your definition of purity, but I disagree with respect to your 
evaluation of BASIC and C. To me, they seem to be built upon the formal 
language of arithmetic expressions, so they should, to be pure 
arithmetic expression languages, adhere to such equations as the 
commutative law for integers.


  forall x y : integer, x + y = y + x

But due to possible side effects of x and y, languages like BASIC and C 
do not adhere to this, and many other laws. I would therefore consider 
them impure. They could be more pure by allowing side effects only in 
statements, but not in expressions.


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Dan Doel
On Wednesday 11 August 2010 3:13:56 pm Tillmann Rendel wrote:
 I understand your argument to be the following: Functional languages are
 built upon the lambda calculus, so a *pure* functional language has to
 preserve the equational theory of the lambda calculus, including, for
 example, beta reduction. But since BASIC or C are not built upon any
 formal calculus with an equational theory, there is not notion of purity
 for these languages.

In the discussion from #haskell I mentioned, some folks argued that BASIC was 
pure because there was no equivalent of Haskell's evaluation, only execution. 
I was just attempting to translate that to a more Sabry-like explanation, 
where there would be an empty (or otherwise trivial) sublanguage, and so 
purity would be trivial, because evaluation does nothing (or something along 
those lines).

 I like your definition of purity, but I disagree with respect to your
 evaluation of BASIC and C. To me, they seem to be built upon the formal
 language of arithmetic expressions, so they should, to be pure
 arithmetic expression languages, adhere to such equations as the
 commutative law for integers.
 
forall x y : integer, x + y = y + x
 
 But due to possible side effects of x and y, languages like BASIC and C
 do not adhere to this, and many other laws. I would therefore consider
 them impure. They could be more pure by allowing side effects only in
 statements, but not in expressions.

I'm no BASIC expert, but they were talking about very rudimentary BASICs. The 
sort where line numbers and GOTO are your control flow, not even subroutines. 
I'm not sure if that affects your point here or not.

Certainly, if you consider numeric arithmetic to be the core language, C is an 
impure extension of it (the #haskell folks weren't actually arguing that C was 
pure; just the simple BASIC). Not sure about the above BASIC, but a fancier 
BASIC would be, in the same way.

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Ertugrul Soeylemez
Edward Z. Yang ezy...@mit.edu wrote:

 Excerpts from Luke Palmer's message of Tue Aug 10 01:04:04 -0400 2010:
  Except, of course, you want the signature
 
evalCont :: Cont r a - a
 
  Which is not possible.  But I am not sure where all this discussion
  is coming from, Maybe and (r -) cannot be broken out of.  Isn't
  that example enough?

 I'm confused... that's the type of evalCont, no?

There is no evalCont, there is runCont:

  runCont :: (a - r) - Cont r a - r

Note that Cont/ContT computations result in a value of type 'r':

  newtype Cont r a = Cont ((a - r) - r)


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Edward Z. Yang
Excerpts from Ertugrul Soeylemez's message of Tue Aug 10 02:31:14 -0400 2010:
 There is no evalCont, there is runCont:
 
   runCont :: (a - r) - Cont r a - r
 
 Note that Cont/ContT computations result in a value of type 'r':
 
   newtype Cont r a = Cont ((a - r) - r)

Yes, but if you pass in 'id' as the continuation to 'runCont',
the entire expression will result in 'a'.  The continuation monad
doesn't act globally...

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Ertugrul Soeylemez
Edward Z. Yang ezy...@mit.edu wrote:

 Excerpts from Ertugrul Soeylemez's message of Tue Aug 10 02:31:14 -0400 2010:
  There is no evalCont, there is runCont:
 
runCont :: (a - r) - Cont r a - r
 
  Note that Cont/ContT computations result in a value of type 'r':
 
newtype Cont r a = Cont ((a - r) - r)

 Yes, but if you pass in 'id' as the continuation to 'runCont', the
 entire expression will result in 'a'.  The continuation monad doesn't
 act globally...

Then you can only run evalCont, if r = a, which makes that function
quite pointless:

  evalCont :: Cont r r - r
  evalCont = runCont id


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Edward Z. Yang
Excerpts from Ertugrul Soeylemez's message of Tue Aug 10 03:40:02 -0400 2010:
 Then you can only run evalCont, if r = a, which makes that function
 quite pointless:
 
   evalCont :: Cont r r - r
   evalCont = runCont id

Ah, yes, that was what I was imagining.  I don't think the function is
useless (though it is pointless ;-); it lets you transform continuation-style
code into normal code.  Also, r is usually not fixed (unless you use mapCont
or similar), so it might be more accurately described as Cont a a - a.

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Martijn van Steenbergen

On 8/2/10 7:09, Ertugrul Soeylemez wrote:

Given the definition of a Haskell function, Haskell is a pure language.
The notion of a function in other languages is not:

   int randomNumber();

The result of this function is an integer.  You can't replace the
function call by its result without changing the meaning of the program.


I'm not sure this is fair. It's perfectly okay to replace a call 
randomNumber() by that method's *body* (1), which is what you argue is 
okay in Haskell.


Martijn.


(1) Modulo some renaming, and modulo the complicated non-compositional 
meanings of control statements such as return, etc.

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Felipe Lessa
On Tue, Aug 10, 2010 at 6:21 PM, Martijn van Steenbergen
mart...@van.steenbergen.nl wrote:
 On 8/2/10 7:09, Ertugrul Soeylemez wrote:

 Given the definition of a Haskell function, Haskell is a pure language.
 The notion of a function in other languages is not:

   int randomNumber();

 The result of this function is an integer.  You can't replace the
 function call by its result without changing the meaning of the program.

 I'm not sure this is fair. It's perfectly okay to replace a call
 randomNumber() by that method's *body* (1), which is what you argue is
 okay in Haskell.

Nope.  For example, suppose we have:

  int randomNumber(int min, int max);

Equivalentely:

  randomNumber :: Int - Int - IO Int

In Haskell if we say

  (+) $ randomNumber 10 15 * randomNumber 10 15

That's the same as

  let x = randomNumber 10 15
  in (+) $ x * x

If we had in C:

  return (randomNumber(10, 15) + randomNumber(10, 15))

That would not be the same as:

  int x = randomNumber(10, 15)
  return (x + x)

Cheers!

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Steve Schafer
On Tue, 10 Aug 2010 18:27:49 -0300, you wrote:

Nope.  For example, suppose we have:

  int randomNumber(int min, int max);

Equivalentely:

  randomNumber :: Int - Int - IO Int

In Haskell if we say

  (+) $ randomNumber 10 15 * randomNumber 10 15

That's the same as

  let x = randomNumber 10 15
  in (+) $ x * x

If we had in C:

  return (randomNumber(10, 15) + randomNumber(10, 15))

That would not be the same as:

  int x = randomNumber(10, 15)
  return (x + x)

I think you're misinterpreting what Martijn is saying. He's not talking
about referential transparency at all. What he's saying is that in a
language like C, you can always replace a function call with the code
that constitutes the body of that function. In C-speak, you can inline
the function.

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Martijn van Steenbergen

On 8/10/10 23:27, Felipe Lessa wrote:

If we had in C:

   return (randomNumber(10, 15) + randomNumber(10, 15))

That would not be the same as:

   int x = randomNumber(10, 15)
   return (x + x)


That's not fair. You're comparing C's '=' with Haskell's '='. But you 
should be comparing C's '=' with Haskell's '-'.


In your Haskell example, x :: IO Int. In your C example, x :: Int.

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Felipe Lessa
On Tue, Aug 10, 2010 at 6:36 PM, Martijn van Steenbergen
mart...@van.steenbergen.nl wrote:
 On 8/10/10 23:27, Felipe Lessa wrote:

 If we had in C:

   return (randomNumber(10, 15) + randomNumber(10, 15))

 That would not be the same as:

   int x = randomNumber(10, 15)
   return (x + x)

 That's not fair. You're comparing C's '=' with Haskell's '='. But you should
 be comparing C's '=' with Haskell's '-'.

 In your Haskell example, x :: IO Int. In your C example, x :: Int.

Well, then maybe we will agree with eachother when we decide on what
is fair. =)

You quoted:

Given the definition of a Haskell function, Haskell is a pure language.
The notion of a function in other languages is not:

  int randomNumber();

The result of this function is an integer.  You can't replace the
function call by its result without changing the meaning of the program.

So, given the functions

  int randomNumber(int, int)
  randomNumber :: Int - Int - IO Int

what is replace the function call by its result?  Function call in C
is, for example,

  randomNumber(10, 15);

and the result of this call has type int.  In Haskell, what is a
function call?  Well, it's

  randomNumber 10 15

and the result is IO Int.  When we replace the function call by its
result, I think it is fair to replace the C function call by an int
and the Haskell function call by an IO Int, because that is what
those functions return.

To fit your definition of fairness I would have to say that function
application is

  \cont - randomNumber 10 15 = \x - cont x

which has type (Int - IO a) - IO a.  I don't think this is
function call at all, and only works for monads.

IMHO, Ertugrul was pointing out the difference of C's int and
Haskell's IO Int.  An 'IO Int' may be passed around and you don't
change the meaning of anything.

Cheers, =)

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Martijn van Steenbergen

On 8/10/10 23:53, Felipe Lessa wrote:

and the result is IO Int.  When we replace the function call by its
result, I think it is fair to replace the C function call by an int
and the Haskell function call by an IO Int, because that is what
those functions return.


Fair enough. :-)

Also, a correction to what I said earlier: it's not C's = that 
corresponds to a bind -, it's (...args...) that does. I think.


On a side note, imperative languages with first-class 
functions/delegates can express your Haskell example. For example, 
Javascript:


  var x = function() { return randomNumber(10, 15); }
  return x() + x();

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-08 Thread Richard O'Keefe

On Aug 3, 2010, at 11:37 PM, Christopher Witte wrote:

 On 3 August 2010 01:34, Richard O'Keefe o...@cs.otago.ac.nz wrote:
 There's a thing I'm still finding extremely hard about monads,
 and that's how to get into the frame of mind where inventing
 things like Monad and Applicative and Arrows is something I could
 do myself.  Functor, yes, I could have invented Functor.
 But not the others.
 
 Maybe looking at Sigfpe's blog post You Could Have Invented Monads! (And 
 Maybe You Already Have.) will help.


Notice the tense, could have.  I have read You Could Have Invented
Monads, and recommended it to students.  In fact I _did_ invent
monads, in the guise of parser combinators.  That is to say, having
heard of parser combinators, I developed my own set, which contained
operations recognisable with hindsight as the operations of Monad and
MonadPlus c BUT I DID NOT REALISE THAT THAT WAS WHAT I HAD DONE.
After reading that blog post, yes.


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-08 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/8/10 19:28 , Richard O'Keefe wrote:
 On Aug 3, 2010, at 11:37 PM, Christopher Witte wrote:
 Maybe looking at Sigfpe's blog post You Could Have Invented Monads! (And 
 Maybe You Already Have.) will help.
 
 Notice the tense, could have.  I have read You Could Have Invented
 Monads, and recommended it to students.  In fact I _did_ invent
 monads, in the guise of parser combinators.  That is to say, having
 heard of parser combinators, I developed my own set, which contained
 operations recognisable with hindsight as the operations of Monad and
 MonadPlus c BUT I DID NOT REALISE THAT THAT WAS WHAT I HAD DONE.
 After reading that blog post, yes.

That's what the And Maybe You Already Have part is about

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxfQQ4ACgkQIn7hlCsL25V5aQCfaweA9PmrInW3BSQwVQdDhdnQ
vo0AnRbv58abJ7jINqDsZG2UaXifmRLl
=c9Ro
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-03 Thread Christopher Witte
On 3 August 2010 01:34, Richard O'Keefe o...@cs.otago.ac.nz wrote:

 There's a thing I'm still finding extremely hard about monads,
 and that's how to get into the frame of mind where inventing
 things like Monad and Applicative and Arrows is something I could
 do myself.  Functor, yes, I could have invented Functor.
 But not the others.


Maybe looking at Sigfpe's blog post You Could Have Invented Monads! (And
Maybe You Already
Have.)http://blog.sigfpe.com/2006/08/you-could-have-invented-monads-and.htmlwill
help.


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-02 Thread Richard O'Keefe
The thing that I found hardest to understand about monads is that
they are used to obtain very special consequences (fitting things
like I/O and updatable arrays into a functional language) without
actually involving any special machinery.  Whenever you look for
the magic, it's nowhere.  But it's happening none the less.  It's
really the monad laws that matter; they express _just_ enough of
the informal notion of doing things one after the other to be
useful for side-effective things that need to be done one after
the other without expressing so much that they preclude
informally pure things like lists and maybes.

There's a thing I'm still finding extremely hard about monads,
and that's how to get into the frame of mind where inventing
things like Monad and Applicative and Arrows is something I could
do myself.  Functor, yes, I could have invented Functor.
But not the others.


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-02 Thread aditya siram
Agreed. In fact I have the most trouble imagining what Haskell code looked
like before monads.

-deech

On Mon, Aug 2, 2010 at 6:34 PM, Richard O'Keefe o...@cs.otago.ac.nz wrote:

 The thing that I found hardest to understand about monads is that
 they are used to obtain very special consequences (fitting things
 like I/O and updatable arrays into a functional language) without
 actually involving any special machinery.  Whenever you look for
 the magic, it's nowhere.  But it's happening none the less.  It's
 really the monad laws that matter; they express _just_ enough of
 the informal notion of doing things one after the other to be
 useful for side-effective things that need to be done one after
 the other without expressing so much that they preclude
 informally pure things like lists and maybes.

 There's a thing I'm still finding extremely hard about monads,
 and that's how to get into the frame of mind where inventing
 things like Monad and Applicative and Arrows is something I could
 do myself.  Functor, yes, I could have invented Functor.
 But not the others.


 ___
 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: Can we come out of a monad?

2010-08-02 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/2/10 19:59 , aditya siram wrote:
 Agreed. In fact I have the most trouble imagining what Haskell code looked
 like before monads.

IIRC the type of main was something like [Request] - [Response].

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxXYvIACgkQIn7hlCsL25UaZgCfSso+NXgwRNJt1uc5uSCoIY4N
c/8AoMGm6H9SqwAAVnarOH5sXdgWx6TW
=d9nq
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-02 Thread Dean Herington

At 8:29 PM -0400 8/2/10, Brandon S Allbery KF8NH wrote:


On 8/2/10 19:59 , aditya siram wrote:

 Agreed. In fact I have the most trouble imagining what Haskell code looked
 like before monads.


IIRC the type of main was something like [Request] - [Response].


Actually, the Haskell 1.2 report (published in SIGPLAN Notices, May 1992) has:

main :: [Response] - [Request]

(Yes, it was awkward to program I/O that way!)  That version of 
Haskell also had a continuation-based I/O framework.


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


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Ertugrul Soeylemez
Kevin Jardine kevinjard...@gmail.com wrote:

 Or is it possible to call a function in a monad and return a pure
 result? I think that is what the original poster was asking?

 I know that unsafePerformIO can do this, but I thought that was a bit
 of a hack.

What most people forget is that in Haskell there is /no/ impure stuff
involved.  Even the IO monad is completely pure.  The unsafePerformIO
function breaks this rule, hence it's unsafe.  Take as an example the
following toy implementation of the 'cat' program:

  main :: IO ()
  main = do
args - getArgs
case args of
  []- getContents = putStr
  files - mapM_ (readFile = putStr) files

Here the domain-specific language, which is defined by the IO monad, is
used to model a computation, which interacts with the outside world.
All of this code is completely pure.  But the DSL models computations,
which may change the world during (=).

Even the 'putStr' function is well referentially transparent.  You can
safely replace its application by its result.  But note that its result
is /not/ of type (), but of type 'IO ()'.  Its result is an IO
computation, i.e. a statement in the DSL defined by IO.  As a clarifying
example look at this function:

  printAndSquare :: Integer - IO Integer
  printAndSquare x = print x  return (x^2)

If you write 'printAndSquare 5' somewhere in your code, then you're
calling the function 'printAndSquare' with the argument 5, which gives a
result of type 'IO Integer'.  You can safely replace any occurence of
'printAndSquare 5' by its result.  The following four computations are
equivalent:

  fmap read getLine = printAndSquare = print

  fmap read getLine = (\x - print x  return (x^2)) = print

  do num - fmap read getLine
 square - printAndSquare num
 print square

  do num - fmap read getLine
 square - print num  return (num^2)
 print square

I have made direct use of the referential transparency rule.  The result
of applying the function 'printAndSquare' is not the same as the
run-time result of the computation, which it expresses.

Everything between (=) is pure.  You're dealing with normal Haskell
expressions here, and there is no magic involved, since IO is really
just a language.  You never get out of IO, because as soon as you do
'-' in do-notation, you are giving the result of an IO computation a
certain name.  Instead of saying

  getContents = putStr

you say

  do content - getContents
 putStr content

The only difference is that you have named the result explicitly.  Don't
try to give this operational meaning.  It's just a different way to
express the same statement in the IO language.

If you want to write a function, which returns a random boolean, the
correct way to do it is one of these:

  randomBool :: RngState - (Bool, RngState)
  randomBool :: State RngState Bool
  randomBool :: IO Bool

In fact, the two latter examples aren't even functions.  They are simply
values -- statements in a domain-specific language.  For the second
example it's the 'State RngState' language, for the third example it's
the IO language.  The following is also simply a value:

  randomBool :: Bool

But it's really a value of type Bool.  It's not a statement in some DSL.
It's not a computation.  It's not a function.  Just a constant value.


 I'm still trying to understand how monads interact with types so I am
 interested in this as well.

A monad is a type constructor, which is an instance of the Monad class
and which obeys the monad laws.  That's it.


 On Jul 30, 10:11 am, Kevin Jardine kevinjard...@gmail.com wrote:
  Oops, I should have written
 
  IO ByteString
 
  as the State stuff is only *inside* execState.
 
  But a monad none the less?
 
  Kevin
 
  On Jul 30, 9:59 am, Kevin Jardine kevinjard...@gmail.com wrote:
 
   The original poster states that the type of modifiedImage is simply
   ByteString but given that it calls execState, is that possible?
 
   Would it not be State ByteString?
 
   Kevin
 
   On Jul 30, 9:49 am, Anton van Straaten an...@appsolutions.com wrote:
 
C K Kashyap wrote:
 In the code here -
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
 If I look at the type of modifiedImage, its simply ByteString - but
 isn't it actually getting into and back out of the state monad? I am 
 of
 the understanding that once you into a monad, you cant get out of it? 
 Is
 this breaking the monad scheme?
 
modifiedImage uses the execState function, which has the following type:
 
   execState :: State s a - s - s
 
In other words, it applies a State monad value to a state, and returns a
new state.  Its entire purpose is to run the monad and obtain the
resulting state.
 
A monadic value of type State s a is a kind of delayed computation
that doesn't do anything until you apply it to a state, using a function
like execState or evalState.  Once you do that, the computation runs,
the monad is evaluated away, 

[Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Ertugrul Soeylemez
Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

 No, a pure function is one without any side effects.

There are no functions with side effects in Haskell, unless you use
hacks like unsafePerformIO.  Every Haskell function is perfectly
referentially transparent, i.e. pure.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Thomas Davie

On 1 Aug 2010, at 11:43, Ertugrul Soeylemez wrote:

 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:
 
 No, a pure function is one without any side effects.
 
 There are no functions with side effects in Haskell, unless you use
 hacks like unsafePerformIO.  Every Haskell function is perfectly
 referentially transparent, i.e. pure.

This is why we badly need a new term, say, io-pure.  That means, neither has 
side effects, nor produces an action that when run by the runtime has side 
effects.

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Ertugrul Soeylemez
Thomas Davie tom.da...@gmail.com wrote:

 On 1 Aug 2010, at 11:43, Ertugrul Soeylemez wrote:

  Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:
 
  No, a pure function is one without any side effects.
 
  There are no functions with side effects in Haskell, unless you use
  hacks like unsafePerformIO.  Every Haskell function is perfectly
  referentially transparent, i.e. pure.

 This is why we badly need a new term, say, io-pure.  That means,
 neither has side effects, nor produces an action that when run by the
 runtime has side effects.

Why?  We have terms like 'IO computation' or 'monadic value', and that
should hit the nail on the head.  People should learn what type of
computations the IO monad models, and generally they learn that quite
early.

I have the impression that to talk about something being impure in
Haskell confuses people more than anything else.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Ivan Miljenovic
On 1 August 2010 20:43, Ertugrul Soeylemez e...@ertes.de wrote:
 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

 No, a pure function is one without any side effects.

 There are no functions with side effects in Haskell, unless you use
 hacks like unsafePerformIO.  Every Haskell function is perfectly
 referentially transparent, i.e. pure.

At code-writing time, yes; at run-time there are side effects...

In terms of what a function does, is readFile actually pure?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Lyndon Maydwell
I thought it was pure as, conceptually, readFile isn't 'run' rather it
constructs a pure function that accepts a unique world state as a
parameter. This might be totally unrealistic, but this is how I see IO
functions remaining pure. Is this a good mental model?


 In terms of what a function does, is readFile actually pure?

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Ertugrul Soeylemez
Ivan Miljenovic ivan.miljeno...@gmail.com wrote:

 On 1 August 2010 20:43, Ertugrul Soeylemez e...@ertes.de wrote:

  There are no functions with side effects in Haskell, unless you use
  hacks like unsafePerformIO.  Every Haskell function is perfectly
  referentially transparent, i.e. pure.

 At code-writing time, yes; at run-time there are side effects...

 In terms of what a function does, is readFile actually pure?

Yes, it's a pure function.  But it models a computation, which changes
the world's state.  If you happen to get a real Haskell code
representation of 'readFile', you can safely replace its call by its
body without messing things up (applying the usual lambda reduction
rules, of course).

Note that a function is something of type 'a - b' for some type a and
some type b.  The result of the function 'readFile' is not of type
String, but of type IO String.  For the same file name parameter, it
always gives the same result computation.

It is really questionable whether it makes sense to use the term
impure for the computations, which are modelled by IO.  I don't think
we have a useful theoretical foundation for what impure means in this
context.  You can model IO as State Universe (regardless of the problems
with that model), in which case even the computations are perfectly pure
and representable as Haskell functions.  In fact the Clean language uses
this model, whereas Haskell leaves this abstract.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Ivan Miljenovic
On 2 August 2010 14:47, Lyndon Maydwell maydw...@gmail.com wrote:
 I thought it was pure as, conceptually, readFile isn't 'run' rather it
 constructs a pure function that accepts a unique world state as a
 parameter. This might be totally unrealistic, but this is how I see IO
 functions remaining pure. Is this a good mental model?

That is what I believe Ertugrul is aiming at, but I believe that that
is a rule-lawyering interpretation in trying to argue that all of
Haskell is pure.  We could use this same argument to state that _all_
programming languages are pure, as they too have implict World state
variables that get passed around.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Lyndon Maydwell
That's true I suppose, although since there are no implicit parameters
in haskell, it really has to be a DSL in implementation, rather than
just theory right?

On Mon, Aug 2, 2010 at 12:51 PM, Ivan Miljenovic
ivan.miljeno...@gmail.com wrote:
 On 2 August 2010 14:47, Lyndon Maydwell maydw...@gmail.com wrote:
 I thought it was pure as, conceptually, readFile isn't 'run' rather it
 constructs a pure function that accepts a unique world state as a
 parameter. This might be totally unrealistic, but this is how I see IO
 functions remaining pure. Is this a good mental model?

 That is what I believe Ertugrul is aiming at, but I believe that that
 is a rule-lawyering interpretation in trying to argue that all of
 Haskell is pure.  We could use this same argument to state that _all_
 programming languages are pure, as they too have implict World state
 variables that get passed around.

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Ivan Miljenovic
On 2 August 2010 14:59, Lyndon Maydwell maydw...@gmail.com wrote:
 That's true I suppose, although since there are no implicit parameters
 in haskell, it really has to be a DSL in implementation, rather than
 just theory right?

http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/other-type-extensions.html#implicit-parameters

You were saying? ;p

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Ertugrul Soeylemez
Lyndon Maydwell maydw...@gmail.com wrote:

 I thought it was pure as, conceptually, readFile isn't 'run' rather it
 constructs a pure function that accepts a unique world state as a
 parameter. This might be totally unrealistic, but this is how I see IO
 functions remaining pure. Is this a good mental model?

Yes, but some people argue that there are problems with this model.  For
example it doesn't really catch the forkIO concept and the interactions
between threads.  For this model, forkIO is just a side effect like
everything else and if you takeMVar a value, then it comes from the
world, which isn't very useful.

But don't bother, because that model works most of the time.  Personally
I have switched from your model to the model of an embedded DSL.  It's a
simpler mental model and doesn't interpret too much.  You just get some
primitive IO computations and a number of combinators to stick them
together.  That's it.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


[Haskell-cafe] Re: Can we come out of a monad?

2010-08-01 Thread Ertugrul Soeylemez
Ivan Miljenovic ivan.miljeno...@gmail.com wrote:

 On 2 August 2010 14:47, Lyndon Maydwell maydw...@gmail.com wrote:
  I thought it was pure as, conceptually, readFile isn't 'run' rather
  it constructs a pure function that accepts a unique world state as a
  parameter. This might be totally unrealistic, but this is how I see
  IO functions remaining pure. Is this a good mental model?

 That is what I believe Ertugrul is aiming at, but I believe that that
 is a rule-lawyering interpretation in trying to argue that all of
 Haskell is pure.  We could use this same argument to state that _all_
 programming languages are pure, as they too have implict World state
 variables that get passed around.

Given the definition of a Haskell function, Haskell is a pure language.
The notion of a function in other languages is not:

  int randomNumber();

The result of this function is an integer.  You can't replace the
function call by its result without changing the meaning of the program.
In Haskell, this wouldn't even be a function.  It would be a
computation, i.e. simply a value.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-31 Thread Ertugrul Soeylemez
Brent Yorgey byor...@seas.upenn.edu wrote:

 On Fri, Jul 30, 2010 at 03:46:09AM -0700, Kevin Jardine wrote:
 
  When I plunged into Haskell earlier this year, I had no problem with
  understanding static typing, higher level functions and even
  separating pure functions from IO functions.
 
  The more I learn about monads, however, the less I understand them.
  I've seen plenty of comments suggesting that monads are easy to
  understand, but for me they are not.

 Lies.  [...]

 Even worse, this misguided but common insistence that monads are easy
 to understand inevitably makes people feel stupid when they discover
 that they aren't.

 Monads are hard to understand.  But they are *worth understanding*.

I agree to some extent, but only to some.  Mostly the problem of people
is that they are trying to understand monads as opposed to specific
instances.  It's better to learn the IO monad, state monads, the
list monad, the Maybe monad, the Parser monad, etc.

My experience is that the more specific examples you learn, the more you
will see the common design pattern.  Eventually it will make /click/ and
out of a sudden the lights will turn on.

So what's monad?  It's nothing.  Simple.

Better ask:  What's the Maybe monad?.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-31 Thread Dan Doel
On Saturday 31 July 2010 8:13:37 am Ertugrul Soeylemez wrote:
 I agree to some extent, but only to some.  Mostly the problem of people
 is that they are trying to understand monads as opposed to specific
 instances.  It's better to learn the IO monad, state monads, the
 list monad, the Maybe monad, the Parser monad, etc.

I think there are 'easy' answers to what are monads, too, at least in the 
way they tend to appear in Haskell. But, the easiness may well depend on 
having background that isn't common in computer programming.

Some of it is, though. Embedded domain-specific language is a buzz phrase 
these days, so it's probably safe to assume most folks are familiar with the 
idea. From that starting point, one might ask how to approach EDSLs from a 
more mathematical perspective, and making use of the type system. We might be 
led to the following:

1) We want to distinguish 'programs written in the EDSL' via types somehow. It 
may not make sense to use EDSL operations just anywhere in the overall 
program.

2) Algebra looks promising for talking about languages. Our DSLs will probably 
have some base operations, which we'll combine to make our programs. So, our 
EDSL type above should probably be related to algebraic theories somehow.

Once we've decided on the above, well, monads are a way in category theory of 
talking about algebraic theories. So it stands to reason that a lot of the 
EDSLs we're interested in will be monads. And so, by talking about monads in 
general, we can construct operations that make sense in and on arbitrary EDSLs 
(like, say, sequence = stick together several expressions).

And that covers a lot of what monads are used for in Haskell.

  'Maybe a' designates expressions in a language with failure
  'Either e a' designates expressions with a throw operation
  'State s a' allows get and put
  'IO a' has most of the features in imperative languages.
  etc.

So the 'easy' answer is that (embedded) languages tend to be algebraic 
theories, and monads are a way of talking about those. Of course, that general 
answer may still be pretty meaningless if you don't know what algebraic 
theories are, so it's still probably good to look at specific monads.

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
The original poster states that the type of modifiedImage is simply
ByteString but given that it calls execState, is that possible?

Would it not be State ByteString?

Kevin

On Jul 30, 9:49 am, Anton van Straaten an...@appsolutions.com wrote:
 C K Kashyap wrote:
  In the code here -
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
  If I look at the type of modifiedImage, its simply ByteString - but
  isn't it actually getting into and back out of the state monad? I am of
  the understanding that once you into a monad, you cant get out of it? Is
  this breaking the monad scheme?

 modifiedImage uses the execState function, which has the following type:

    execState :: State s a - s - s

 In other words, it applies a State monad value to a state, and returns a
 new state.  Its entire purpose is to run the monad and obtain the
 resulting state.

 A monadic value of type State s a is a kind of delayed computation
 that doesn't do anything until you apply it to a state, using a function
 like execState or evalState.  Once you do that, the computation runs,
 the monad is evaluated away, and a result is returned.

 The issue about not being able to escape that (I think) you're referring
 to applies to the functions within that computation.  A State monad
 computation typically consists of a chain of monadic functions of type
 (a - State s b) composed using bind (=).  A function in that composed
 chain has to return a monadic value, which constrains the ability of
 such a function to escape from the monad.

 Within a monadic function, you may deal directly with states and
 non-monadic values, and you may run functions like evalState or
 execState which eliminate monads, but the function still has to return a
 monadic value in the end, e.g. using return to lift an ordinary value
 into the monad.

 Anton
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
Oops, I should have written

IO ByteString

as the State stuff is only *inside* execState.

But a monad none the less?

Kevin

On Jul 30, 9:59 am, Kevin Jardine kevinjard...@gmail.com wrote:
 The original poster states that the type of modifiedImage is simply
 ByteString but given that it calls execState, is that possible?

 Would it not be State ByteString?

 Kevin

 On Jul 30, 9:49 am, Anton van Straaten an...@appsolutions.com wrote:

  C K Kashyap wrote:
   In the code here -
  http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
   If I look at the type of modifiedImage, its simply ByteString - but
   isn't it actually getting into and back out of the state monad? I am of
   the understanding that once you into a monad, you cant get out of it? Is
   this breaking the monad scheme?

  modifiedImage uses the execState function, which has the following type:

     execState :: State s a - s - s

  In other words, it applies a State monad value to a state, and returns a
  new state.  Its entire purpose is to run the monad and obtain the
  resulting state.

  A monadic value of type State s a is a kind of delayed computation
  that doesn't do anything until you apply it to a state, using a function
  like execState or evalState.  Once you do that, the computation runs,
  the monad is evaluated away, and a result is returned.

  The issue about not being able to escape that (I think) you're referring
  to applies to the functions within that computation.  A State monad
  computation typically consists of a chain of monadic functions of type
  (a - State s b) composed using bind (=).  A function in that composed
  chain has to return a monadic value, which constrains the ability of
  such a function to escape from the monad.

  Within a monadic function, you may deal directly with states and
  non-monadic values, and you may run functions like evalState or
  execState which eliminate monads, but the function still has to return a
  monadic value in the end, e.g. using return to lift an ordinary value
  into the monad.

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

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
Or is it possible to call a function in a monad and return a pure
result? I think that is what the original poster was asking?

I know that unsafePerformIO can do this, but I thought that was a bit
of a hack.

I'm still trying to understand how monads interact with types so I am
interested in this as well.

Kevin

On Jul 30, 10:11 am, Kevin Jardine kevinjard...@gmail.com wrote:
 Oops, I should have written

 IO ByteString

 as the State stuff is only *inside* execState.

 But a monad none the less?

 Kevin

 On Jul 30, 9:59 am, Kevin Jardine kevinjard...@gmail.com wrote:

  The original poster states that the type of modifiedImage is simply
  ByteString but given that it calls execState, is that possible?

  Would it not be State ByteString?

  Kevin

  On Jul 30, 9:49 am, Anton van Straaten an...@appsolutions.com wrote:

   C K Kashyap wrote:
In the code here -
   http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
If I look at the type of modifiedImage, its simply ByteString - but
isn't it actually getting into and back out of the state monad? I am of
the understanding that once you into a monad, you cant get out of it? Is
this breaking the monad scheme?

   modifiedImage uses the execState function, which has the following type:

      execState :: State s a - s - s

   In other words, it applies a State monad value to a state, and returns a
   new state.  Its entire purpose is to run the monad and obtain the
   resulting state.

   A monadic value of type State s a is a kind of delayed computation
   that doesn't do anything until you apply it to a state, using a function
   like execState or evalState.  Once you do that, the computation runs,
   the monad is evaluated away, and a result is returned.

   The issue about not being able to escape that (I think) you're referring
   to applies to the functions within that computation.  A State monad
   computation typically consists of a chain of monadic functions of type
   (a - State s b) composed using bind (=).  A function in that composed
   chain has to return a monadic value, which constrains the ability of
   such a function to escape from the monad.

   Within a monadic function, you may deal directly with states and
   non-monadic values, and you may run functions like evalState or
   execState which eliminate monads, but the function still has to return a
   monadic value in the end, e.g. using return to lift an ordinary value
   into the monad.

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

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

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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: Can we come out of a monad?

2010-07-30 Thread Anton van Straaten

 On Jul 30, 9:59 am, Kevin Jardine kevinjard...@gmail.com wrote:

 The original poster states that the type of modifiedImage is simply
 ByteString but given that it calls execState, is that possible?
 Would it not be State ByteString?

 Oops, I should have written

 IO ByteString

 as the State stuff is only *inside* execState.

 But a monad none the less?

State is a pure monad that doesn't involve IO.  It works by threading a 
state value through the monadic computation, so old states are discarded 
and new states are passed on, and no actual mutation is involved.  This 
means there's no need to bring IO into it.


If you look at the type signature of execState, you'll see that unless 
the state type 's' involves IO, the return type can't involve IO.


It can help to run little examples of this.  Here's a GHCi transcript:

Prelude :m Control.Monad.State
Prelude Control.Monad.State let addToState :: Int - State Int (); 
addToState x = do s - get; put (s+x)

Prelude Control.Monad.State let mAdd4 = addToState 4
Prelude Control.Monad.State :t mAdd4
m :: State Int ()
Prelude Control.Monad.State let s = execState mAdd4 2
Prelude Control.Monad.State :t s
s :: Int
Prelude Control.Monad.State s
6

In the above, addToState is a monadic function that adds its argument x 
to the current state.  mAdd4 is a monadic value that adds 4 to whatever 
state it's eventually provided with.  When execState provides it with an 
initial state of 2, the monadic computation is run, and the returned 
result is 6, which is an Int, not a monadic type.



Or is it possible to call a function in a monad and return a pure
result? I think that is what the original poster was asking?


If you use a function like execState (depending on the monad), you can 
typically run a monadic computation and get a non-monadic result. 
However, if you're doing that inside a monadic function, you still have 
to return a value of monadic type - so typically, you use 'return', 
which lifts a value into the monad.



I know that unsafePerformIO can do this, but I thought that was a bit
of a hack.


IO is a special monad which has side effects.  unsafePerformIO is just 
one of the functions that can run IO actions, but because the monad has 
side effects, this is unsafe in general.  With a pure monad like State, 
there's no such issue.


Anton

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
I think that these are therefore the responses to the original
questions:

 I am of the understanding that once you into a monad, you cant get out of it?

You can run monadic functions and get pure results. So it looks like
in that sense you can get out of it.

  Is this breaking the monad scheme?

Apparently not. Although functions that do this for monads that have
side effects are unsafe, so use them carefully.

Cheers,
Kevin

On Jul 30, 11:17 am, Anton van Straaten an...@appsolutions.com
wrote:
   On Jul 30, 9:59 am, Kevin Jardine kevinjard...@gmail.com wrote:
  
   The original poster states that the type of modifiedImage is simply
   ByteString but given that it calls execState, is that possible?
   Would it not be State ByteString?

   Oops, I should have written
  
   IO ByteString
  
   as the State stuff is only *inside* execState.
  
   But a monad none the less?

 State is a pure monad that doesn't involve IO.  It works by threading a
 state value through the monadic computation, so old states are discarded
 and new states are passed on, and no actual mutation is involved.  This
 means there's no need to bring IO into it.

 If you look at the type signature of execState, you'll see that unless
 the state type 's' involves IO, the return type can't involve IO.

 It can help to run little examples of this.  Here's a GHCi transcript:

 Prelude :m Control.Monad.State
 Prelude Control.Monad.State let addToState :: Int - State Int ();
 addToState x = do s - get; put (s+x)
 Prelude Control.Monad.State let mAdd4 = addToState 4
 Prelude Control.Monad.State :t mAdd4
 m :: State Int ()
 Prelude Control.Monad.State let s = execState mAdd4 2
 Prelude Control.Monad.State :t s
 s :: Int
 Prelude Control.Monad.State s
 6

 In the above, addToState is a monadic function that adds its argument x
 to the current state.  mAdd4 is a monadic value that adds 4 to whatever
 state it's eventually provided with.  When execState provides it with an
 initial state of 2, the monadic computation is run, and the returned
 result is 6, which is an Int, not a monadic type.

  Or is it possible to call a function in a monad and return a pure
  result? I think that is what the original poster was asking?

 If you use a function like execState (depending on the monad), you can
 typically run a monadic computation and get a non-monadic result.
 However, if you're doing that inside a monadic function, you still have
 to return a value of monadic type - so typically, you use 'return',
 which lifts a value into the monad.

  I know that unsafePerformIO can do this, but I thought that was a bit
  of a hack.

 IO is a special monad which has side effects.  unsafePerformIO is just
 one of the functions that can run IO actions, but because the monad has
 side effects, this is unsafe in general.  With a pure monad like State,
 there's no such issue.

 Anton

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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: Can we come out of a monad?

2010-07-30 Thread Anton van Straaten

Kevin Jardine wrote:

I think that these are therefore the responses to the original
questions:


I am of the understanding that once you into a monad, you cant get out of it?


You can run monadic functions and get pure results. 


Some clarifications:

First, many monads (including State) are completely pure in a 
referential transparency sense, so the issue we're discussing is not a 
question of whether results are pure (in general) but rather whether 
they're monadic or not, i.e. whether the type of a result is something 
like Monad m = m a, or just a.


Second, what I was calling a monadic function is a function of type:

  Monad m = a - m b

These are the functions that bind (=) composes.  When you apply these 
functions to a value of type a, you always get a monadic value back of 
type m b, because the type says so.


These functions therefore *cannot* do anything to escape the monad, 
and by the same token, a chain of functions composed with bind, or the 
equivalent sequence of statements in a 'do' expression, cannot escape 
the monad.


It is only the monadic values (a.k.a. actions) of type m b that you 
can usually run using a runner function specific to the monad in 
question, such as execState (or unsafePerformIO).


(Note that as Lyndon Maydwell pointed out, you cannot escape a monad 
using only Monad type class functions.)



So it looks like in that sense you can get out of it.


At this level, you can think of a monad like a function (which it often 
is, in fact).  After you've applied a function to a value and got the 
result, you don't need the function any more.  Ditto for a monad, except 
that for monads, the applying is usually done by a monad-specific runner 
function.


Anton

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
I think that we are having a terminology confusion here. For me, a
pure function is one that does not operate inside a monad. Eg. ++,
map, etc.

It was at one point my belief that although code in monads could call
pure functions, code in pure functions could not call functions that
operated inside a monad.

I was then introduced to functions such as execState and
unsafePerformIO which appear to prove that my original belief was
false.

Currently I am in a state of deep confusion, but that is OK, because
it means that I am learning something new!

Kevin

On Jul 30, 11:55 am, Anton van Straaten an...@appsolutions.com
wrote:
 Kevin Jardine wrote:
  I think that these are therefore the responses to the original
  questions:

  I am of the understanding that once you into a monad, you cant get out of 
  it?

  You can run monadic functions and get pure results.

 Some clarifications:

 First, many monads (including State) are completely pure in a
 referential transparency sense, so the issue we're discussing is not a
 question of whether results are pure (in general) but rather whether
 they're monadic or not, i.e. whether the type of a result is something
 like Monad m = m a, or just a.

 Second, what I was calling a monadic function is a function of type:

    Monad m = a - m b

 These are the functions that bind (=) composes.  When you apply these
 functions to a value of type a, you always get a monadic value back of
 type m b, because the type says so.

 These functions therefore *cannot* do anything to escape the monad,
 and by the same token, a chain of functions composed with bind, or the
 equivalent sequence of statements in a 'do' expression, cannot escape
 the monad.

 It is only the monadic values (a.k.a. actions) of type m b that you
 can usually run using a runner function specific to the monad in
 question, such as execState (or unsafePerformIO).

 (Note that as Lyndon Maydwell pointed out, you cannot escape a monad
 using only Monad type class functions.)

  So it looks like in that sense you can get out of it.

 At this level, you can think of a monad like a function (which it often
 is, in fact).  After you've applied a function to a value and got the
 result, you don't need the function any more.  Ditto for a monad, except
 that for monads, the applying is usually done by a monad-specific runner
 function.

 Anton

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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: Can we come out of a monad?

2010-07-30 Thread Daniel Díaz
I don't understand why to call impure to the types instances of a class.
Monad is simply a class with their methods. Even the pure list is a monad.
The only difference between Monad and other classes is do notation, and only
affects notation.

The impure side is a type, not a class: IO.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Ivan Lazar Miljenovic
Kevin Jardine kevinjard...@gmail.com writes:

 I think that we are having a terminology confusion here. For me, a
 pure function is one that does not operate inside a monad. Eg. ++,
 map, etc.

No, a pure function is one without any side effects.

 It was at one point my belief that although code in monads could call
 pure functions, code in pure functions could not call functions that
 operated inside a monad.

Not at all.  I can do something like map (liftM succ) [Just 2,
Nothing], where liftM is a monadic function.  The thing is that I'm
applying it to a pure monad (i.e. the Maybe monad doesn't have side
effects).

 I was then introduced to functions such as execState and
 unsafePerformIO which appear to prove that my original belief was
 false.

unsafePerformIO is the wild-card here; it's whole purpose is to be able
to say that this IO action (usually linking to a C library or some
such) is pure, promise!!!.

 Currently I am in a state of deep confusion, but that is OK, because
 it means that I am learning something new!

The big point here that you seem to be tied up in is that Monad /=
impure.

I see three broad classifications of Monads:

1) Data structures that can be used as monads, such as [a] and Maybe a.

2) Special monadic wrappers/transformers such as State, Reader,
   etc. which allow you to act as if something is being done
   sequentially (which is the whole point of =) but is actually a pure
   function.  The ST monad also appears to be able to be used like this
   if you use runST.

3) Side-effect monads: IO, STM, ST (used with stToIO), etc.  The
   classical monads, so to speak which you seem to be thinking about.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Anton van Straaten

Kevin Jardine wrote:

I think that we are having a terminology confusion here. For me, a
pure function is one that does not operate inside a monad. Eg. ++,
map, etc.


Ivan Miljenovic has already given a good response, to which I'll only 
add this:


I suspect that your idea of the meaning of purity came from 
over-generalization from the IO monad.  IO actions may be impure, but 
that's not true of all other monad types.  (Most are actually pure.)


Really, the IO monad is a horrible exception to normal monadic behavior, 
and in an ideal world it should only be introduced as a special case 
after gaining a good understanding of monads in general.


Of course in practice, people like their programs to be able to do I/O, 
so the IO monad ends up being one of the first things learned.


It's a bit like teaching a new carpenter about the concept of tools, 
and then starting them out with a chainsaw, leading to the natural 
conclusion that tools are loud, insanely dangerous things.


Anton

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
So far the comments here only increase my confusion (which as I say,
is not bad because it means that I am learning something!).

As a Haskell newbie, the first thing I learned about monads is that
they have a type signature that creates a kind of mud you can't wash
off.

eg.

f :: String - MyMonad String

By mentioning the monad, you get to use its special functions but as a
hard price, you must return a value with a type signature that locks
it within the monad (although you can remove the signature within
other monads using -).

As some people have hinted, perhaps the problem is that most Haskell
newbies are introduced to monads through the IO monad and other monads
are different.

When I plunged into Haskell earlier this year, I had no problem with
understanding static typing, higher level functions and even
separating pure functions from IO functions.

The more I learn about monads, however, the less I understand them.
I've seen plenty of comments suggesting that monads are easy to
understand, but for me they are not.

Cheers,
Kevin

On Jul 30, 12:29 pm, Tillmann Rendel ren...@informatik.uni-
marburg.de wrote:
 C K Kashyap wrote:
  I am of the
  understanding that once you into a monad, you cant get out of it?

 That's not correct.

 There are many monads, including Maybe, [], IO, ... All of these monads
 provide operations (=), return and fail, and do notation implemented
 in terms of these functions, as a common interface. Using just this
 common interface, you cannot get out of the monad.

 But most if not all monads also provide additional operations, specific
 to the monad in question. Often, these operations can be used to get
 out of that monad. For example, with Maybe, you can use pattern matching:

    case do x - return 5
            fail some message
            return (x + 3) of
      Just a   -  a
      Nothing  -  0

 So we can get out of many monads, but we need to know which one it is to
 use the appropriate operation.

 Kevin Jardine wrote:
  I'm still trying to understand how monads interact with types so I am
  interested in this as well.

  From my point of view, the most important fact about monads is:

    There is nothing special about monads!

 The type class Monad behaves like very other type class. A monadic type
 constructor behaves like every other type constructor. The type class
 methods (=), return and fail behave like every other type class
 method. There is nothing special about monads.

 The only speciality of monads is do notation, but do notation is only a
 syntactic convenience, and can be translated into calls of (=), return
 and fail, which, as noted above, are not special in any way.

 So, back to your question, since there is nothing special about monads,
 monads do not interact with types in any special way.

    Tillmann
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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: Can we come out of a monad?

2010-07-30 Thread Colin Paul Adams
 Kevin == Kevin Jardine kevinjard...@gmail.com writes:

Kevin The more I learn about monads, however, the less I understand
Kevin them.  I've seen plenty of comments suggesting that monads
Kevin are easy to understand, but for me they are not.

I used to have the same problem.

Then I read:

http://ertes.de/articles/monads.html

and after that it was very clear.
-- 
Colin Adams
Preston Lancashire
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Ivan Lazar Miljenovic
Anton van Straaten an...@appsolutions.com writes:

 Ivan Miljenovic has already given a good response

Why thank you, kind sir!

/me bows

 I suspect that your idea of the meaning of purity came from
 over-generalization from the IO monad.  IO actions may be impure, but
 that's not true of all other monad types.  (Most are actually pure.)

 Really, the IO monad is a horrible exception to normal monadic
 behavior, and in an ideal world it should only be introduced as a
 special case after gaining a good understanding of monads in general.

Actually, the general consensus seems to be nowadays that people should
be taught IO without any mentions to monads at all (there are various
tutorials around, and if memory serves RWH does this as well), then
introduce the concept of monads and then say oh, btw, that IO thing
we've been using all this time?  It's also one of these weird monad
things.

 It's a bit like teaching a new carpenter about the concept of tools,
 and then starting them out with a chainsaw, leading to the natural
 conclusion that tools are loud, insanely dangerous things.

Heh, I like this analogy.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Ivan Lazar Miljenovic
Kevin Jardine kevinjard...@gmail.com writes:

 The more I learn about monads, however, the less I understand them.
 I've seen plenty of comments suggesting that monads are easy to
 understand, but for me they are not.

How did you learn monads?

More and more people seem to be getting away from trying to say that
monads are containers/burritos/etc. and just teaching them by way of the
definition, either = and return or just join (ignoring that wart known
as fail); Tillman alluded to this approach earlier.

One way of doing so (e.g. by RWH) is to use these definitions in a
specific (non-IO) monad (usually a parser) and then generalise them.  If
you want an alternative to RWH that takes this approach, I've found Tony
Morris' take on this to be reasonable:

Slides (currently seem to be down):
http://projects.tmorris.net/public/what-does-monad-mean/artifacts/1.0/chunk-html/index.html
 

Video: http://vimeo.com/8729673

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Brent Yorgey
On Fri, Jul 30, 2010 at 03:46:09AM -0700, Kevin Jardine wrote:
 
 When I plunged into Haskell earlier this year, I had no problem with
 understanding static typing, higher level functions and even
 separating pure functions from IO functions.
 
 The more I learn about monads, however, the less I understand them.
 I've seen plenty of comments suggesting that monads are easy to
 understand, but for me they are not.

Lies.  Monads are not easy to understand.  Anyone who says otherwise
is selling something (likely a monad tutorial that they wrote).  Or
else they are saying it out of a well-meaning but misguided idea that
telling people that monads are easy will make it so, because the real
problem with monads is only that people THINK they are hard.  So if
only everyone stopped freaking out and realized that learning about
monads is actually easy, perhaps helped by a playing a recorded voice
at night crooning to you in soothing tones that you can achieve
anything you like by just visualizing your success and realizing that
you have already had the power within you all along, then learning
monads will be a snap!

Lies.  

Even worse, this misguided but common insistence that monads are easy
to understand inevitably makes people feel stupid when they discover
that they aren't.

Monads are hard to understand.  But they are *worth understanding*.

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
On Jul 30, 1:11 pm, Brent Yorgey byor...@seas.upenn.edu wrote:

 Monads are hard to understand.  But they are *worth understanding*.

That's the most inspiring and encouraging statement I've seen all
week.

Thanks!

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Tillmann Rendel

Hi,

I wrote:

There is nothing special about monads!


Kevin Jardine wrote:

I've seen plenty of comments suggesting that monads are easy to
understand, but for me they are not.


My point was that monads are not a language feature whith special 
treatment of the compiler, but more like a design pattern or a standard 
interface, a way of using the language. There is no compiler magic about 
monads. Therefore, they can, in principle, be understand by reading 
their definition in Haskell.


Nevertheless, I agree that it is hard to understand monads, because they 
are a clever way of using Haskell and use several of Haskell's more 
advanced features.


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Anton van Straaten

Kevin Jardine wrote:

As a Haskell newbie, the first thing I learned about monads is that
they have a type signature that creates a kind of mud you can't wash
off.


There are places where you can't wash it off, and places where you can.


eg.

f :: String - MyMonad String

By mentioning the monad, you get to use its special functions but as a
hard price, you must return a value with a type signature that locks
it within the monad


That's perfectly correct: you must return a value with a type signature 
that locks it within the monad.  That's because you're referring here 
to returning a value from a monadic function with a return type of 
MyMonad String.  But that's just one part of the picture.


Consider a caller of that function: after applying f to some string, it 
ends up with a value of type MyMonad String.  One of the things you can 
typically do with such values is wash off the mud using a runner 
function, specific to the monad.


They're called runners (informally) because what they do is run the 
delayed computation represented by the monad.  In the case of the State 
monad, the runner takes an initial state and supplies it to the monad in 
order to start the computation.  If these runners didn't exist, the 
monad would be rather useless, because it would never actually execute. 
 The result of running that computation typically eliminates the monad 
type - the mud is washed off.


You can even do this inside a monadic function, e.g.:

g m = do s - get
 let x = evalState m s   -- wash the mud off m !
 ...

But the value of x above will be locked inside the function - you can't 
return such values to the caller without using e.g. return x, to 
return a monadic value.


So you may be able to wash the mud off a monadic value, but if you want 
to pass that value outside a monadic function you have to put the mud 
back on first.


However, if you have a monadic value *outside* a monadic function, no 
such rule applies.



The more I learn about monads, however, the less I understand them.
I've seen plenty of comments suggesting that monads are easy to
understand, but for me they are not.


Monads are very general, which means they're not easily learned by the 
common style of extrapolating from examples.  They're easy to understand 
in hindsight though!  :-}


Anton

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Ertugrul Soeylemez
Hello,

it's a bit hidden in Haskell, but a monad instance consists of three
functions:

  fmap   :: (a - b) - (m a - m b)
  return :: a - m a
  join   :: m (m a) - m a

Nothing more is needed to define a monad.  In Haskell, a monad is
expressed by 'return' and (=) instead, but this is equivalent.

The types of these functions tell you what you can do with the monad.
You can put values into it and you can turn a doubly wrapped monadic
value into a singly wrapped monadic value (usually by dropping
information).

Unless there is a function, which has deeper comprehension of a monadic
value than these two functions, like 'runState' or 'head', you can never
get values out of it.  For the IO monad no such function can exist.
This is intentional.


Greets,
Ertugrul


C K Kashyap ckkash...@gmail.com wrote:

 Hi,
 In the code here -
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
 If I look at the type of modifiedImage, its simply ByteString - but isn't it
 actually getting into and back out of the state monad? I am of the
 understanding that once you into a monad, you cant get out of it? Is this
 breaking the monad scheme?



-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Ivan Lazar Miljenovic
Ertugrul Soeylemez e...@ertes.de writes:

 Hello,

 it's a bit hidden in Haskell, but a monad instance consists of three
 functions:

   fmap   :: (a - b) - (m a - m b)

You don't even need fmap defined for it to be a monad, since fmap f m =
liftM f m = m = (return . f)

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/30/10 06:06 , Kevin Jardine wrote:
 I think that we are having a terminology confusion here. For me, a
 pure function is one that does not operate inside a monad. Eg. ++,
 map, etc.
 
 It was at one point my belief that although code in monads could call
 pure functions, code in pure functions could not call functions that
 operated inside a monad.
 
 I was then introduced to functions such as execState and
 unsafePerformIO which appear to prove that my original belief was
 false.
 
 Currently I am in a state of deep confusion, but that is OK, because
 it means that I am learning something new!

A monad is just a wrapper that lets you take an action of some kind whenever
the wrapped value is operated on.

Pure means referentially transparent; that is, it should always be
possible to substitute an expression for its expansion without changing its
meaning.

Now, certain specific monads (IO, ST, STM) are used specifically for
operations that are *not* referentially transparent.  Those operations are
therefore confined to occurring only within the monad wrapper; ST allows you
to extract a referentially transparent value (although it's up to the
programmer to enforce that, and the only consequences for violation are
potential odd program behaviors), the others do not without doing evil things.

*** Eye-bleedy ahead; skip the next paragraph if you are in over your head. ***

In the case of ST and STM, it is possible to pull values back out; in the
case of ST, this means that non-referentially-transparent operations can
take place behind the curtain as long as what emerges from the curtain is
the same as would happen with a referentially transparent version (this is
used when it's more efficient to alter values in place than to produce new
values), while STM operations can only be extracted to IO (STM is in some
sense an extension of IO) and IO operations can only be extracted by running
the program or using unsafePerformIO (or its cousins unsafeInterleaveIO and
unsafeIOtoST/unsafeSTtoIO), which are labeled unsafe specifically because
they're exposing non-referentially-transparent operations which are
therefore capable of causing indeterminate program behavior.

*** resuming the flow ***

The majority of monads (State, Writer, Reader, etc.) are entirely
referentially transparent in their workings; in these cases, the wrapper is
used simply to add a hook that is itself referentially transparent.  The
three mentioned above are all quite similar, in that the hook just carries
a second value along and the monad definition includes functions that can
operate on that value (get, gets, put, modify; tell; ask, asks, local).
Other referentially transparent monads are used to provide controllable
modification of control flow:  Maybe and (Either a) let you short-circuit
evaluation based on a notion of failure; list aka [] lets you operate on
values in parallel, with backtracking when a branch fails.  Cont is the
ultimate expression of this, in effect allowing the hook to be evaluated
at any time by the wrapped operation; as such, it's worth studying, but it
will probably warp your brain a bit.  (It's possible to derive any of the
referentially transparent monads from Cont.)

The distinction between these two classes, btw, lies in whether the hook
allows things to escape.  In the case of ST, IO, and STM, the hook carries
around an existentially qualified type, which by definition cannot be given
a type outside of the wrapper.  (Think of it this way:  it's existentially
qualified because its existence is qualified to only apply within the wrapper.)

*** more eye-bleedy ahead ***

In many IO implementations, IO is just ST with a magic value that can
neither be created nor modified nor destroyed, simply passed around.  The
value is meaningless (and, in ghc, at least, nonexistent!); only its type is
significant, because the type prevents anything using it from escaping.  The
other half of this trick is that operations in IO quietly use (by
reference) this value, so that they are actually partially applied
functions; this is why we refer to IO actions.  An action in this case
is simply a partially applied function which is waiting for the magic
(non-)value to be injected into it before it can produce a value.  In
effect, it's a baton passed between actions to insure that they take place
in sequence.  And this is why the unsafe functions are unsafe; they allow
violation of the sequence enforced by the baton.  unsafePerformIO goes
behind the runtime's back to pull a copy of the baton out of the guts of the
runtime and feeds it to an I/O action; unsafeInterleaveIO clones the
baton(!); unsafeIOtoST doesn't actually do anything other than hide the
baton, but the only thing you can do with it then is pass it to unsafeSTtoIO
- --- which is really unsafePerformIO under the covers.  (The purpose of those
two functions is that ST's mutable arrays are identical to IO's mutable
arrays, and 

Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/30/10 11:48 , Ivan Lazar Miljenovic wrote:
 Ertugrul Soeylemez e...@ertes.de writes:
 it's a bit hidden in Haskell, but a monad instance consists of three
 functions:

   fmap   :: (a - b) - (m a - m b)
 
 You don't even need fmap defined for it to be a monad, since fmap f m =
 liftM f m = m = (return . f)

fmap/join and return/bind are isomorphic; given either set, you can produce
the other.  The usual category-theory definition of monads uses the former;
Haskell uses the latter, because it allows operations to easily be chained
together.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxS9foACgkQIn7hlCsL25Uc2ACgoLG8uti3d0oWrv1H56fRJ3W4
xZIAn1KotatZklktHpKEwdib6AKXrNOr
=Io9w
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread wren ng thornton

Ivan Lazar Miljenovic wrote:

More and more people seem to be getting away from trying to say that
monads are containers/burritos/etc. and just teaching them by way of the
definition, either = and return or just join


You always need return. The choice of primitives is:

return, (=)

or:

fmap, return, join

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread wren ng thornton

Brandon S Allbery KF8NH wrote:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/30/10 11:48 , Ivan Lazar Miljenovic wrote:

Ertugrul Soeylemez e...@ertes.de writes:

it's a bit hidden in Haskell, but a monad instance consists of three
functions:

  fmap   :: (a - b) - (m a - m b)

You don't even need fmap defined for it to be a monad, since fmap f m =
liftM f m = m = (return . f)


fmap/join and return/bind are isomorphic; given either set, you can produce
the other.


No. fmap+join is isomorphic to bind. Your options are (fmap,return,join) 
or (return,bind). There is no way to get by without the return, since 
that's the natural transformation necessary for entering the monad in 
the first place.


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