Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Kim-Ee Yeoh


Ronald Guida wrote:
 
 Here is the brief explanation I came up with:
   Arrows and monads are abstract data types used to construct Domain
   Specific Embedded Languages (DSELs) within Haskel.  A simple arrow
   provides a closed DSEL.  A monad is a special type of arrow that
   creates an open DSEL by allowing users to embed arbitrary Haskel
   within it.
 
 Is this an accurate explanation?  I hate to feed a fire, but is
 Domain Specific Embedded Language a well-defined phrase, or is it
 just another example of linguistic cruft?
 

Neither. It's the latest buzzword, joining the likes of AOP and
Generics. Haskell has an opportunity to ride the DSEL bandwagon,
and like most such opportunities it can take her where she don't
want to go.


Ronald Guida wrote:
 
 Also, is this a /useful/ explanation, or have I simply hidden the
 complexity by invoking the concepts of ADTs and DSELs?
 

It certainly has a nice spin. I've nominated you to the Monad
Marketing Team already.

-- 
View this message in context: 
http://www.nabble.com/Explaining-monads-tf4244948.html#a12140216
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-14 Thread apfelmus

Stefan O'Rear wrote:

apfelmus wrote:



My assumption is that we have an equivalence

  forall a,b . m (a - m b) ~ (a - m b)

because any side effect executed by the extra m on the outside can well 
be delayed until we are supplied a value a. Well, at least when all 
arguments are fully applied, for some notion of fully applied


I figured that wouldn't be a problem since our values don't escape, and
the functions we define all respect the embedding... More formally:

Projections and injections:

  proj :: Monad m = m (a - m b) - (a - m b)

proj ma = \x - ma = \fn' - fn' x
inj  fn = return fn

Define an equivalence relation:

ma ≡ mb - proj ma = proj mb



Projection respects equivalence:

ma ≡ mb - proj ma = proj mb(intro -)
ma ≡ mb = proj ma = proj mb(equiv def)
proj ma = proj mb = proj ma = proj mb  (assumption)

Application respects equivalence:


Yeah, that's the right approach, but it has a few typos. The correct 
version is


 (@) :: Monad m = m (a - m b) - m a - m b
 (@) ma = \x - x = proj ma

Formulating (@) in terms of  proj ma  is a very clever idea since it 
follows immediately that


 ma @ x = ma' @ x  iff  proj ma = proj ma'  iff  ma ≡ ma'

In other words, when viewed through  @  and  proj  only, equivalent 
actions give equivalent results.



The main point is that this does not hold for the other curry-friendly 
type  m a - m b


 proj :: Monad m = (m a - m b) - (a - m b)
 proj f = f . return

 (@) :: Monad m = (m a - m b) - m a - m b
 (@) = id

 ma ≡ ma'  iff  proj ma = proj ma'

since those functions may execute their argument multiple times. So, 
here's the counterexample


 once  :: Monad m = m A - m A
 once = id

 twice :: Monad m = m A - m A
 twice x = x  once x

Now, we have

 proj once = return = proj twice

but

 effect :: IO ()   -- a given effect
 effect = putStrLn Kilroy was here!

 once  @ effect = effect
 ≠ twice @ effect = effect  effect


The same can be done for several arguments, along the lines of

  proj2 :: m (a - m (b - m c)) - (a - b - m c)
  proj2 f = proj . (proj f)

  app2 :: m (a - m (b - m c)) - (m a - m b - m c)
  app2 f mx my
   = (f @ mx) @ my
   = my = proj (mx = proj f)
   = my = \y - mx = \x - proj2 f x y

and similar results.

Regards,
apfelmus

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Dougal Stanton
On 14/08/07, Ronald Guida [EMAIL PROTECTED] wrote:

 My present goal is to understand monads well enough to be able to
 explain them to others.  I wonder if it's possible to create a
 tutorial that explains monads well enough so that they just make
 sense or click for people.

It seems everyone wants to do this, with not much success! :-(

From reading this thread (piecemeal rather than in one concentrated
session) I get the impression that no-one agrees on what, if anything,
a monad is. If there were a wiki page What_Is_A_Monad and all these
ideas were whittled down whenever a counter-proof (such as Identity or
Reader) were raised --- what would be left?

I get the impression it would look like this:

  (return x) = f == f x
  m = return == m
  (m = f) = g == m = (\x - f x = g)

And then where would we be? ;-)

I say all this from the point of view of someone who has a reasonably
robust intuitive idea of monads that still fails to encompass the List
monad. I too would like to understand the overall idea to this monad
malarkey...

Cheers,

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


[Haskell-cafe] Parsec: Parenthesized expressions and more!

2007-08-14 Thread Vimal
Hi

I was trying out some parsing with parsec. I tried:
Accepting proper parenthesized expressions, this was the
code:

parens :: Parser ()
parens = do
  char '('
  parens
  char ')'
  parens
  | return ()

Implementing basically: S - (S)S | e.

I doubt the fact that 'e' was actually considered, because
the program seems to be accepting all strings of the form
())*. Did I go wrong somewhere? I guess this could be because,
the input was partially accepted. Can I force it to derive the
entire input string?

And, btw, is there a method to implement an epsilon production?
I tried
do { string  ; rules ... }
And it didn't seem to work.

I am also trying out this problem just for fun, but I seem to be getting
wrong answers! http://spoj.pl/problems/FOOL
Maybe I implemented something wrong. So, i will wait for some comments
on the above parsing, and try one more time before I ask questions on that :D

Cheers
-- 
-- Vimal
Department of Computer Science and Engineering
Indian Institute of Technology Madras
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Parsec: Parenthesized expressions and more!

2007-08-14 Thread Christian Maeder
Vimal wrote:
 Hi
 
 I was trying out some parsing with parsec. I tried:
 Accepting proper parenthesized expressions, this was the
 code:
 
 parens :: Parser ()
 parens = do
   char '('
   parens
   char ')'
   parens
   | return ()

I would indent | return () a bit less:
...
parens
  | return ()

Use parens  eof to test for full string consumption.

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


Re: [Haskell-cafe] Re: Explaining monads

2007-08-14 Thread Bertram Felgenhauer
Benjamin Franksen wrote:
 Brian Brunswick wrote:
  One thing that I keep seeing people say (not you), is that
  monads /sequence/ side effects. This is wrong, or at
  least a limited picture.
  
  /All/ of the above structures are about combining compatible things things
  together in a row.
 
 I am a bit astonished.
 
 Let's take the simplest example: Maybe. The effect in question is the
 premature abortion of a computation (when Nothing is returned). And of
 course Maybe sequences these effects, that's what you use it for: the
 _first_ action to be encountered that returns Nothing aborts the
 computation. Clearly sequencing goes on here.

sequencing is an overloaded term.

Dan Weston said in an earlier thread that monads sequence denotationally,
but not necessarily operationally. Brian makes the same point.
I also believe that this is an important distinction to make.

 I won't talk about List Monad because I always had difficulty understanding
 the List Monad.

Maybe that's because the distinction of denotational and operational
sequencing actually matters for the list monad.

I'll try to explain.

Consider

   a = b = c

This is equivalent to

   [()]  a = b = c

We can think of this as defining a tree with three levels:

  - () at the root.

  - 'a' produces the children of the root.
  - 'b' and 'c' each add another level to the tree - given a node
from the previous level, they produce the children of that node.

In other words, you *specify* a breadth first traversal of that
tree, and you *sequence* the subsequent levels of that traversal.

The catch here is lazy evaluation - each intermediate list of the
breadth first traversal is produced incrementally so what you get
at run time is actually a *depth first* traversal. As a result,
there's no nice sequencing anymore, operationally.

HTH,

Bertram

P.S.
  The explanation I gave above is deliberately simplified - it's
  actually only an explanation of the list *arrow*.

  The list monad allows the structure of the traversal to be
  different for various subtrees of a node. Consider

  [()]  [1,2,3] = \n - if odd n then [n] else [1..n] = \m - [n+m]

  which produces the following tree:

()
+- n=1
|  `- 1
+- n=2
|  +- m=1
|  |  `- 3
|  `- m=2
| `- 4
`- n=3
   `- 3

  This tree no longer has uniform levels. In my opinion the best way to
  think of this is operationally, as a depth first traversal.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Converting Emacs syntax coloured Haskell code to HTML

2007-08-14 Thread Peter Verswyvelen
I noticed many code snippets on the wiki that have syntax colouring.

 

How is this done? Can I convert syntax coloured code from Emacs to HTML? 

 

I'm using the Haskell mode for Emacs to get the syntax colouring.

 

I'm writing a monads for C# programmers tutorial (oh no) and would
like to use this feature. 

 

Of course I won't publish this tutorial before sending it to this mailing
list, because when a newbie writes a tutorial, it is usually a disaster ;-)

 

But the feedback I get from this community is super handy (that is when it
is not PhD talk which I don't understand ;), so I guess comments on this
tutorial will give me a better understanding.

 

Thanks,

Peter

 

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


Re: [Haskell-cafe] Converting Emacs syntax coloured Haskell code to HTML

2007-08-14 Thread Alfonso Acosta
M-x htmlize-buffer

On 8/14/07, Peter Verswyvelen [EMAIL PROTECTED] wrote:




 I noticed many code snippets on the wiki that have syntax colouring.



 How is this done? Can I convert syntax coloured code from Emacs to HTML?



 I'm using the Haskell mode for Emacs to get the syntax colouring.



 I'm writing a monads for C# programmers tutorial (oh no) and would
 like to use this feature.



 Of course I won't publish this tutorial before sending it to this mailing
 list, because when a newbie writes a tutorial, it is usually a disaster ;-)



 But the feedback I get from this community is super handy (that is when it
 is not PhD talk which I don't understand ;), so I guess comments on this
 tutorial will give me a better understanding.



 Thanks,

 Peter


 ___
 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] Converting Emacs syntax coloured Haskell code to HTML

2007-08-14 Thread Bas van Dijk
On 8/14/07, Peter Verswyvelen [EMAIL PROTECTED] wrote:
 I noticed many code snippets on the wiki that have syntax colouring.

 How is this done? Can I convert syntax coloured code from Emacs to HTML?

Look at HsColour:

http://www.cs.york.ac.uk/fp/darcs/hscolour/

regards,

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Lanny Ripple
Having just gone through all the tutorials and things (again but 
this time I think it stuck) the Haskell community is on the wrong 
track as far as teaching Monads to new programmers.


If I were teaching addition and multiplication to children I 
wouldn't start with, We'll begin by defining an algebraic 
structure named a Group.  From there we'll expand our concept 
to a Ring and Field.  A group is a set and a binary operator 
usually named + (or sometimes *) such that


