Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-09 Thread David Virebayre
On Fri, Aug 6, 2010 at 5:58 PM, Alex Stangl a...@stangl.us wrote:
 On Fri, Aug 06, 2010 at 10:17:26AM -0500, aditya siram wrote:
 From my vantage point they are (in no particular order) : Reader, Writer,
 State, IO, ST, STM, Parsec (have I missed any?) and of course the
 transformer versions. I am debating whether or not to add [] to the bunch.

 Not sure how much time you have budgeted, but I'd start with a simple
 one like Maybe, actually show how to implement it, then move on to list,

I second that. Especially, if the audience is more familiar with
imperative langages, then the reader, writer and state monad may not
immediately impress them.

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


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-09 Thread wren ng thornton

aditya siram wrote:

Thanks all for you suggestions!
Upon further reflection I realized that my audience is more pragmatic than
theoretical. Instead of emphasizing how monads are constructed and the monad
laws I think I want to dive right into the most common and useful monads.

From my vantage point they are (in no particular order) : Reader, Writer,

State, IO, ST, STM, Parsec (have I missed any?) and of course the
transformer versions. I am debating whether or not to add [] to the bunch.


Whether you add [] or not, you should definitely include Maybe. Maybe 
captures the most basic kind of fallible computation, so it shows up all 
over the place with pragmatic coding. Compare against null pointers, 
returning -1 to signal error when a positive number is the expected 
return, using 0 to express an infinite limit on some kind of resource, 
etc. Maybe does the same thing, except it does them cleanly and 
correctly because we express the possibility of failure in the type 
system instead of relying on magic values to express them. Magic 
values are even worse than magic numbers and other magic constants, IMO.


Once you've explained Maybe, you can mention (Either a) in passing; they 
should figure out the generalization immediately.


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


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-09 Thread aditya siram
Yes I think that showing the Maybe and List implementation of monads is
essential. They're practical and in a lot of ways they represent two
completely different types of computation demonstrating the flexibility of
the Monad abstraction. Thanks for that suggestion.
-deech


On Mon, Aug 9, 2010 at 4:33 AM, wren ng thornton w...@freegeek.org wrote:

 aditya siram wrote:

 Thanks all for you suggestions!
 Upon further reflection I realized that my audience is more pragmatic than
 theoretical. Instead of emphasizing how monads are constructed and the
 monad
 laws I think I want to dive right into the most common and useful monads.

 From my vantage point they are (in no particular order) : Reader, Writer,

 State, IO, ST, STM, Parsec (have I missed any?) and of course the
 transformer versions. I am debating whether or not to add [] to the bunch.


 Whether you add [] or not, you should definitely include Maybe. Maybe
 captures the most basic kind of fallible computation, so it shows up all
 over the place with pragmatic coding. Compare against null pointers,
 returning -1 to signal error when a positive number is the expected return,
 using 0 to express an infinite limit on some kind of resource, etc. Maybe
 does the same thing, except it does them cleanly and correctly because we
 express the possibility of failure in the type system instead of relying on
 magic values to express them. Magic values are even worse than magic
 numbers and other magic constants, IMO.

 Once you've explained Maybe, you can mention (Either a) in passing; they
 should figure out the generalization immediately.

 --
 Live well,
 ~wren

 ___
 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] Suggestions For An Intro To Monads Talk.

2010-08-06 Thread aditya siram
Thanks all for you suggestions!
Upon further reflection I realized that my audience is more pragmatic than
theoretical. Instead of emphasizing how monads are constructed and the monad
laws I think I want to dive right into the most common and useful monads.
From my vantage point they are (in no particular order) : Reader, Writer,
State, IO, ST, STM, Parsec (have I missed any?) and of course the
transformer versions. I am debating whether or not to add [] to the bunch.