No no no.  You start with, You all know how to count from one to 
10.  If we have 1 item and we 'add' another 1 item we have 2 
items.  We write this 1+1=2.


The tutorials seriously need to step back and start with 
something like, To enforce order of evaluation we evaluate 
closures* returning a defined type.  The first closure will feed 
its result to the second which will in turn feed it's result to 
the third.  Since the third closure can't be evaluated without 
having the results from the second and first (and thus they had 
to be evaluated earlier in time) we get a defined evaluation 
sequence.  Here are some examples...


(* Even using the word 'closure' is scary for those not familiar 
with them.)


Then, like Monads For Functional Programming (the paper that 
finally clicked Monads for me) you point out that evaluating all 
these closures returning a defined type in various ways form a 
structure (which you can then explain) and we can use that 
structure and change out the underlying effect(s) as needed.


Now of course if your new programmer has the the necessary 
background you can throw them in the deep end.  But don't do that 
to someone coming at the language from something like Java 
learned out of a business degree course.  (My background is a CS 
degree with math minor and it still took two go-s at Haskell 
before I got as far as understanding what folks were talking 
about with Monads.  Wish I had found Wadler's MFFP the first time 
around.)  Where are the shallow end tutorials?  (Don't get me 
wrong.  The tutorials are good but there is also a place for the 
learn-by-rote with lots of examples ones too.)


  $0.02,
  -ljr

PS - Not so much directed at Ronald's post but his was convenient 
to get me on my soapbox.


Ronald Guida wrote:

My present goal is to understand monads well enough to be able to
explain them to others.  I wonder if it's possible to create a
tutorial that explains monads well enough so that they just make
sense or click for people.

--
Lanny Ripple [EMAIL PROTECTED]
ScmDB / Cisco Systems, Inc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Bathroom reading

2007-08-14 Thread Dougal Stanton
I'm looking for cool but mind-bending examples of functional brilliance.

Let us say, hypothetically, you had a bathroom without any reading
material. And having read all the Dilbert and Garfield you could
seriously stomach, decide you should educate yourself while on the
job. :-)

So you decide to print up some one-liner style programs into a
little booklet. Something between credit-card and postcard sized, with
a neat but mind-bending program on it. Don Stewart occasionally swoops
in with some fixpoint malarkey to defuse heated discussions. I mean
that kind of thing, but with a slightly wider scope than just fibs...

Suggestions, please!

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Sebastian Sylvan
On 14/08/07, Lanny Ripple [EMAIL PROTECTED] wrote:
 Having just gone through all the tutorials and things (again but
 this time I think it stuck) the Haskell community is on the wrong
 track as far as teaching Monads to new programmers.

 If I were teaching addition and multiplication to children I
 wouldn't start with, We'll begin by defining an algebraic
 structure named a Group.  From there we'll expand our concept
 to a Ring and Field.  A group is a set and a binary operator
 usually named + (or sometimes *) such that

 No no no.  You start with, You all know how to count from one to
 10.  If we have 1 item and we 'add' another 1 item we have 2
 items.  We write this 1+1=2.

 The tutorials seriously need to step back and start with
 something like, To enforce order of evaluation we evaluate
 closures* returning a defined type.  The first closure will feed
 its result to the second which will in turn feed it's result to
 the third.  Since the third closure can't be evaluated without
 having the results from the second and first (and thus they had
 to be evaluated earlier in time) we get a defined evaluation
 sequence.  Here are some examples...

 (* Even using the word 'closure' is scary for those not familiar
 with them.)

 Then, like Monads For Functional Programming (the paper that
 finally clicked Monads for me) you point out that evaluating all
 these closures returning a defined type in various ways form a
 structure (which you can then explain) and we can use that
 structure and change out the underlying effect(s) as needed.

 Now of course if your new programmer has the the necessary
 background you can throw them in the deep end.  But don't do that
 to someone coming at the language from something like Java
 learned out of a business degree course.  (My background is a CS
 degree with math minor and it still took two go-s at Haskell
 before I got as far as understanding what folks were talking
 about with Monads.  Wish I had found Wadler's MFFP the first time
 around.)  Where are the shallow end tutorials?  (Don't get me
 wrong.  The tutorials are good but there is also a place for the
 learn-by-rote with lots of examples ones too.)


Agreed, people tend to complicate things in the interest of being
precise, which is probably a misstake when dealing with
non-mathematicians.

I like the very light weight analogy (which works for most practical
uses of monads) that a monadic action is a recipe (you can even say
that they're stored in sealed envelopes to model the opaqueness of
e.g. IO). You can store recipes in boxes (data structures), pass them
around,  combine them to make new recipes etc. That's an abstraction
of actions that everyone is familiar with. The analogy might not fit
everything perfectly, but at least the reader will be with you from
the start, and that makes it more likely that they'll follow you when
you start diverging from the metaphor. Then you say that the GHC
runtime system is the cook, who will take the main recipe and follow
it.



-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bathroom reading

2007-08-14 Thread Bas van Dijk
On 8/14/07, Dougal Stanton [EMAIL PROTECTED] wrote:
 I'm looking for cool but mind-bending examples of functional brilliance.

 Let us say, hypothetically, you had a bathroom without any reading
 material. And having read all the Dilbert and Garfield you could
 seriously stomach, decide you should educate yourself while on the
 job. :-)

 So you decide to print up some one-liner style programs into a
 little booklet. Something between credit-card and postcard sized, with
 a neat but mind-bending program on it. Don Stewart occasionally swoops
 in with some fixpoint malarkey to defuse heated discussions. I mean
 that kind of thing, but with a slightly wider scope than just fibs...

 Suggestions, please!

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


Maybe:

http://www.haskell.org/haskellwiki/Blow_your_mind

and:

http://haskell.org/haskellwiki/Research_papers/Functional_pearls

regards,

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


Re: [Haskell-cafe] Bathroom reading

2007-08-14 Thread Brandon S. Allbery KF8NH


On Aug 14, 2007, at 11:17 , Dougal Stanton wrote:


Let us say, hypothetically, you had a bathroom without any reading
material. And having read all the Dilbert and Garfield you could
seriously stomach, decide you should educate yourself while on the
job. :-)


Sounds to me like you want a waterproof panel displaying #haskell.  :)

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Bathroom reading

2007-08-14 Thread Spencer Janssen
On Tuesday 14 August 2007 10:17:53 Dougal Stanton wrote:
 I'm looking for cool but mind-bending examples of functional brilliance.

 Let us say, hypothetically, you had a bathroom without any reading
 material. And having read all the Dilbert and Garfield you could
 seriously stomach, decide you should educate yourself while on the
 job. :-)

 So you decide to print up some one-liner style programs into a
 little booklet. Something between credit-card and postcard sized, with
 a neat but mind-bending program on it. Don Stewart occasionally swoops
 in with some fixpoint malarkey to defuse heated discussions. I mean
 that kind of thing, but with a slightly wider scope than just fibs...

 Suggestions, please!

 D.

Here's a small puzzle: without using a Haskell interpreter, explain what 
the 'foo' function does.

 foo = filterM (const [True, False])

In case you aren't familiar, here's the definition of filterM:

 filterM  :: (Monad m) = (a - m Bool) - [a] - m [a]
 filterM _ [] =  return []
 filterM p (x:xs) =  do
flg - p x
ys  - filterM p xs
return (if flg then x:ys else ys)


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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Jeff Polakow
Hello,

There is clearly a problem with the Haskell/monad tutorials out there...

 The tutorials seriously need to step back and start with 
 something like, To enforce order of evaluation we evaluate 
 closures* returning a defined type.  The first closure will feed 
 its result to the second which will in turn feed it's result to 
 the third.  Since the third closure can't be evaluated without 
 having the results from the second and first (and thus they had 
 to be evaluated earlier in time) we get a defined evaluation 
 sequence.  Here are some examples...
 
The style of this description is nice; however the description itself is 
wrong. 

Monads DO NOT determine order of evaluation. Previous posts on this thread 
give several examples. 

In lazy languages, data dependencies determine the order of evaluation. X 
must be evaluated before Y if Y depends upon the result of X. You can 
force the order of evaluation without using a monad just as you can have a 
monad which does not determine the order in which things get evaluated.

From the point of view of a programmer, a monad is simply a useful 
(higher-order) combinator pattern. All monadic code can be flattened by 
replacing occurrences of bind (=) with it's definition.

One general intuition about monads is that they represent computations 
rather than simple (already computed) values:

x :: Int   -- x is an Int

x :: Monad m = m Int  -- x is a computation of an Int

x :: [Int] -- x is a computation of an Int which can 
return multiplie values

x :: Maybe Int -- x is a computation of an Int which might 
fail (return Nothing)

x :: State s Int   -- x is a computation of an Int which relies 
on, and returns (possibly modified) 
   --   a value of type s. Note: State s Int is 
isomorphic to: s - (Int,s)

x :: IO Int-- x is a computation of an Int which can 
interact with the outside world.

Return explains how to make a simple computation which returns a specified 
value.
Bind explains how to use the result of a computation to compute something 
else.
 
-Jeff


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bathroom reading

2007-08-14 Thread Brent Yorgey

 So you decide to print up some one-liner style programs into a
 little booklet. Something between credit-card and postcard sized, with
 a neat but mind-bending program on it. Don Stewart occasionally swoops
 in with some fixpoint malarkey to defuse heated discussions. I mean
 that kind of thing, but with a slightly wider scope than just fibs...


Clearly, we need to actually put together such a book!  I'm imagining
something where you have two mostly blank facing pages, with the code by
itself in the middle of the right page; then the next 2-4 pages devoted to a
short discussion of the code, how it works, related issues and techniques,
and a list of references.  All featuring beautiful typography and fantastic
writing, of course. =)

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Lanny Ripple
Look!  You are doing it again!  :)  Does that paragraph even 
contain the word Monad?  :)


I'm aware a monad is an abstraction and as such it doesn't *do* 
anything.  My point was along the lines that you don't need to 
know that your working in a field to be able to learn that


   3/2 = 1.5

.

  -ljr

Jeff Polakow wrote:


Hello,

There is clearly a problem with the Haskell/monad tutorials out there...

  The tutorials seriously need to step back and start with
  something like, To enforce order of evaluation we evaluate
  closures* returning a defined type.  The first closure will feed
  its result to the second which will in turn feed it's result to
  the third.  Since the third closure can't be evaluated without
  having the results from the second and first (and thus they had
  to be evaluated earlier in time) we get a defined evaluation
  sequence.  Here are some examples...
 
The style of this description is nice; however the description itself is 
wrong.


Monads DO NOT determine order of evaluation. Previous posts on this 
thread give several examples.


In lazy languages, data dependencies determine the order of evaluation. 
X must be evaluated before Y if Y depends upon the result of X. You can 
force the order of evaluation without using a monad just as you can have 
a monad which does not determine the order in which things get evaluated.


 From the point of view of a programmer, a monad is simply a useful 
(higher-order) combinator pattern. All monadic code can be flattened by 
replacing occurrences of bind (=) with it's definition.


One general intuition about monads is that they represent computations 
rather than simple (already computed) values:


x :: Int   -- x is an Int

x :: Monad m = m Int  -- x is a computation of an Int

x :: [Int] -- x is a computation of an Int which can 
return multiplie values


x :: Maybe Int -- x is a computation of an Int which might 
fail (return Nothing)


x :: State s Int   -- x is a computation of an Int which relies 
on, and returns (possibly modified)
   --   a value of type s. Note: State s Int is 
isomorphic to: s - (Int,s)


x :: IO Int-- x is a computation of an Int which can 
interact with the outside world.


Return explains how to make a simple computation which returns a 
specified value.
Bind explains how to use the result of a computation to compute 
something else.
 
-Jeff


---

This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.


--
Lanny Ripple [EMAIL PROTECTED]
ScmDB / Cisco Systems, Inc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Alex Queiroz
Hallo,

On 8/14/07, Jeff Polakow [EMAIL PROTECTED] wrote:

 Hello,

 There is clearly a problem with the Haskell/monad tutorials out there...

  The tutorials seriously need to step back and start with
   something like, To enforce order of evaluation we evaluate
   closures* returning a defined type.  The first closure will feed
   its result to the second which will in turn feed it's result to
   the third.  Since the third closure can't be evaluated without
   having the results from the second and first (and thus they had
   to be evaluated earlier in time) we get a defined evaluation
   sequence.  Here are some examples...
  
 The style of this description is nice; however the description itself is
 wrong.

 Monads DO NOT determine order of evaluation. Previous posts on this thread
 give several examples.


 And his point was completely missed.

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Dan Piponi
On 8/14/07, Jeff Polakow [EMAIL PROTECTED] wrote:
 One general intuition about monads is that they represent computations
 rather than simple (already computed) values:

 x :: Int   -- x is an Int
 x :: Monad m = m Int  -- x is a computation of an Int

What's a computation? It seems to me that in a lazy language, x::Int
represents a computation of an int, not an already computed value.
x::[Int] is a computation that returns multiple values. x::(Int,Int)
is a computation that returns a pair of values. x::() is a computation
that returns nothing. x::Map a b is a computation that gives a way to
associate values of type a with values of type b. Some of these are
monads, some are not. What's the difference between them? Why are you
calling certain values computations?
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Dan Piponi
On 8/14/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 I like the very light weight analogy (which works for most practical
 uses of monads) that a monadic action is a recipe

Many introductory programming books present the idea of a program as a
recipe. Here's a recipe for computing factorials:

fact 0 = 1
fact n = n*fact (n-1)

Where do monads come in?
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Jeff Polakow
Hello,

 Look!  You are doing it again!  :)  Does that paragraph even 
 contain the word Monad?  :)
 
Sorry. Your first paragraph led me to believe you were writing about 
monads.

 I'm aware a monad is an abstraction and as such it doesn't *do* 
 anything.  My point was along the lines that you don't need to 
 know that your working in a field to be able to learn that
 
 3/2 = 1.5
 
I agree.

I think one of the problem with understanding monads comes from people 
mistakenly believing monads force an order of evaluation. This is a 
shortcoming of general Haskell tutorials which fail to convey that the 
order of evaluation is determined by data dependencies. If new programmers 
know that monads have nothing to do with forcing the order of evaluation 
when they start learning about monads, then maybe they will be less 
confused as they sort out what monads are actually used for.

-Jeff




---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Bathroom reading

2007-08-14 Thread Chad Scherrer
Maybe something of these?

http://www.haskell.org/haskellwiki/Blow_your_mind

-- 

Chad Scherrer

Time flies like an arrow; fruit flies like a banana -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Derek Elkins
On Tue, 2007-08-14 at 09:55 -0500, Lanny Ripple wrote:
 Having just gone through all the tutorials and things (again but 
 this time I think it stuck) the Haskell community is on the wrong 
 track as far as teaching Monads to new programmers.
 
 If I were teaching addition and multiplication to children I 
 wouldn't start with, We'll begin by defining an algebraic 
 structure named a Group.  From there we'll expand our concept 
 to a Ring and Field.  A group is a set and a binary operator 
 usually named + (or sometimes *) such that
 
 No no no.  You start with, You all know how to count from one to 
 10.  If we have 1 item and we 'add' another 1 item we have 2 
 items.  We write this 1+1=2.

For every monad tutorial of the former type, I can find ten of the
latter.  This is not the problem.  A similar complaint is tutorials that
invoke category theory; almost none of them do this either.

What people need to do is stop reading two page blog posts by someone
who's just got monads and read the well-written peer-reviewed papers
by the people who clearly know what they are talking about.  Luckily,
for monads applied to Haskell we have Wadler, a witty, enjoyable and
clear writer/speaker.  All of Wadler's monad introductions are
readable by anyone with a basic grasp of Haskell.  You certainly don't
need to be even remotely an academic to understand them.  I'm willing to
bet that many people who say they don't understand monads and have read
every tutorial about them haven't read -any- of Wadler's papers.

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Sebastian Sylvan
On 14/08/07, Dan Piponi [EMAIL PROTECTED] wrote:
 On 8/14/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
  I like the very light weight analogy (which works for most practical
  uses of monads) that a monadic action is a recipe

 Many introductory programming books present the idea of a program as a
 recipe. Here's a recipe for computing factorials:

 fact 0 = 1
 fact n = n*fact (n-1)

 Where do monads come in?

Well I would try to distinguish between code that we write to compute
values, and values which represent monadic actions when coming up with
analogies. You may wish to explain code as recipes too, but I think
your students would start getting confused if you overload the same
analogy for two different things.

The point was to find some real world analogy for abstraction of an
action. A cooking recipe fits the bill pretty well. Everyone gets
that you can have a model of making pancake batter in the form of
a recipe, and that you can combine such recipes with other recipes or
store them in boxes or whatever. Once you're that far along, you're
half way there in teaching them enough to be able to use most monads
in practice.


-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Lanny Ripple
A very good point.  I even knew that implicitly but wasn't 
thinking in those terms explicitly when writing up my first post 
and it does make a difference in how you view things.


  -ljr

Jeff Polakow wrote:


Hello,

  Look!  You are doing it again!  :)  Does that paragraph even
  contain the word Monad?  :)
 
Sorry. Your first paragraph led me to believe you were writing about 
monads.


  I'm aware a monad is an abstraction and as such it doesn't *do*
  anything.  My point was along the lines that you don't need to
  know that your working in a field to be able to learn that
 
  3/2 = 1.5
 
I agree.

I think one of the problem with understanding monads comes from people 
mistakenly believing monads force an order of evaluation. This is a 
shortcoming of general Haskell tutorials which fail to convey that the 
order of evaluation is determined by data dependencies. If new 
programmers know that monads have nothing to do with forcing the order 
of evaluation when they start learning about monads, then maybe they 
will be less confused as they sort out what monads are actually used for.


-Jeff



---

This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.


--
Lanny Ripple [EMAIL PROTECTED]
ScmDB / Cisco Systems, Inc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Lennart Augustsson
You don't normally call x::Int a computation of an Int because there's
nothing that distinguishes the value of the x from what it was before you
computed it.  So I prefer to regard x as a value (in a domain, of course).
But for x :: (Monad m) = m Int there is something else happening, so the
word computation makes sense.
This is just the terminology people use, not an absolute truth, so you're
free to think it's wrong. :)
BTW, if you regard non-termination as an effect then even x :: Int is a
computation.

  -- Lennart

On 8/14/07, Dan Piponi [EMAIL PROTECTED] wrote:

 On 8/14/07, Jeff Polakow [EMAIL PROTECTED] wrote:
  One general intuition about monads is that they represent computations
  rather than simple (already computed) values:

  x :: Int   -- x is an Int
  x :: Monad m = m Int  -- x is a computation of an Int

 What's a computation? It seems to me that in a lazy language, x::Int
 represents a computation of an int, not an already computed value.
 x::[Int] is a computation that returns multiple values. x::(Int,Int)
 is a computation that returns a pair of values. x::() is a computation
 that returns nothing. x::Map a b is a computation that gives a way to
 associate values of type a with values of type b. Some of these are
 monads, some are not. What's the difference between them? Why are you
 calling certain values computations?
 --
 Dan
 ___
 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] Explaining monads

2007-08-14 Thread Lanny Ripple


Derek Elkins wrote:

What people need to do is stop reading two page blog posts by someone
who's just got monads and read the well-written peer-reviewed papers


I have taught many people to program in group settings and 
individually in my career.  I have referred them to many 
tutorials.  I have used many examples from tutorials I thought 
were useful.  I can't recall a single time I've ever turned to a 
beginner and said, And you really should brush up on the 
peer-reviewed papers to learn this part.



by the people who clearly know what they are talking about.  Luckily,
for monads applied to Haskell we have Wadler, a witty, enjoyable and
clear writer/speaker.  All of Wadler's monad introductions are
readable by anyone with a basic grasp of Haskell.  You certainly don't
need to be even remotely an academic to understand them.  I'm willing to
bet that many people who say they don't understand monads and have read
every tutorial about them haven't read -any- of Wadler's papers.


I'm confused.  Are you praising Wadler or bashing the tutorials 
(or both)?  *I* was carping about the tutorials (and even 
mentioned that Wadler was my breakthrough) so I suspect we are in 
violent agreement.


  -ljr

--
Lanny Ripple [EMAIL PROTECTED]
ScmDB / Cisco Systems, Inc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Jeff Polakow
Hello,

 On 8/14/07, Jeff Polakow [EMAIL PROTECTED] wrote:
  One general intuition about monads is that they represent computations
  rather than simple (already computed) values:
 
  x :: Int   -- x is an Int
  x :: Monad m = m Int  -- x is a computation of an Int
 
 What's a computation? It seems to me that in a lazy language, x::Int
 represents a computation of an int, not an already computed value.

This intuition for monads as computations is independent of operational 
semantics.

 x::[Int] is a computation that returns multiple values. x::(Int,Int)
 is a computation that returns a pair of values. x::() is a computation
 that returns nothing. x::Map a b is a computation that gives a way to
 associate values of type a with values of type b. Some of these are
 monads, some are not. What's the difference between them? Why are you
 calling certain values computations?

Of course, the type [Int] denotes a value which is a list of Ints; 
additionally [Int] can be viewed as a value representing the 
nondeterministic computation of a single Int. Generally, the type Monad m 
= m Int can be viewed as a value representing the computation of an Int. 
However, I do not mean to imply that everything which can be viewed as a 
computation of something is a monad. 