To explain monads (now that I have Timothy's awesome blog post to reference)
I'll be drawing the parallel between monads and interfaces in Java. And
thanks to Tillman for showing me where the analogy breaks down. Are there
any such parallels in other languages like Perl and Python?

I'm still a little iffy on why the monad concept isn't used in other
languages. From where I sit it seems as though monads really let you play
with the order of evaluation - just because one statement is executed after
another doesn't mean they are executed in that order. I think other
languages don't make this easy.

-deech

On Wed, Aug 4, 2010 at 6:21 PM, Daniel van den Eijkel d...@gmx.net wrote:

  For me, the following two things did the magic, so I'll suggest them:

 1.
 Writing a recursive function that takes a binary tree and returns the same
 tree, but with its leaves enumerated. Each function call takes the tree and
 the counter and returns the resulting tree and the new counter value. The
 pattern that emerges is similar to the state monad. The pattern shows that
 the order of the recursive calls is not ambiguous, unlike in a function that
 just counts the leaves, for example. Changing the order of the recursive
 calls changes the result.
 (code below)

 2.
 Putting the above pattern into a datatype and rewriting the apply-funtion
 for this datatype (=) allows only to apply funtions in a non-ambiguous
 way. Not giving a deconstructor for the IO monad forces the programmer to
 decide in which order calls to IO functions have to be done.

 I hope this is clear enough; I was able to use the IO monad at the moment I
 realized that Haskell uses this kind of trick to ensure that the order of
 execution of function arguments is always well-defined and never ambiguous.
 Of course, there is much more about monads, but this was my entry point.

 Best regards
 Daniel


 code (tree enumeration):

 data Tree a = Leaf a | Node (Tree a) (Tree a) deriving Show

 enumTree n (Node a b) =
  let (n', a')  = enumTree n a in
  let (n'', b') = enumTree n' b in
  (n'', Node a' b')

 enumTree n (Leaf x) = (n+1, Leaf n)





 aditya siram schrieb:

 Hi all,
 I am doing an Intro To Monads talk in September [1]. The audience
 consists of experienced non-Haskell developers but they will be familiar
 with basic functional concepts (closures, first-class functions etc.).

 I am looking for suggestions on how to introduce the concept and its
 implications. I'd also like to include a section on why monads exist and why
 we don't really see them outside of Haskell.

 Has anyone here done a talk like this? And if so what parts of your
 presentation were successful and what would you stay away from.

 Thanks for the feedback.
 -deech

 [1] It's in St.Louis, Missouri at the St.Louis Perl Mongers 
 meetinghttp://St.Louis%20Perl%20Mongers%20meetingso come on by if you're 
 around!

 --

 ___
 Haskell-Cafe mailing 
 listhaskell-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] Suggestions For An Intro To Monads Talk.

2010-08-06 Thread Alex Stangl
On Fri, Aug 06, 2010 at 10:17:26AM -0500, aditya siram wrote:
 From my vantage point they are (in no particular order) : Reader, Writer,
 State, IO, ST, STM, Parsec (have I missed any?) and of course the
 transformer versions. I am debating whether or not to add [] to the bunch.

Not sure how much time you have budgeted, but I'd start with a simple
one like Maybe, actually show how to implement it, then move on to list,
and then finally talk about Reader, Writer, State, etc. from a more high
level perspective. Hopefully people would grok the monad concept by that
point, and should realize how useful it is to add logging, or state,
etc. Then they may wonder about mixing in more than 1, so that could
lead to transformers.


 To explain monads (now that I have Timothy's awesome blog post to reference)
 I'll be drawing the parallel between monads and interfaces in Java. And
 thanks to Tillman for showing me where the analogy breaks down. Are there
 any such parallels in other languages like Perl and Python?

I get the type class / Java interface analogy, but trying to draw a
parallel between Java interface and monads seems likely to just create
confusion IMHO.


 I'm still a little iffy on why the monad concept isn't used in other
 languages. From where I sit it seems as though monads really let you play
 with the order of evaluation - just because one statement is executed after
 another doesn't mean they are executed in that order. I think other
 languages don't make this easy.

I first encountered monads in OCaml. And the concept exists in other languages,
although maybe not always explicitly by that name.

Good luck, should be a good talk,

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


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-06 Thread Stephen Tetley
At version 2 Parsec was an amalgamation of a state and error monad -
by amalgamation I mean the data types and Monad instance encoded the
combination directly, it wasn't made from transformers. Version 3 of
Parsec complicates things a quite a bit.

If you're addressing Perl programmers, you could try and encode the
monads in Perl and see what it looks like. Maybe Mark Jason Dominus
the author of Higher Order Perl has done this already?


On 6 August 2010 16:17, aditya siram aditya.si...@gmail.com wrote:
 [SNIP] I think I want to dive right into the most common and useful monads.
 From my vantage point they are (in no particular order) : Reader, Writer,
 State, IO, ST, STM, Parsec (have I missed any?) and of course the
 transformer versions. I am debating whether or not to add [] to the bunch.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-06 Thread Jonathan Geddes
On Fri, Aug 6, 2010 at 9:17 AM, aditya siram aditya.si...@gmail.com wrote:

 Upon further reflection I realized that my audience is more pragmatic than 
 theoretical. Instead of emphasizing how monads are constructed and the monad 
 laws I think I want to dive right into the most common and useful monads. 
 From my vantage point they are (in no particular order) : Reader, Writer, 
 State, IO, ST, STM, Parsec (have I missed any?) and of course the transformer 
 versions. I am debating whether or not to add [] to the bunch.

If your audience is indeed a pragmatic lot then they will not be
interested in the same things as a more theoretical crowd (obviously).
So they might not be interested in Monads at all. You've got your work
cut out for you!
With that said, I would suggest starting with the advantages of
purity. I would guess that 95% of bugs in imperative code are related
to some erroneous state. Pure code, on the other hand is immune to
this huge class of bugs. Sometimes state is useful or even necessary
(stateful computations, IO, in-place algorithms, etc), so you really
can't forgo state entirely. The cool thing about Monads is they allow
us to have our cake and eat it too! We can model stateful computations
in pure code. You might also mention the separation of pure and impure
code and how this helps us to reason about a program.

 I'm still a little iffy on why the monad concept isn't used in other 
 languages. From where I sit it seems as though monads really let you play 
 with the order of evaluation - just because one statement is executed after 
 another doesn't mean they are executed in that order. I think other languages 
 don't make this easy.


My guess would be that other languages have much less commitment to
purity. You don't need Monads in other languages because state is
implicit, everything is in the IO monad, in a sense. While Monads are
still an excellent abstraction in other languages they're often more
awkward than just using implicit state/IO/whatever operations. Haskell
has some sweet built-in syntax for monads.
Also related to advantages of purity:
http://www.haskell.org/haskellwiki/Why_Haskell_just_works
I think this approach (stating benefits of purity and maybe laziness)
would be more interesting to a pragmatic crowd. Just a guess though.
Good luck with your presentation!
--Jonathan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-06 Thread David Sankel
On Fri, Aug 6, 2010 at 11:17 AM, aditya siram aditya.si...@gmail.comwrote:

 I'm still a little iffy on why the monad concept isn't used in other
 languages.


The greatest feat that monads have accomplished, in my opinion, is providing
the right mathematical abstraction for declaring side-effect and stateful
computation in a pure functional language. For the first time it was now
possible for a pure functional programming language to be a general purpose
programming language. That's was quite an accomplishment!

The second most important feat of monads was their close offspring, the
monad transformers. These guys gave pure functional programmers the ability
to maintain invariants on which side-effect/stateful computations their end
users are going to use. This enhanced verifiability by a measured mix of
pure and impure.

The other languages that you mention are impure. So feat #1 is pointless
since they were already general purpose without monads, and feat #2 is
not realistically achievable since impure languages generally don't have a
way of restricting a function from having arbitrary side-effects.

There have been some clever things done with monads aside from #1 and #2.
Parsec is one, but it seems applicative functors are a better match for the
parsing domain. Other things are neat, but not killer features that would
turn the head of a pragmatist of the impure type in my opinion.

So, that is why I think the monad concept isn't generally used in other
languages.

David

-- 
David Sankel
Sankel Software
www.sankelsoftware.com
585 617 4748 (Office)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-06 Thread Gregory Crosswhite
 It might be a little late at this point, but here's my take on monads:

In most imperative languages sequencing of statements is a feature that
is hard-coded into the language to act in a certain way, e.g. to have a
particular implicit state (the global state plus possibly the fields
available from a class, if the code is in a method).  In Haskell,
sequencing of statements is a first-class feature of the language that
we can define to work however we want.  For example, the Maybe monad
allows us to define the sequencing operation to abort whenever we access
a Maybe value that is Nothing.  In most languages they have to introduce
a special keyword return to get this kind of early-exit functionality,
but in Haskell we don't need such a keyword because Monads allow us to
extend the sequencing operation to *add* this kind of functionality.

Similarly, in most languages you cannot completely change the implicit
state available to code;  the most that you can do is to use
Object-Oriented programming, which is an additional feature to the
language, to add additional implicit state that is available to code
(when it is inside a method) that stacks on top of the global state.  By
contrast, in Haskell defining an implicit state for code is trivial, and
furthermore we can do additional things like forcing this state to be
read-only, all without having to add new features to the language itself.

Not only is sequencing is a first-class operation that we can define at
will, but it is also possible to compose the functionality of multiple
sequencing operations so that, for example, we can get access to both a
read-only state, a global mutable state, *and* have the ability to
perform an early exit from our code, all (again) within the language. 
This technique is known as stacking Monad transformers, and there are
multiple libraries for doing it.

Finally, here is something that is trivial to do in Haskell:  create a
sequencing operation based on continuations that allows code to perform
operations asynchronously while writing code in a synchronous style. 
That is, you can define a monad that lets you write code that looks like

do
result - request x
case result of
A - request y
B - request z

which has the feature that rather than blocking a thread while we wait
for a request, we instead actually implicitly creates a callback that
runs the rest of the code as soon as the result as ready.  In most other
languages you'd have to invent a special language features such as
continuations in order to allow for a coding style like this, but in
Haskell we don't need them because *overriding the sequence operation
itself* is a first-class feature of the language that allows us to do this.

So again, the moral of this story is that just like having access to
continuations as a first-class object allows one to do powerful things,
so too does having access to the sequencing operation as a first-class
object let us do stuff that makes our job as programmers easier.

Cheers,
Greg

On 08/06/10 08:17, aditya siram wrote:
 Thanks all for you suggestions!
 Upon further reflection I realized that my audience is more pragmatic
 than theoretical. Instead of emphasizing how monads are constructed
 and the monad laws I think I want to dive right into the most common
 and useful monads. From my vantage point they are (in no particular
 order) : Reader, Writer, State, IO, ST, STM, Parsec (have I missed
 any?) and of course the transformer versions. I am debating whether or
 not to add [] to the bunch.

 To explain monads (now that I have Timothy's awesome blog post to
 reference) I'll be drawing the parallel between monads and interfaces
 in Java. And thanks to Tillman for showing me where the analogy breaks
 down. Are there any such parallels in other languages like Perl and
 Python?

 I'm still a little iffy on why the monad concept isn't used in other
 languages. From where I sit it seems as though monads really let you
 play with the order of evaluation - just because one statement is
 executed after another doesn't mean they are executed in that order. I
 think other languages don't make this easy.

 -deech

 On Wed, Aug 4, 2010 at 6:21 PM, Daniel van den Eijkel d...@gmx.net
 mailto:d...@gmx.net wrote:

 For me, the following two things did the magic, so I'll suggest them:

 1.
 Writing a recursive function that takes a binary tree and returns
 the same tree, but with its leaves enumerated. Each function call
 takes the tree and the counter and returns the resulting tree and
 the new counter value. The pattern that emerges is similar to the
 state monad. The pattern shows that the order of the recursive
 calls is not ambiguous, unlike in a function that just counts the
 leaves, for example. Changing the order of the recursive calls
 changes the result.
 (code below)

 2.
 Putting the above pattern into a datatype and rewriting the
 

Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-06 Thread Stephen Tetley
On 6 August 2010 20:47, David Sankel cam...@gmail.com wrote:

 There have been some clever things done with monads aside from #1 and #2.
 Parsec is one, but it seems applicative functors are a better match for the
 parsing domain.

Monadic bind is very, very handy for parsing, giving you context
sensitive parsing if you need it.

If you have a grammar that is LL1 plus helpers (i.e. the extended
Kleene operators - many1, sepBy etc.) then applicative formalism is
nice and as Doaitse Swierstra has shown provides good opportunities
for optimization; but I'd hasten to call it a better match in general.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-04 Thread Tillmann Rendel

Hi,

aditya siram wrote:

For example in the beginning it was useful for me to think of monads
(and typeclasses really) as approximating Java interfaces.


Type classes are somewhat parallel to Java interfaces, but Monad is a 
*specific* type class, so it should be somewhat parallel to a *specific* 
Java interface, if at all.



Type classes are somewhat parallel to Java interfaces because a Java 
interface


  interface Foo {
Result method (Argument argument);
  }

declares that there is a set of types so that every type T in that set 
has an operation (T, Argument) - Result, with these operations all 
implemented specifically to particular type T. In Haskell, the type class


  class Foo t where
method : t - Argument - Result

expresses a similar concept. There are a number of differences though:

Firstly, in Java, calls to the method are late bound, while in Haskell, 
they are early bound. However, a kind of late bound behavior can be 
achieved using existentials.


Secondly, in Java, the receiver of the method has to be of type T, and T 
may not appear at other positions in the type of the method, while in 
Haskell, T may appear anywhere in the type of the method, even more then 
once.


Finally, in Java, T has to be a proper type (of kind *), while in 
Haskell, it may be an improper type (of a kind involving -).



Already for the type class Functor, these differences become relevant.

  class Functor f where
fmap :: (a - b) - f a - f b

f has kind (* - *), and it is mentioned twice in the type of fmap.


Conclusion: While Haskell type classes have some similarities to Java 
interfaces, the type class Functor (or Monad, if you like) is not that 
similar to any Java interface, because it uses features specific to 
Haskell type classes which are not available in Java interfaces.



Nevertheless, it may be helpful for a Java developer to understand that 
Haskell type classes are more similar to Java interfaces than to Java 
classes.


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


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-04 Thread Hans Aberg

On 3 Aug 2010, at 23:51, aditya siram wrote:

I am doing an Intro To Monads talk in September [1]. The audience  
consists of experienced non-Haskell developers but they will be  
familiar with basic functional concepts (closures, first-class  
functions etc.).


I am looking for suggestions on how to introduce the concept and its  
implications. I'd also like to include a section on why monads exist  
and why we don't really see them outside of Haskell.


Probably because one does not bother writing them out in the type  
system. I wrote on a C++ wrap for Guile, and they showed up when  
typing expressions, though C++ templates are too limited to make this  
efficiently.


The monad has a code lifting property. If one has code which has both  
non-monadic and monadic components, it can be lifted up to the monadic  
level without having iterates (can be taken away with the monad  
projection).


So if one has code which has both non-IO and IO components, it can be  
lifted to the becoming all IO. Since IO and other imperative  
structures are incompatible with the lazy evaluation default, the type  
system can be used to describe them using monads.


Then one can use syntactic sugar like do and = to make the code  
look like ordinary imperative code.


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


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-04 Thread Daniel van den Eijkel




For me, the following two things did the magic, so I'll suggest them:

1.
Writing a recursive function that takes a binary tree and returns the
same tree, but with its leaves enumerated. Each function call takes the
tree and the counter and returns the resulting tree and the new counter
value. The pattern that emerges is similar to the state monad. The
pattern shows that the order of the recursive calls is not ambiguous,
unlike in a function that just counts the leaves, for example. Changing
the order of the recursive calls changes the result.
(code below)

2. 
Putting the above pattern into a datatype and rewriting the
apply-funtion for this datatype (=) allows only to apply
funtions in a non-ambiguous way. Not giving a deconstructor for the IO
monad forces the programmer to
decide in which order calls to IO functions have to be done.

I hope this is clear enough; I was able to use the IO monad at the
moment I realized that Haskell uses this kind of "trick" to ensure that
the order of execution of function arguments is always well-defined and
never ambiguous. Of course, there is much more about monads, but this
was my entry point.

Best regards
Daniel


code (tree enumeration):

data Tree a = Leaf a | Node (Tree a) (Tree a) deriving Show

enumTree n (Node a b) =
let (n', a') = enumTree n a in
let (n'', b') = enumTree n' b in 
(n'', Node a' b')

enumTree n (Leaf x) = (n+1, Leaf n)





aditya siram schrieb:
Hi all,
I am doing an "Intro To Monads" talk in September [1]. The audience
consists of experienced non-Haskell developers but they will be
familiar with basic functional concepts (closures, first-class
functions etc.). 
  
I am looking for suggestions on how to introduce the concept and its
implications. I'd also like to include a section on why monads exist
and why we don't really see them outside of Haskell.
  
Has anyone here done a talk like this? And if so what parts of your
presentation were successful and what would you stay away from.
  
Thanks for the feedback.
-deech
  
[1] It's in St.Louis, Missouri at the St.Louis Perl
Mongers meeting so come on by if you're around!
  

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



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


[Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-03 Thread aditya siram
Hi all,
I am doing an Intro To Monads talk in September [1]. The audience consists
of experienced non-Haskell developers but they will be familiar with basic
functional concepts (closures, first-class functions etc.).

I am looking for suggestions on how to introduce the concept and its
implications. I'd also like to include a section on why monads exist and why
we don't really see them outside of Haskell.

Has anyone here done a talk like this? And if so what parts of your
presentation were successful and what would you stay away from.

Thanks for the feedback.
-deech

[1] It's in St.Louis, Missouri at the St.Louis Perl Mongers
meetinghttp://St.Louis%20Perl%20Mongers%20meetingso come on by if
you're around!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-03 Thread Dan Piponi
On Tue, Aug 3, 2010 at 2:51 PM, aditya siram aditya.si...@gmail.com wrote:
 I am doing an Intro To Monads talk in September [1].
 ...what would you stay away from.

Some things to stay away from:

http://byorgey.wordpress.com/2009/01/12/abstraction-intuition-and-the-monad-tutorial-fallacy/

(Though I secretly harbour a belief that there is a correct metaphor
that everyone should be using. :-)
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-03 Thread aditya siram
Thanks for reminding me. Although I wonder if there is a difference between
drawing metaphors (monads are burritos etc.) and drawing parallels. For
example in the beginning it was useful for me to think of monads (and
typeclasses really) as approximating Java interfaces. Now this parallel dies
pretty quickly but it was something for me to hold onto while internalizing
the concepts. Is there a danger in telling people this?

-deech

On Tue, Aug 3, 2010 at 5:36 PM, Dan Piponi dpip...@gmail.com wrote:

 On Tue, Aug 3, 2010 at 2:51 PM, aditya siram aditya.si...@gmail.com
 wrote:
  I am doing an Intro To Monads talk in September [1].
  ...what would you stay away from.

 Some things to stay away from:


 http://byorgey.wordpress.com/2009/01/12/abstraction-intuition-and-the-monad-tutorial-fallacy/

 (Though I secretly harbour a belief that there is a correct metaphor
 that everyone should be using. :-)
 --
 Dan

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


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-03 Thread TIMOTHY MICHAEL CARSTENS

On Aug 3, 2010, at 4:44 PM, aditya siram wrote:

Thanks for reminding me. Although I wonder if there is a difference between 
drawing metaphors (monads are burritos etc.) and drawing parallels.

Since they are experienced developers, your audience will want to know how to 
use monads to solve problems they can already solve in other languages.  
Drawing parallels is the quickest way to bootstrap this.

For example in the beginning it was useful for me to think of monads (and 
typeclasses really) as approximating Java interfaces. Now this parallel dies 
pretty quickly but it was something for me to hold onto while internalizing the 
concepts. Is there a danger in telling people this?

I believe you can draw such a parallel safely (I wrote an extended example of 
this [1] which received good feedback on ycombinator and bad feedback on 
reddit's r/haskell).  Use the familiar to bootstrap the idea, then generalize 
from there.  Certainly it would be bad to use such an example and not explain 
where it breaks down, but on the other hand, an example like this will get them 
on board much faster than a monad is anything satisfying the following 
axioms...

As you suggested at the beginning of the thread, they will wonder why they 
don't see monads in other languages.  I'm sure someone else has thought about 
this more than I have, but the absence of type classes and good syntactic 
support is likely the main culprit.

Depending on time allotted, you might not have a chance to include any good 
killer examples of why monads are valuable.  If you do have the time, though, 
I've found that people respond well to examples of parsec [2].

1. 
https://intoverflow.wordpress.com/2010/07/20/i-come-from-java-and-want-to-know-what-monads-are-in-haskell/
2. http://hackage.haskell.org/package/parsec-3.0.0


-deech

On Tue, Aug 3, 2010 at 5:36 PM, Dan Piponi 
dpip...@gmail.commailto:dpip...@gmail.com wrote:
On Tue, Aug 3, 2010 at 2:51 PM, aditya siram 
aditya.si...@gmail.commailto:aditya.si...@gmail.com wrote:
 I am doing an Intro To Monads talk in September [1].
 ...what would you stay away from.

Some things to stay away from:

http://byorgey.wordpress.com/2009/01/12/abstraction-intuition-and-the-monad-tutorial-fallacy/

(Though I secretly harbour a belief that there is a correct metaphor
that everyone should be using. :-)
--
Dan

ATT1..txt

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


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-03 Thread Ozgur Akgun
Today I read this fantastic blog post:
You Could Have Invented Monads! (And Maybe You Already Have.)
http://blog.sigfpe.com/2006/08/you-could-have-invented-monads-and.html

You most probably have seen the post by now, but I just wanted to remind it,
just in case.

Best,

On 3 August 2010 22:51, aditya siram aditya.si...@gmail.com wrote:

 Hi all,
 I am doing an Intro To Monads talk in September [1]. The audience
 consists of experienced non-Haskell developers but they will be familiar
 with basic functional concepts (closures, first-class functions etc.).

 I am looking for suggestions on how to introduce the concept and its
 implications. I'd also like to include a section on why monads exist and why
 we don't really see them outside of Haskell.

 Has anyone here done a talk like this? And if so what parts of your
 presentation were successful and what would you stay away from.

 Thanks for the feedback.
 -deech

 [1] It's in St.Louis, Missouri at the St.Louis Perl Mongers 
 meetinghttp://St.Louis%20Perl%20Mongers%20meetingso come on by if you're 
 around!

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




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


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-03 Thread Alexander Solla


On Aug 3, 2010, at 2:51 PM, aditya siram wrote:

I am looking for suggestions on how to introduce the concept and its  
implications. I'd also like to include a section on why monads exist  
and why we don't really see them outside of Haskell.


Start with functors (things that attach values/functions/functors to  
values in an algebra).  Move on to applicative functors (functors that  
can interpret the thing that is getting things attached to it).  Move  
on to monads (applicative functors where you can explicitly control  
the order of evaluation/interpretation).


Monads exist because every adjunction generates a monad, every monad  
generates an adjunction, and adjunctions are everywhere.  Any time you  
can put things next to each other, you can create a monad that  
captures the notion.  A monad corresponds to putting things to the  
left (at least syntactically) of the main object.  A comonad  
corresponds to putting things to the right of the main object  
(assuming we observe the monad = left convention).


There are monads every where.  They typically carry around extra  
structure in other programming languages.  That is, you can't quantify  
over them, because they have been specialized.  For example, any  
language that has a map function automatically supports monadic  
computation, in virtue of the fact that map accepts one argument  
functions.  (I.e., functions where the function's name goes on the  
left, and the argument goes on the right)


sub minus_one = { $x = @_[0]; return $x * (-1); }

return map minus_one
map double
map square [1.. 10]

(I hardly remember Perl now though...)  Notice that you can't change  
the order of the operations without changing the semantics.  This is  
strictly a monadic computation, in Perl, PHP, etc.  Ruby is a little  
nicer than Perl, since it allows functors other than lists.  If you  
make a class a member of the Enumerate mixin, you can call .each on  
the class's instances, give it a monadic (one argument) function, and  
it returns a new functor over the relevant type of object.


funky_tree.each { node | node.value.square.double.minus_one }
(in the function composition case, or ... in the structurally  
moandic case:)


funky_tree.each { node | node.value }
   .each { value | square value }
   .each { square' | double square' }
   .each { doubled | minus_one double }

I doubt this is legal Ruby either.  It's been a few years since I  
touched it.

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


Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-03 Thread Colin Paul Adams
 Alexander == Alexander Solla a...@2piix.com writes:

Alexander On Aug 3, 2010, at 2:51 PM, aditya siram wrote:

 I am looking for suggestions on how to introduce the concept and its
 implications. I'd also like to include a section on why monads
 exist and why we don't really see them outside of Haskell.

Alexander Start with functors (things that attach
Alexander values/functions/functors to values in an algebra).  Move
Alexander on to applicative functors (functors that can interpret
Alexander the thing that is getting things attached to it).  Move
Alexander on to monads

Too late! The audience has already dozed off.

Alexander (applicative functors where you can
Alexander explicitly control the order of
Alexander evaluation/interpretation).


-- 
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] Suggestions For An Intro To Monads Talk.

2010-08-03 Thread C K Kashyap
Hi,
Please take a look at this video
http://videoarch1.s-inf.de/FP.2005-SS-Giesl.(COt).HD_Videoaufzeichnung/2005-SS-FP.U09.2005-07-06.HDV.avi

Here Monad's are explained as something that helps making your program
modular. The teacher gives an example implementation of an expression
evaluator with and without monads. It takes a complete rewrite to
incorporate changes in the program without monads where as only minor tweaks
are required for the implementation with monads - also, its easier to
identify the location where change needs to be done and the change is
isolated.

And the flow is pretty nice - as in, people will not doze off :)

Regards,
Kashyap

On Tue, Aug 3, 2010 at 10:04 PM, Colin Paul Adams
co...@colina.demon.co.ukwrote:

  Alexander == Alexander Solla a...@2piix.com writes:

Alexander On Aug 3, 2010, at 2:51 PM, aditya siram wrote:

  I am looking for suggestions on how to introduce the concept and its
 implications. I'd also like to include a section on why monads
 exist and why we don't really see them outside of Haskell.

 Alexander Start with functors (things that attach
Alexander values/functions/functors to values in an algebra).  Move
Alexander on to applicative functors (functors that can interpret
Alexander the thing that is getting things attached to it).  Move
Alexander on to monads

 Too late! The audience has already dozed off.

Alexander (applicative functors where you can
Alexander explicitly control the order of
Alexander evaluation/interpretation).


 --
 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




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