In any case, this is only meant to be a general (i.e. high-level) 
intuition. BTW, this intuition was, more or less, the one used by Moggi 
when describing how monads can be used to describe denotational models for 
languages.

-Jeff


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Brian Brunswick
On 14/08/07, Jeff Polakow [EMAIL PROTECTED] wrote:

 Of course, the type [Int] denotes a value which is a list of Ints;
 additionally [Int] can be viewed as a value representing the
 nondeterministic computation of a single Int. Generally, the type Monad m =
 m Int can be viewed as a value representing the computation of an Int.



But thats not really right. What exactly m Int does /depends/ on m. It might
represent 0 or more computations
of Int, or computations of Int carrying some extra stuff around, or complex
control logic about what the computation does
when.

All that is really given, is that we can feed another 'Int-m a' thingy to
it using bind, and get back an m a, and the
thingy we fed in might even be used zero or more times while doing it.

These 'thingy's are called Kleisli Arrows, by the way.

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


Re: [Haskell-cafe] Bathroom reading

2007-08-14 Thread Dougal Stanton
On 14/08/07, Brent Yorgey [EMAIL PROTECTED] wrote:
 Clearly, we need to actually put together such a book!  I'm imagining
 something where you have two mostly blank facing pages, with the code by
 itself in the middle of the right page; then the next 2-4 pages devoted to a
 short discussion of the code, how it works, related issues and techniques,
 and a list of references.  All featuring beautiful typography and fantastic
 writing, of course. =)

Oh indeed! This wasn't *completely* idle chatter on my part. I used to
work in a print shop and we did a lot of work for art and architecture
students who would do this kind of thing all the time. Fantastic
little notebook-style gifts of images and blank pages and elegant
typography. It's just a shame so many of them were terrible at
spelling! :-P

It shouldn't be too difficult to use LaTeX to this end. Once a
document class has been hammered out you can offer a range of
different booklets! The Evolution of a Haskell Programmer series
would be a good place to start. Bring it to your next job interview to
whip out when someone points to that bit on your CV and says, what's
that?.

Any skilled TeXers in the house?

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Dan Piponi
On 8/14/07, Lennart Augustsson [EMAIL PROTECTED] wrote:
 You don't normally call x::Int a computation of an Int because there's
 nothing that distinguishes the value of the x from what it was before you
 computed it.

Can you spell out exactly what you mean by this?

 So I prefer to regard x as a value (in a domain, of course).
 But for x :: (Monad m) = m Int there is something else happening

When someone uses the phrase something else it implies that we are
talking about two things, a something and a disjoint something
else. For example, if x = [1,2,3] what is the something and what is
the something else? What was the x before [I] computed it and how
does it differ from its value?

 This is just the terminology people use, not an absolute truth, so you're
 free to think it's wrong. :)

For something like this I prefer to think in terms of useful and
not useful. If you find the term computation useful, I might find
it useful too. So I'm jealous as I can't figure out how to use it. :-)
I'm not looking for a formal definition or anything like that. But I
would like a reliable way to distinguish between things that are
computations and things that are not.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Dan Piponi
On 8/14/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 14/08/07, Dan Piponi [EMAIL PROTECTED] wrote:
  Where do monads come in?

 Well I would try to distinguish between code that we write to compute
 values, and values which represent monadic actions when coming up with
 analogies.

How would you make that distinction? At this point I can imagine
students immediately thinking that my factorial program is a recipe
and wondering why it doesn't involve monads. Either you distinguish
between these things in a circular way using monads (no use when
teaching monads in the first place) or you have some a priori
distinction that you point out to students.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Sebastian Sylvan
On 14/08/07, Dan Piponi [EMAIL PROTECTED] wrote:
 On 8/14/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
  On 14/08/07, Dan Piponi [EMAIL PROTECTED] wrote:
   Where do monads come in?
 
  Well I would try to distinguish between code that we write to compute
  values, and values which represent monadic actions when coming up with
  analogies.

 How would you make that distinction?

How can you *not* make a distinction? If you view source code as
recipes, that's fine, but the *code* doesn't even exist in the
program! You can't pass *code* around (unless you do it as String).
Clearly there's a gulf of difference between the source code ASCII
string that represent the factorial function, and a first class value
that represents an action *in* the language.


 At this point I can imagine
 students immediately thinking that my factorial program is a recipe
 and wondering why it doesn't involve monads.

Well that's easy, don't use the recipe analogy to explain code, use it
for monadic values exclusively, and you avoid the confusion entirely!

I don't think it's that complicated. Monads have a monadic type. They
represent an abstract form of an action, which can be viewed as an
analogy to real-world cooking recipes. As long as you don't
deliberately confuse things by using the same analogy for two
different things I don't see where confusion would set in.


-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bathroom reading

2007-08-14 Thread Brent Yorgey
On 8/14/07, Dougal Stanton [EMAIL PROTECTED] wrote:

 On 14/08/07, Brent Yorgey [EMAIL PROTECTED] wrote:
  Clearly, we need to actually put together such a book!  I'm imagining
  something where you have two mostly blank facing pages, with the code by
  itself in the middle of the right page; then the next 2-4 pages devoted
 to a
  short discussion of the code, how it works, related issues and
 techniques,
  and a list of references.  All featuring beautiful typography and
 fantastic
  writing, of course. =)

 Oh indeed! This wasn't *completely* idle chatter on my part. I used to
 work in a print shop and we did a lot of work for art and architecture
 students who would do this kind of thing all the time. Fantastic
 little notebook-style gifts of images and blank pages and elegant
 typography. It's just a shame so many of them were terrible at
 spelling! :-P

 It shouldn't be too difficult to use LaTeX to this end. Once a
 document class has been hammered out you can offer a range of
 different booklets! The Evolution of a Haskell Programmer series
 would be a good place to start. Bring it to your next job interview to
 whip out when someone points to that bit on your CV and says, what's
 that?.

 Any skilled TeXers in the house?

 D.


Well, it wasn't completely idle chatter on my part, either! =)   After
spending the past year writing (and typesetting) a mathematics book in my
spare time, I would consider myself an intermediate to advanced user of
LaTeX, although I know much less about TeX itself than I would like
(although I do intend to learn).  Unfortunately, what with applying to grad
school and other things, it probably wouldn't be wise for me to spearhead
such a project at the moment, although I'd be excited about contributing.
But I very well might pick it up at a later date if no one decides to run
with it right now.

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Dan Piponi
On 8/14/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 Well that's easy, don't use the recipe analogy to explain code, use it
 for monadic values exclusively, and you avoid the confusion entirely!

 I don't think it's that complicated.

It certainly is complicated. I think I have a good grasp of monads to
the point where I can tease novel monads (and comonads) out from
algorithms that people previously didn't see as monadic. And yet I
still don't understand what you are saying (except with respect to one
specific monad, IO, where I can interpret 'action' as meaning an I/O
operation).

 Monads have a monadic type. They
 represent an abstract form of an action, which can be viewed as an
 analogy to real-world cooking recipes.

All functions can be viewed as recipes. (+) is a recipe. Give me some
ingredients (two numbers) and I'll use (+) to give you back their sum.

 As long as you don't
 deliberately confuse things by using the same analogy for two
 different things I don't see where confusion would set in.

If I was one of your students and you said that monads are recipes I
would immediately ask you where the monads are in my factorial program
regardless of whether you had introduced one or two different
analogies for recipes. There are two sides to every analogy. If you
have an analogy between A and B then you can use knowledge about A to
understand B. But conversely, if you can't set up the same analogy
between A and B then that tells you something useful about B also. As
far as I can see, your description of a monad fits every computer
program I have ever written, and as a result I don't see what it is
that makes monads special. And monads are special.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Explaining monads

2007-08-14 Thread Aaron Denney
On 2007-08-14, Dan Piponi [EMAIL PROTECTED] wrote:
 On 8/14/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 I like the very light weight analogy (which works for most practical
 uses of monads) that a monadic action is a recipe

 Many introductory programming books present the idea of a program as a
 recipe. Here's a recipe for computing factorials:

 fact 0 = 1
 fact n = n*fact (n-1)

 Where do monads come in?

Playing the devil's advocate here:

Recipe is a reasonable description for imperative code ... because it's
all in the IO monad.

Not such a good mapping for functional code.

(I don't think recipe is a good analogy for, say, the List monad, reader
monads, etc.)

-- 
Aaron Denney
--

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Jeff Polakow
Hello,

 On 14/08/07, Jeff Polakow [EMAIL PROTECTED] wrote:
 Of course, the type [Int] denotes a value which is a list of Ints; 
 additionally [Int] can be viewed as a value representing the 
 nondeterministic computation of a single Int. Generally, the type 
 Monad m = m Int can be viewed as a value representing the 
 computation of an Int. 
 
 
 But thats not really right. What exactly m Int does /depends/ on m. 
 It might represent 0 or more computations
 of Int, or computations of Int carrying some extra stuff around, or 
 complex control logic about what the computation does 
 when.
 
Perhaps the confusion is in the word computation. I'm using the word in an 
abstract sense. I do not mean the actual execution of Haskell code to 
produce a value. Thus, under this intuition:

The type Int represents a value which denotes an Int. The type m Int 
denotes a value which is a single computation (for an unspecified notion 
of computation) of an Int. A specific computation of an Int might result 
in several, or zero, actual Ints (the list monad); a String or an Int (the 
Either String monad); the constant () (the trivial monad); ...

The type Monad m = m Int cannot represent multiple computations of an 
Int. The type Monad m = [m Int] represents multiple computations of an 
Int (of course, any container type can be used in place of list).

-Jeff


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Bathroom reading

2007-08-14 Thread Aaron Denney
On 2007-08-14, Spencer Janssen [EMAIL PROTECTED] wrote:
 On Tuesday 14 August 2007 10:17:53 Dougal Stanton wrote:
 I'm looking for cool but mind-bending examples of functional brilliance.

 Let us say, hypothetically, you had a bathroom without any reading
 material. And having read all the Dilbert and Garfield you could
 seriously stomach, decide you should educate yourself while on the
 job. :-)

 So you decide to print up some one-liner style programs into a
 little booklet. Something between credit-card and postcard sized, with
 a neat but mind-bending program on it. Don Stewart occasionally swoops
 in with some fixpoint malarkey to defuse heated discussions. I mean
 that kind of thing, but with a slightly wider scope than just fibs...

 Suggestions, please!

 D.

 Here's a small puzzle: without using a Haskell interpreter, explain what 
 the 'foo' function does.

 foo = filterM (const [True, False])

powerset.  Very nice use of the list monad.

-- 
Aaron Denney
--

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


[Haskell-cafe] Error building takusen with Cabal-1.1.6.2

2007-08-14 Thread John Dell'Aquila
Setup.hs wants a module that Cabal hides. Am I doing something wrong (newbie :-)
or should I try to fall back to Cabal-1.1.6.1?

$ ghc --make -o setup Setup.hs

Setup.hs:13:7:
Could not find module `Distribution.Compat.FilePath':
  it is hidden (in package Cabal-1.1.6.2)

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Sebastian Sylvan
On 14/08/07, Dan Piponi [EMAIL PROTECTED] wrote:
 On 8/14/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:
  Well that's easy, don't use the recipe analogy to explain code, use it
  for monadic values exclusively, and you avoid the confusion entirely!
 
  I don't think it's that complicated.

 It certainly is complicated. I think I have a good grasp of monads to
 the point where I can tease novel monads (and comonads) out from
 algorithms that people previously didn't see as monadic. And yet I
 still don't understand what you are saying (except with respect to one
 specific monad, IO, where I can interpret 'action' as meaning an I/O
 operation).

  Monads have a monadic type. They
  represent an abstract form of an action, which can be viewed as an
  analogy to real-world cooking recipes.

 All functions can be viewed as recipes. (+) is a recipe. Give me some
 ingredients (two numbers) and I'll use (+) to give you back their sum.

No, (+) is a function, not a recipe. Again, you're introducing
confusion because you use the same analogy for two *different* things.
Use it for one of the things and you don't have that problem.
I want to use recipe to mean an abstraction for an action. It
could litterally be a text string containing the C code required to do
a particular IO action, for example. (+) isn't an abstraction in the
same sense, it *is* the action itself. (+) is the actual value of
the function that will add two numbers together. A monadic value is an
abstract recipe that you can't actually use directly (you can only
combine them, and if you're lucky you can perform them once you're
done combining them, e.g. ST, but not IO).



  As long as you don't
  deliberately confuse things by using the same analogy for two
  different things I don't see where confusion would set in.

 If I was one of your students and you said that monads are recipes I
 would immediately ask you where the monads are in my factorial program
 regardless of whether you had introduced one or two different
 analogies for recipes.

Why would you? I really don't see where you would get that idea? If I
tell you that a function returns a fruit, would you ask where the
fruit in your factorial program is? Probably not. Why would you go off
and take an analogy for monads and apply it to something completely
different and still think the analogy holds?
A function is *not* a recipe in this analogy, it's just a function
(which you hopefully should've covered by the time you get to monads.
Monadic values, and *only* monadic values (not functions!) are to be
viewed as analogous to real world cooking recipes in this analogy.
Functions shouldn't. If you start mixing things together it will get
confused, so just don't!

I don't think this is very difficult to understand, so if you still
don't get it, I think you're just going to have to read it again
because I can't explain it any better, and in my experience, newbies
tend to understand this analogy within seconds (maybe that's the
problem, you're not a newbie)...

-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Arie Peterson

Dan Piponi wrote:

| On 8/14/07, Lennart Augustsson [EMAIL PROTECTED] wrote:
|  You don't normally call x::Int a computation of an Int because there's
|  nothing that distinguishes the value of the x from what it was before
|  you computed it.
|
| Can you spell out exactly what you mean by this?

Let's take a formal viewpoint: when writing a haskell program, you specify
what properties your values must satisfy. So 'x = 6' means that I want 'x'
to equal the value 6. To make solution of these equations tractable, we
have agreed that we treat them as (recursive) definitions of the LHS.

Now, the compiler may actually treat 'x = 6' as a specification of a
computation. From this formal point of view, however, that is an
implementation detail, and we don't need to speak about 'computations'.

Does this help at all?


| When someone uses the phrase something else it implies that we are
| talking about two things, a something and a disjoint something
| else. For example, if x = [1,2,3] what is the something and what is
| the something else? What was the x before [I] computed it and how
| does it differ from its value?
|
|| This is just the terminology people use, not an absolute truth, so
|| you're free to think it's wrong. :)
|
| For something like this I prefer to think in terms of useful and
| not useful. If you find the term computation useful, I might find
| it useful too. So I'm jealous as I can't figure out how to use it. :-)
| I'm not looking for a formal definition or anything like that. But I
| would like a reliable way to distinguish between things that are
| computations and things that are not.

Well, it depends on the context really, and on how hard you squint. Sorry
to disappoint you :-) (friendly apologetic smile, not an evil laugh).

Instead of [1,2,3], let me underhandly take the list [False,True]. Nothing
'computational' about it, right? Just a basic list, with some boolean
entries.

But behold! In the context of the 'power set' function from the other thread:

 power = filterM (const [False,True])

, this innocuous list suddenly reveals its monadic/computational
character. In this context, you may interpret [False,True] as a
'multi-valued computation of a boolean', which yields both False and True.
'const [False,True]' is a monadic predicate, which yields both False and
True on any element. filterM then applies this predicate to all elements
of a list, sequencing the computational/multi-valued aspects.


Greetings,

Arie

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Malte Milatz
Dan Piponi, Tue, 14 Aug 2007 11:52:16 -0700:
 All functions can be viewed as recipes. (+) is a recipe. Give me some
 ingredients (two numbers) and I'll use (+) to give you back their sum.

(+) is not a recipe, it is a chef. On the other hand, 
(return 5 :: State Integer) is a recipe. You need a
chef, namely runState, to get your meal.

Oh my, imagery can be so crazy.

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Sebastian Sylvan
On 14/08/07, Malte Milatz [EMAIL PROTECTED] wrote:
 Dan Piponi, Tue, 14 Aug 2007 11:52:16 -0700:
  All functions can be viewed as recipes. (+) is a recipe. Give me some
  ingredients (two numbers) and I'll use (+) to give you back their sum.

 (+) is not a recipe, it is a chef. On the other hand,
 (return 5 :: State Integer) is a recipe. You need a
 chef, namely runState, to get your meal.

 Oh my, imagery can be so crazy.

Thank you! That does make sense.

-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Seth Gordon

Sebastian Sylvan wrote:

On 14/08/07, Dan Piponi [EMAIL PROTECTED] wrote:

If I was one of your students and you said that monads are recipes I
would immediately ask you where the monads are in my factorial program
regardless of whether you had introduced one or two different
analogies for recipes.


Why would you? I really don't see where you would get that idea? If I
tell you that a function returns a fruit, would you ask where the
fruit in your factorial program is? Probably not. Why would you go off
and take an analogy for monads and apply it to something completely
different and still think the analogy holds?
A function is *not* a recipe in this analogy, it's just a function
(which you hopefully should've covered by the time you get to monads.
Monadic values, and *only* monadic values (not functions!) are to be
viewed as analogous to real world cooking recipes in this analogy.
Functions shouldn't. If you start mixing things together it will get
confused, so just don't!


As a mostly-newbie who is working on his own monad tutorial 
(bwah-hah-hah), I share Dan's confusion about your analogy.


Teacher: Monads are like recipes.

Student: Aren't functions like recipes, too?

Teacher: Well, yes, but we're talking about monads now, not functions.

That response doesn't help the student, because the student already 
knows about functions, and would probably understand monads a lot better 
if he or she knew how monads are *different from* functions. 
(Especially since, umm, isn't the ((-) a) data type a monad?)

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


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Sebastian Sylvan
On 14/08/07, Seth Gordon [EMAIL PROTECTED] wrote:
 Sebastian Sylvan wrote:
  On 14/08/07, Dan Piponi [EMAIL PROTECTED] wrote:
  If I was one of your students and you said that monads are recipes I
  would immediately ask you where the monads are in my factorial program
  regardless of whether you had introduced one or two different
  analogies for recipes.
 
  Why would you? I really don't see where you would get that idea? If I
  tell you that a function returns a fruit, would you ask where the
  fruit in your factorial program is? Probably not. Why would you go off
  and take an analogy for monads and apply it to something completely
  different and still think the analogy holds?
  A function is *not* a recipe in this analogy, it's just a function
  (which you hopefully should've covered by the time you get to monads.
  Monadic values, and *only* monadic values (not functions!) are to be
  viewed as analogous to real world cooking recipes in this analogy.
  Functions shouldn't. If you start mixing things together it will get
  confused, so just don't!

 As a mostly-newbie who is working on his own monad tutorial
 (bwah-hah-hah), I share Dan's confusion about your analogy.

 Teacher: Monads are like recipes.

 Student: Aren't functions like recipes, too?

 Teacher: Well, yes, but we're talking about monads now, not functions.


Teacher: No, functions are like chefs. They do things to their input.
Monads are like recipes, they don't *do* anything at all, they just
represent an action, they need chefs to interpret them.

-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] defining last using foldr

2007-08-14 Thread Alexteslin

Hi,

I am trying to do the exercise which asks to define built-in functions
'last' and 'init' using 'foldr' function, such as last Greggery Peccary =
'y'

the type for my function is: 

myLast :: [Char] - Char 

I am not generalizing type so that make it less complicated.  But what ever
i am trying would not work.  The only function type foldr takes as an
argument is either (a-a-a) or (a-b-b) and none of the functions i found
that would match this type from Char to Char.  So in other words should be
(Char-Char-Char).  I can define the function without foldr but that misses
the point of the exercise.  

Any hint will be appreciated,
Thank you 
-- 
View this message in context: 
http://www.nabble.com/defining-last-using-foldr-tf4269357.html#a12151145
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Re: defining last using foldr

2007-08-14 Thread Aaron Denney
On 2007-08-14, Alexteslin [EMAIL PROTECTED] wrote:

 Hi,

 I am trying to do the exercise which asks to define built-in functions
 'last' and 'init' using 'foldr' function, such as last Greggery Peccary =
 'y'

 the type for my function is: 

 myLast :: [Char] - Char 

 I am not generalizing type so that make it less complicated.  But what ever
 i am trying would not work.  The only function type foldr takes as an
 argument is either (a-a-a) or (a-b-b) and none of the functions i found
 that would match this type from Char to Char.  So in other words should be
 (Char-Char-Char).  I can define the function without foldr but that misses
 the point of the exercise.  

Folds replace the cons operator (:) with the function you pass it.
If you want the tail of the list, you want what is on the right hand
side of every cons (unless that's []).

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Error building takusen with Cabal-1.1.6.2

2007-08-14 Thread Benjamin Franksen
John Dell'Aquila wrote:
 Setup.hs wants a module that Cabal hides. Am I doing something wrong
(newbie :-)
 or should I try to fall back to Cabal-1.1.6.1?
 
 $ ghc --make -o setup Setup.hs
 
 Setup.hs:13:7:
 Could not find module `Distribution.Compat.FilePath':
   it is hidden (in package Cabal-1.1.6.2)

This is what I did to make takusen build with ghc-6.6.1:

[EMAIL PROTECTED]: .../haskell/takusen_0  darcs whatsnew 
{
hunk ./Setup.hs 13
-import Distribution.Compat.FilePath (splitFileName, joinPaths)^M$
+import System.FilePath (splitFileName, combine)^M$
hunk ./Setup.hs 124
-  libDirs - canonicalizePath (joinPaths path libDir)^M$
-  includeDirs - canonicalizePath (joinPaths path includeDir)^M$
+  libDirs - canonicalizePath (combine path libDir)^M$
+  includeDirs - canonicalizePath (combine path includeDir)^M$
}

HTH
Ben

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


Re: [Haskell-cafe] defining last using foldr

2007-08-14 Thread Rodrigo Queiro
I've found a way to do it, but it's not pretty.

Hint: The function in the foldr first get the last value, and will
need to keep it the whole way through. How can it tell if it is being
given the last item or an earlier item?

I'm generally not too good at the Socratic method, so feel free to
email for some more help or my answer.

On 14/08/07, Alexteslin [EMAIL PROTECTED] wrote:

 Hi,

 I am trying to do the exercise which asks to define built-in functions
 'last' and 'init' using 'foldr' function, such as last Greggery Peccary =
 'y'

 the type for my function is:

 myLast :: [Char] - Char

 I am not generalizing type so that make it less complicated.  But what ever
 i am trying would not work.  The only function type foldr takes as an
 argument is either (a-a-a) or (a-b-b) and none of the functions i found
 that would match this type from Char to Char.  So in other words should be
 (Char-Char-Char).  I can define the function without foldr but that misses
 the point of the exercise.

 Any hint will be appreciated,
 Thank you
 --
 View this message in context: 
 http://www.nabble.com/defining-last-using-foldr-tf4269357.html#a12151145
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 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] defining last using foldr

2007-08-14 Thread Alexteslin

Well, i have tried cons (:) operator but when it passed to foldr doesn't work
because cons operator operates first character and then the list but the
foldr argument takes a function (a-a-a).  Maybe i am missing the point
here?


Aaron Denney wrote:
 
 On 2007-08-14, Alexteslin [EMAIL PROTECTED] wrote:

 Hi,

 I am trying to do the exercise which asks to define built-in functions
 'last' and 'init' using 'foldr' function, such as last Greggery Peccary
 =
 'y'

 the type for my function is: 

 myLast :: [Char] - Char 

 I am not generalizing type so that make it less complicated.  But what
 ever
 i am trying would not work.  The only function type foldr takes as an
 argument is either (a-a-a) or (a-b-b) and none of the functions i
 found
 that would match this type from Char to Char.  So in other words should
 be
 (Char-Char-Char).  I can define the function without foldr but that
 misses
 the point of the exercise.  
 
 Folds replace the cons operator (:) with the function you pass it.
 If you want the tail of the list, you want what is on the right hand
 side of every cons (unless that's []).
 
 -- 
 Aaron Denney
 --
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/defining-last-using-foldr-tf4269357.html#a12151694
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] defining last using foldr

2007-08-14 Thread Chaddaï Fouché
2007/8/14, Alexteslin [EMAIL PROTECTED]:
 Well, i have tried cons (:) operator but when it passed to foldr doesn't work
 because cons operator operates first character and then the list but the
 foldr argument takes a function (a-a-a).  Maybe i am missing the point
 here?


What Aaron was saying was that in this list :
1 : 2 : 3 : 4 : []
A fold replaced the cons (:) by another function (and [] by another constant).

Your problem isn't so easy to do with a foldr, a foldl would be easier
and a foldr1 or foldl1 even better. Are you sure you can't use one of
those other folds ?

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


Re: [Haskell-cafe] defining last using foldr

2007-08-14 Thread Rodrigo Queiro
You can consider foldr to be continual modification of a state. The
initial state is given as an argument, and then the (a - b - b)
function is passed the next element of the list and the current state,
and it returns the new state. foldr will then return the final state,
from which the result can be extracted. Does that help?

On 14/08/07, Alexteslin [EMAIL PROTECTED] wrote:

 Well, i have tried cons (:) operator but when it passed to foldr doesn't work
 because cons operator operates first character and then the list but the
 foldr argument takes a function (a-a-a).  Maybe i am missing the point
 here?


 Aaron Denney wrote:
 
  On 2007-08-14, Alexteslin [EMAIL PROTECTED] wrote:
 
  Hi,
 
  I am trying to do the exercise which asks to define built-in functions
  'last' and 'init' using 'foldr' function, such as last Greggery Peccary
  =
  'y'
 
  the type for my function is:
 
  myLast :: [Char] - Char
 
  I am not generalizing type so that make it less complicated.  But what
  ever
  i am trying would not work.  The only function type foldr takes as an
  argument is either (a-a-a) or (a-b-b) and none of the functions i
  found
  that would match this type from Char to Char.  So in other words should
  be
  (Char-Char-Char).  I can define the function without foldr but that
  misses
  the point of the exercise.
 
  Folds replace the cons operator (:) with the function you pass it.
  If you want the tail of the list, you want what is on the right hand
  side of every cons (unless that's []).
 
  --
  Aaron Denney
  --
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

 --
 View this message in context: 
 http://www.nabble.com/defining-last-using-foldr-tf4269357.html#a12151694
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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

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


[Haskell-cafe] Re: defining last using foldr

2007-08-14 Thread Aaron Denney
(Quoting reformatted.  Try to have your responses below what you are
responding to.  It makes it easier to read as a conversation.)

On 2007-08-14, Alexteslin [EMAIL PROTECTED] wrote:
 Aaron Denney wrote:
 Folds replace the cons operator (:) with the function you pass it.
 If you want the tail of the list, you want what is on the right hand
 side of every cons (unless that's []).


 Well, i have tried cons (:) operator but when it passed to foldr doesn't work
 because cons operator operates first character and then the list but the
 foldr argument takes a function (a-a-a).  Maybe i am missing the point
 here?

I didn't say to use (:), I said foldr works by replacing (:) with some
other function.

foldr also takes a function of type (a - b - b).

foldr f e 
replaces
(first : (middle : (last : [])))
with
(first `f` (middle `f` (last `f` e)))

You want last to be kept, so 
f x e = x

this causes the overall pattern to reduce to
(first `f` (middle `f` last))

This time you need
f y last = last

This means you need to discriminate between e and last.

If you make e the same type as last, you could accidentally compare
them equal.  So instead of using the same type, we want one with one
more value.  There is a standard one: Maybe a, with constructors
Just a and Nothing.  And you also need to promote last to this
type with the constructor Just, because the result gets fed in on the
right.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: defining last using foldr

2007-08-14 Thread Aaron Denney
On 2007-08-14, Chaddaï Fouché [EMAIL PROTECTED] wrote:
 2007/8/14, Alexteslin [EMAIL PROTECTED]:
 Well, i have tried cons (:) operator but when it passed to foldr doesn't work
 because cons operator operates first character and then the list but the
 foldr argument takes a function (a-a-a).  Maybe i am missing the point
 here?


 What Aaron was saying was that in this list :
 1 : 2 : 3 : 4 : []
 A fold replaced the cons (:) by another function (and [] by another constant).

 Your problem isn't so easy to do with a foldr, a foldl would be easier
 and a foldr1 or foldl1 even better. Are you sure you can't use one of
 those other folds ?

The problem with foldl is that you can't easily make it polymorphic
because of how the null case is handled.  foldl1 and foldr1 are trivial,
true.

-- 
Aaron Denney
--

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


[Haskell-cafe] Why monad tutorials don't work

2007-08-14 Thread Dan Weston
Conor McBride and Ross Paterson said it best in the introduction to 
their paper Applicative programming with effects [1]:


  This is the story of a pattern that popped up time
  and again in our daily work,..., until the temptation
  to abstract it became irresistible. Let us illustrate
  with some examples.

Translation: Unless you've broken your back hauling water by hand, 
you'll never truly get the utility (even joy) of installing plumbing. 
To help you speed through (but not skip over) this necessary hauling 
drudgery, we will show the movie of us doing it in fast forward, and ask 
you to make the leap of faith that the sweat dripping off our brows is 
real, not sprayed on to make us look impressive.


The fatal flaw of all tutorials is that the easier they make things 
seem, the less visceral understanding of the importance and benefit the 
reader will have.


So here's my 30-second monad meta-metaphor:

Monads are like wrapping paper, so the surprise isn't spoiled before 
Christmas. Every present can be wrapped, the paper doesn't damage what 
it covers, and there's no need to wrap it twice, it's no more opaque 
than wrapping it once.


But you know better! You don't want to bother wrapping your presents. 
Your children promise not to peek until Christmas day anyway. After 
first, you have plenty of time to watch them. But as the holidays 
approach, you get busier, and pretty soon you have to choreograph your 
entire day just to divert their attention. It only takes one slip-up to 
ruin the surprise, so you spend a great deal of effort making this happen.


Your mother (who has been down this route before with you) knows from 
experience that it is just easier to use wrapping paper, but you don't 
believe her. She's so old-fashioned and dogmatic! In a misguided attempt 
to be helpful, she whips out the dreaded Monad Tutorial Book of All 
Human Wisdom and explains the concept of Present Wrapping. The authors 
have PhDs in the science of concealment and compare the common 
properties of paper, boxes, sleight-of-hand, and one-way mirrors, but 
your eyes glaze over because you don't care about mirrors, you just have 
a present. Helpful friends share their war stories, but as you're not a 
bad parent like they are, you don't fall for their arrogant attempts to 
educate you and you point out how in each case their experience doesn't 
fit your needs.


The most amazing thing in this metaphor is the strangely irrepressible 
joy that those who've mastered the art of present wrapping have to share 
their discovery with others. I guess some things are just too good to 
keep to yourself! Sadly, these tend to be the things you can't even give 
away without getting flak for it... :(


Dan Weston

[1] http://www.soi.city.ac.uk/~ross/papers/Applicative.html

Lanny Ripple wrote:
Having just gone through all the tutorials and things (again but this 
time I think it stuck) the Haskell community is on the wrong track as 
far as teaching Monads to new programmers.


If I were teaching addition and multiplication to children I wouldn't 
start with, We'll begin by defining an algebraic structure named a 
Group.  From there we'll expand our concept to a Ring and Field.  
A group is a set and a binary operator usually named + (or sometimes 
*) such that


No no no.  You start with, You all know how to count from one to 10.  
If we have 1 item and we 'add' another 1 item we have 2 items.  We write 
this 1+1=2.


The tutorials seriously need to step back and start with something like, 
To enforce order of evaluation we evaluate closures* returning a 
defined type.  The first closure will feed its result to the second 
which will in turn feed it's result to the third.  Since the third 
closure can't be evaluated without having the results from the second 
and first (and thus they had to be evaluated earlier in time) we get a 
defined evaluation sequence.  Here are some examples...


(* Even using the word 'closure' is scary for those not familiar with 
them.)


Then, like Monads For Functional Programming (the paper that finally 
clicked Monads for me) you point out that evaluating all these closures 
returning a defined type in various ways form a structure (which you can 
then explain) and we can use that structure and change out the 
underlying effect(s) as needed.


Now of course if your new programmer has the the necessary background 
you can throw them in the deep end.  But don't do that to someone coming 
at the language from something like Java learned out of a business 
degree course.  (My background is a CS degree with math minor and it 
still took two go-s at Haskell before I got as far as understanding what 
folks were talking about with Monads.  Wish I had found Wadler's MFFP 
the first time around.)  Where are the shallow end tutorials?  (Don't 
get me wrong.  The tutorials are good but there is also a place for the 
learn-by-rote with lots of examples ones too.)


  $0.02,
  -ljr

PS - Not so much directed 

Re: [Haskell-cafe] Why monad tutorials don't work

2007-08-14 Thread Dougal Stanton
On 14/08/07, Dan Weston [EMAIL PROTECTED] wrote:

[snips another metaphor for monadic programming]

No offence to Dan, whose post I enjoyed. The concept of wrapping is as
close a metaphor as we seem to get without disagreements. But this has
brought me to a realisation, after Paul Erdos:

The Haskell community is a machine for converting coffee to monad tutorials.

In the spirit of the venture, I will now suggest that someone points
out that they don't like coffee, and that I haven't allowed for arrow
tutorials ;-)

Cheers,

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


Re: [Haskell-cafe] Re: defining last using foldr

2007-08-14 Thread Chaddaï Fouché
2007/8/14, Aaron Denney [EMAIL PROTECTED]:
 The problem with foldl is that you can't easily make it polymorphic
 because of how the null case is handled.  foldl1 and foldr1 are trivial,
 true.


The original last fail on empty list, it's far easier to obtain the
same semantic with foldl than with foldr, in fact it isn't hard at all
to make it polymorphic without hassle (contrary to the foldr case)
_if_ you remember that there _is_ a value in Haskell wich belongs to
every type.

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


Re: [Haskell-cafe] Why monad tutorials don't work

2007-08-14 Thread Michael Vanier

snark
As you know, an arrow tutorial is like a wrapper around a monad tutorial, sort of like a container 
around it that can do extra actions with sufficient lifting.  The appropriate higher-order function 
to convert monad tutorials to arrow tutorials will be left as an exercise to the reader.

/snark

I'm becoming more and more convinced that metaphors for monads do more harm than good.  From now on 
I'm going to describe monads as purely abstract entities that obey certain laws, and that _in 
certain instances_ can be viewed to be like containers, or actions, or donuts, or whatever.  In 
other words, a monad is an abstract thing that can generate things that we can metaphorize, but it's 
pointless (point-free?) to try to capture the entire concept in a single metaphor.  I'm reminded of 
a physics teacher who was having a similar problem explaining the concept of tensors, until he said 
that a tensor is something that transforms like a tensor does!.  So a monad is something that 
behaves like a monad does.


Mike (who obviously hasn't had nearly enough coffee today)

Dougal Stanton wrote:

On 14/08/07, Dan Weston [EMAIL PROTECTED] wrote:

[snips another metaphor for monadic programming]

No offence to Dan, whose post I enjoyed. The concept of wrapping is as
close a metaphor as we seem to get without disagreements. But this has
brought me to a realisation, after Paul Erdos:

The Haskell community is a machine for converting coffee to monad tutorials.

In the spirit of the venture, I will now suggest that someone points
out that they don't like coffee, and that I haven't allowed for arrow
tutorials ;-)

Cheers,

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

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


[Haskell-cafe] Re: defining last using foldr

2007-08-14 Thread Aaron Denney
On 2007-08-14, Chaddaï Fouché [EMAIL PROTECTED] wrote:
 2007/8/14, Aaron Denney [EMAIL PROTECTED]:
 The problem with foldl is that you can't easily make it polymorphic
 because of how the null case is handled.  foldl1 and foldr1 are trivial,
 true.


 The original last fail on empty list, it's far easier to obtain the
 same semantic with foldl than with foldr, in fact it isn't hard at all
 to make it polymorphic without hassle (contrary to the foldr case)
 _if_ you remember that there _is_ a value in Haskell wich belongs to
 every type.

Hah.  True.  That does simplify things considerably.  Still, I'd call
that an infelicity in last (and head, for that matter), and would rather
have such errors handled at the call site than making the entire program
fall over.

-- 
Aaron Denney
--

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


Re: [Haskell-cafe] Why monad tutorials don't work

2007-08-14 Thread Dan Piponi
On 8/14/07, Dan Weston [EMAIL PROTECTED] wrote:
 Conor McBride and Ross Paterson said it best in the introduction to
 their paper Applicative programming with effects [1]:

As von Neumann said: Young man, in mathematics you don't understand
things, you just get used to them.

Getting used to something is, practically by definition, something
that you can't do just by reading the ultimate tutorial. You just have
to write the code, see the pattern happen again and again, and
abstract it. There's no short cut. (Well...sometimes...)

On 8/14/07, Michael Vanier [EMAIL PROTECTED] wrote:
  I'm reminded of
 a physics teacher who was having a similar problem explaining the concept of 
 tensors, until he said
 that a tensor is something that transforms like a tensor does!.

Grrr...must...hold...my...tongue...
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Derek Elkins
On Tue, 2007-08-14 at 12:40 -0500, Lanny Ripple wrote:
 Derek Elkins wrote:
  What people need to do is stop reading two page blog posts by someone
  who's just got monads and read the well-written peer-reviewed papers
 
 I have taught many people to program in group settings and 
 individually in my career.  I have referred them to many 
 tutorials.  I have used many examples from tutorials I thought 
 were useful.  I can't recall a single time I've ever turned to a 
 beginner and said, And you really should brush up on the 
 peer-reviewed papers to learn this part.

How about a book?  You've never recommended a book?  But even so, where
did I say tutorial?  The -are- good monad tutorials, they are just
horribly out-weighed by bad ones.  Further, having a tutorial as
supplement to person-to-person education is totally different from
trying to learn purely from tutorials.  Also, what is wrong with papers
or recommending them?  Finally, how often have you been part of a
community where the primary mode of documentation is a research paper...

 
  by the people who clearly know what they are talking about.  Luckily,
  for monads applied to Haskell we have Wadler, a witty, enjoyable and
  clear writer/speaker.  All of Wadler's monad introductions are
  readable by anyone with a basic grasp of Haskell.  You certainly don't
  need to be even remotely an academic to understand them.  I'm willing to
  bet that many people who say they don't understand monads and have read
  every tutorial about them haven't read -any- of Wadler's papers.


 I'm confused.  Are you praising Wadler or bashing the tutorials 
 (or both)?  *I* was carping about the tutorials (and even 
 mentioned that Wadler was my breakthrough) so I suspect we are in 
 violent agreement.

I'm praising Wadler and bashing the good majority of monad tutorials,
but not all of them.  Mostly I'm pointing out an unreasonable aversion
to reading papers, as if a paper couldn't possibly be understandable.

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


Re: [Haskell-cafe] Why monad tutorials don't work

2007-08-14 Thread Erik Jones
On 8/14/07, Michael Vanier [EMAIL PROTECTED] wrote:

I'm becoming more and more convinced that metaphors for monads do more harm
 than good.  From now on
 I'm going to describe monads as purely abstract entities that obey certain
 laws, and that _in
 certain instances_ can be viewed to be like containers, or actions, or
 donuts, or whatever.  In
 other words, a monad is an abstract thing that can generate things that we
 can metaphorize, but it's
 pointless (point-free?) to try to capture the entire concept in a single
 metaphor.  I'm reminded of
 a physics teacher who was having a similar problem explaining the concept
 of tensors, until he said
 that a tensor is something that transforms like a tensor does!.  So a
 monad is something that
 behaves like a monad does.



Nice.  As a Haskell beginner (with previous imperative programming
experience) I subscribed to this list today to say exactly that.  I spent
weeks reading different tutorials that attempted to enlighten by means of
various abstractions before I finally found one that simply showed the
mechanics of the required operators and rules (sounds less formal than laws)
that they need to hold to.  Even then I hadn't quite got it until I met
SPJ at OSCON and heard myself saying, All monads are are labels in front of
values with specific operations defined on them.  His reply was, Yes!
Very abstract isn't it?  Then I'd got it, or realized that I had but
hadn't realized it (if that makes any sense...), as that sequential exchange
of ideas (hah!) brought me to the realization that the abstractions that
monads are held to represent are solely in the usage semantics of aforesaid
operations and, while technically the actual labels used don't matter, we
pick labels whose meaning match those semantics.

So, yes, don't start by giving any extra meaning to the basic monad
operations than their mechanics.  Then show how they can be use to
implement abstractions like state, uncertainty, etc...

Oh yeah, start with terms that programmers already know, e.g. encapsulation
v. wrappers.  Then switch.  Don't start with terminology that's different
and explain the mappings, start with the familiar than follow the mappings
to the different.

-- 
Erik Jones
[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-14 Thread Michael Vanier
For what it's worth, the nature of Haskell is such that you do (at least currently) have to spend a 
lot of time reading research papers to understand what's going on.  Maybe that will change sometime, 
but probably not soon.  This ties in to the open-endedness of Haskell; I sometimes think that really 
understanding all of Haskell is like really understanding all of mathematics.  This is frustrating, 
but it's also what makes the language so rewarding.  I guess what I'm saying is: get used to it, 
it's not so bad.


Mike

Derek Elkins wrote:

On Tue, 2007-08-14 at 12:40 -0500, Lanny Ripple wrote:

Derek Elkins wrote:

What people need to do is stop reading two page blog posts by someone
who's just got monads and read the well-written peer-reviewed papers
I have taught many people to program in group settings and 
individually in my career.  I have referred them to many 
tutorials.  I have used many examples from tutorials I thought 
were useful.  I can't recall a single time I've ever turned to a 
beginner and said, And you really should brush up on the 
peer-reviewed papers to learn this part.


How about a book?  You've never recommended a book?  But even so, where
did I say tutorial?  The -are- good monad tutorials, they are just
horribly out-weighed by bad ones.  Further, having a tutorial as
supplement to person-to-person education is totally different from
trying to learn purely from tutorials.  Also, what is wrong with papers
or recommending them?  Finally, how often have you been part of a
community where the primary mode of documentation is a research paper...


by the people who clearly know what they are talking about.  Luckily,
for monads applied to Haskell we have Wadler, a witty, enjoyable and
clear writer/speaker.  All of Wadler's monad introductions are
readable by anyone with a basic grasp of Haskell.  You certainly don't
need to be even remotely an academic to understand them.  I'm willing to
bet that many people who say they don't understand monads and have read
every tutorial about them haven't read -any- of Wadler's papers.



I'm confused.  Are you praising Wadler or bashing the tutorials 
(or both)?  *I* was carping about the tutorials (and even 
mentioned that Wadler was my breakthrough) so I suspect we are in 
violent agreement.


I'm praising Wadler and bashing the good majority of monad tutorials,
but not all of them.  Mostly I'm pointing out an unreasonable aversion
to reading papers, as if a paper couldn't possibly be understandable.

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

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


[Haskell-cafe] Re:Explaining monads

2007-08-14 Thread Gregory Propf
Sorry to spam you Jeff, again I sent my email to the poster rather than the 
list.  I'm using Yahoo beta webmail and don't see a way to set it to reply to 
the list rather than the originator.  Anyway, this was my post:

Hence the need to perform a run operation like runIdentity, evalState or 
runParser (for Parsec) to get something useful to happen.  Except for lists we 
don't seem to do this.  I suppose lists are so simple that the operators :, ++ 
and the [] constructor do all we ever need with them.  Finally there is no 
runIO because main is essentially that function in every real program? - Greg

- Original Message 
From: Jeff Polakow [EMAIL PROTECTED]
To: [EMAIL PROTECTED]
Cc: [EMAIL PROTECTED]; Haskell-Cafe haskell-cafe@haskell.org
Sent: Tuesday, August 14, 2007 8:45:06
 AM
Subject: Re: [Haskell-cafe] Explaining monads



One general intuition about monads is that they represent
computations rather than simple (already computed) values:



   






  Boardwalk for $500? In 2007? Ha! 
Play Monopoly Here and Now (it's updated for today's economy) at Yahoo! Games.





   

Sick sense of humor? Visit Yahoo! TV's 
Comedy with an Edge to see what's on, when. 
http://tv.yahoo.com/collections/222___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re:Explaining monads

2007-08-14 Thread Brian Brunswick
On 15/08/07, Gregory Propf [EMAIL PROTECTED] wrote:
- Original Message 
From: Jeff Polakow [EMAIL PROTECTED]

One general intuition about monads is that they represent computations
rather than simple (already computed) values:

 I still want to re-iterate that they represent /complex/ computations -
multiple, conditional results, extra stuff etc.

Hence the need to perform a run operation like runIdentity, evalState or
 runParser (for Parsec) to get something useful to happen.  Except for lists
 we don't seem to do this.  I suppose lists are so simple that the operators
 :, ++ and the [] constructor do all we ever need with them.  Finally there
 is no runIO because main is essentially that function in every real
 program? - Greg



What the run functions do is unwrap the  monad. They  take apart the 'm a'
and give you back whatever a's might be
inside, and whatever extra stuff too. (Also feeding extra stuff in when m is
like that) Doing that will involve actually evaluating
the value, forcing all the data dependencies and making the 'actions'
happen.

If the monad type 'm a' is already a type we can take apart directly (list,
maybe etc.) theres no need for a run function.

Note that of course unsafePerformIO is runIO. Its just that it doesn't
really nest safely, so we like to only
use the top level one from main.

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


[Haskell-cafe] GHC linking problems

2007-08-14 Thread SevenThunders

I have a large Haskell/C project that needs to be linked against an even
larger set of C libraries and object files  (OpNet) on a linux box (Fedora
Core 7).  So far I have been able to link my Haskell libraries to some C
test code containing a main function without incident.  However the link
flags are very complex having been extracted from ghc.  (e.g. it requires a
host of -u flags and then a bunch of links to external C libraries including
a long list of Haskell libraries.)  

Unfortunately control over the OpNet compilation and linking process is weak
at best.  Moreover it is not clear how the linking occurs and there is some
suspicion that it ultimately creates a dynamic link library which it loads
from some external process  (the exact calls to gcc are hidden).  During the
OpNet build we get the following error

/usr/lib/ghc-6.6.1/libHSrts.a(Main.o): In function `main':
Main.c:(.text+0x22): undefined reference to `__stginit_ZCMain'
Main.c:(.text+0x43): undefined reference to `ZCMain_main_closure'
collect2: ld returned 1 exit status

I do not get this error when statically linking my libraries to a standalone
C function containing a main() function.  What should I look for?  Are there
known work arounds to this problem?  It's troubling that exporting Haskell
to C should be this problematic.  Unfortunately I can not use ghc to compile
the OpNet code as you might imagine.
-- 
View this message in context: 
http://www.nabble.com/GHC-linking-problems-tf4270650.html#a12155220
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Why monad tutorials don't work

2007-08-14 Thread Bill Wood
On Tue, 2007-08-14 at 16:02 -0700, Dan Piponi wrote:
   . . .
 On 8/14/07, Michael Vanier [EMAIL PROTECTED] wrote:
   I'm reminded of
  a physics teacher who was having a similar problem explaining the concept 
  of tensors, until he said
  that a tensor is something that transforms like a tensor does!.
 
 Grrr...must...hold...my...tongue...

Dan, as a former student of a clone of that physics teacher, I am really
interested in what you will say when you fail to hold your tongue.

 -- Bill Wood


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


[Haskell-cafe] Re: Error building takusen with Cabal-1.1.6.2

2007-08-14 Thread John Dell\'Aquila
That fixed my problem. Thank you very much.

Regards,
John

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


[Haskell-cafe] ANN: HAppS-Data 0.9: XML, Pairs, HList, deriveAll

2007-08-14 Thread Alex Jacobson
We've refactored the happs repos and are now going to releasing 
components of HAppS as individual useful packages.  HAppS-Data is the 
first one.  Don't pull a tag, pull the most recent stuff in the repos.


---
HAppS-Data v0.9: XML, Name/Value Pairs, HList, deriveAll

* toXml and fromXml transform your haskell values to and from XML.
Declare your own instances of class Xml to customize the Xml
representation.

* toPairs and fromPairs transform haskell values to and from
name-value pairs (e.g. for url-encoded data).  Pairs are converted
between xpath expressions.  Use toPairsX if you want a conversion
without the top level constructor, fromPairs can handle that as long
as your type has only one top level constructor.

* toHTMLForms to produce an HTML forms representation of your data
that can be consumed by fromPairs in a urldecoding context.  toHTMLForms
uses toPairsX for shorter input field names.

* $(deriveAll) to batch derive Default and as well as the standard
derivable without all the boring per data deriving declarations

* Default missing values by declaring your own instances of class Default or
have default values derived autotomatically.

* Normalize your values by declaring your own instance of class Normalize.

* Type safe easy-to-use heterogenous collections.  t1 .. t2 .. t3
are a heterogenous lists of values.  (HasT hlist t) is a class
constraint to that the hlist contains a particular type.  (x hlist)::t
obtains a value of type t from inside the hlist.  (u hlist v) updates
the hlist with the value v if the hlist has type.  x and u return
compile time errors if the type is not inside the hlist. fromPairs is
currently broken for hlist.

darcs get http://happs.org/HAppS/HAppS-Data

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


[Haskell-cafe] ANNOUNCE: Guihaskell and PropLang 0.1

2007-08-14 Thread Asumu Takikawa

Hello Haskellers. I'm one of the Google Summer of Code students for '07
and I'd like to announce the project my mentor, Neil Mitchell, and I
have been working on.

== GuiHaskell

Guihaskell is a graphical REPL using PropLang, a GUI combinator library
built on top of Gtk2hs, which aims to be an IDE for Haskell written in
Haskell. It's still rough around the edges, so think of this as an alpha
release. As such, I'd appreciate any feedback very much!

Here's a feature list for 0.1:
* Support for GHCi (default) and Hugs
* Quick switching between compilers
* Simple one-click profiling
* Command history

This first release of Guihaskell is mostly infrastructure. For future 
releases I aim to integrate more tools like Cabal and make it easier to 
use with an editor.

== PropLang

PropLang is a GUI library built on Gtk2hs that allows for high
level design. The GUI is expressed as a series of relationships between
GUI elements and data sources. 

Here's a Hello World example:

  import PropLang.Gtk
  import PropLang.Event
  
  main = do
initPropLang
window - getWindow foobar.glade wndFoo
let tb = getCtrl window button :: ToolButton
tb!onClicked += putStrLn Hello World!
showWindowMain window

This example prints Hello World! when the user presses a button
defined in a Glade file. PropLang is used with glade to define the
interface. You can define more complicated relationships using the
combinators in PropLang.Variable.

Here's a snippet from GuiHaskell:

  tie (txtSelect!text) filename
  (\t - if null t then Nothing else Just t) (maybe  id)

tie takes two PropLang variables and relates them so that when one is
updated, it will inject its value into another. It also takes two
functions to run on the data before injection. This snippet is used to
tie the representation of the currently selected file in GuiHaskell (a
Maybe String) to Gtk's TextView buffer (a String). If you injected a
new value into filename...

  filename - Nothing

then txtSelect's text buffer would be set to .

You can also build other behaviors into PropLang variables to do
interesting things. GuiHaskell has a configuration API built around
PropLang. Configuration items are defined as special PropLang variables:

filename - newVarWithName selected_filename
(newConfValueWithDefault Nothing selected_filename)

newVarWithName in PropLang.Variable lets you make new variables with
custom actions to retrieve and set values. newConfValue is defined in
GuiHaskell to serialize configuration items to disk so they can be read
back after closing the program.

For more information you can generate the Proplang docs with haddock.

== Install

Get the packages here:
http://hackage.haskell.org/packages/archive/GuiHaskell/0.1/GuiHaskell-0.1.tar.gz
http://hackage.haskell.org/packages/archive/proplang/0.1/proplang-0.1.tar.gz

Install with cabal:
runhaskell Setup.lhs configure
runhaskell Setup.lhs build
runhaskell Setup.lhs install

==

You can send feedback to my e-mail, the list, or contact me on IRC (I'm
Shimei on #haskell). Thanks.

Cheers,
Asumu Takikawa


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


Re[2]: [Haskell-cafe] Why monad tutorials don't work

2007-08-14 Thread Miguel Mitrofanov
 Grrr...must...hold...my...tongue...
 
 Dan, as a former student of a clone of that physics teacher, I am really
 interested in what you will say when you fail to hold your tongue.
 
  -- Bill Wood
 

MV I have to admit I was wondering the same thing myself.

So was I.

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