RE: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Simon Peyton-Jones
|  I've heard Simon (Peyton-Jones) twice now mention the desire to be able
|  to embed a monadic subexpression into a monad.  That would be
|  http://article.gmane.org/gmane.comp.lang.haskell.prime/2267 and in the
|  recent OSCON video.
|
| I still think that this syntax extension has profound impact and is a
| bad idea. Simon's and Neill's use case was the dreaded name-supply monad
| where the order of effects really doesn't matter up to alpha-conversion.
| The objection to that use case is that monads are not the right
| abstraction for that, they're too general

Just for the record, I am not arguing that this is the Right Thing; I am quite 
agnostic about it.  But the status quo doesn't seem that great either, and I'm 
all for experimentation.  Same goes for view patterns and record wildcards, for 
example.

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


Re: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Jules Bean

Neil Mitchell wrote:

Hi Chris,


I've heard Simon (Peyton-Jones) twice now mention the desire to be able
to embed a monadic subexpression into a monad.


I think this is a fantastic idea, please do so!


$( expr   )   -- conflicts with template haskell
( - expr )   -- makes sense, and I think it's unambiguous

Other ideas:

``expr``  -- back-ticks make sense for UNIX shell scripters
(| expr |)-- I don't think anything uses this yet


This final (| one |) looks way too much like template haskell, it has
the feel of template haskell, even if it isn't yet in the syntax. Your
(- proposal) feels a bit like an operator section - I'm not sure if
that is a good thing or a bad thing, but for some reason feels
slightly clunky and high-syntax overhead, perhaps because of the
inevitable space between the - and expr, and that ()- are all fairly
high semantic value currently in Haskell, while this extension should
blend in, rather than stand out. 


I'm not sure I agree with Neil's misgivings. Certainly - already has a 
high semantic value, but this is a very closely related notion, so I see 
that as consistent.


As for the (), well as far as I know they only have two meanings: 
grouping and tupling. This seems like a special case of grouping to me.


E.g.:

do
  a - m
  b - n
  l a x b y

becomes

l (- m) x (- n) y

...with, I suppose, left-to-right evaluation order. This looks 'almost 
like substitution' which is the goal.


Jules

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


RE: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Simon Peyton-Jones
See also this thread
http://www.haskell.org/pipermail/haskell-prime/2007-July/002269.html
Magnus made a TH library that does something similar, see
http://www.haskell.org/pipermail/haskell-prime/2007-July/002275.html

Nesting is important. Consider
do { a - f x
   ; b - g a
   ; return (2*b) }

Then you'd like to linearise this to give
do { return (2 * $(g $(f x))) }

The hardest thing about this project is finding a suitable syntax!  You can't 
use the same syntax as TH, but it does have a splice-like flavour, so 
something similar would make sense.  $[ thing ] perhaps?  Or %( thing )?  Avoid 
anything that looks like a TH *quotation* because that suggests the wrong 
thing.  (| thing |) is bad.

A good plan can be to start a Wiki page that describes the problem, then the 
proposed extension, gives lots of exmaples, etc.

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Chris
| Smith
| Sent: 03 August 2007 04:30
| To: haskell-cafe@haskell.org
| Subject: [Haskell-cafe] Re: monad subexpressions
|
| Neil Mitchell [EMAIL PROTECTED] wrote:
|  I think this is a fantastic idea, please do so!
| 
|
| Okay, I'll do it then.  If I have a good weekend, perhaps I'll volunteer
| a talk at AngloHaskell after all!  :)
|
| So what about syntax?  I agree with your objections, so we've got
|
| ( - expr )   -- makes sense, and I think it's unambiguous
| ``expr``  -- back-ticks make sense for UNIX shell scripters
|
| The first is something Simon Peyton-Jones came up with (probably on-the-
| fly) at OSCON, and I rather like it a lot; but I'm concerned about
| ambiguity.  The latter seems sensible as well.  Any other ideas?
|
| --
| Chris Smith
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread apfelmus
Chris Smith wrote:
 I've heard Simon (Peyton-Jones) twice now mention the desire to be able 
 to embed a monadic subexpression into a monad.  That would be 
 http://article.gmane.org/gmane.comp.lang.haskell.prime/2267 and in the 
 recent OSCON video.

I still think that this syntax extension has profound impact and is a
bad idea. Simon's and Neill's use case was the dreaded name-supply monad
where the order of effects really doesn't matter up to alpha-conversion.
The objection to that use case is that monads are not the right
abstraction for that, they're too general. Also, a workaround is to lift
functions

  f :: a - b - m c
  g :: d - m b

to

  f' :: m a - m b - m c
  g' :: m d - m b

and thus flip the need for argument sugar

  f $(g x) y   VS   f' (g' (r$ x)) (r$ y)

With r = return, the latter is Haskell98. See also

  http://thread.gmane.org/gmane.comp.lang.haskell.prime/2263/focus=2267

 Also, I got so frustrated that I ended up abandoning some code
 recently because STM is, in the end, so darn hard to use as a
 result of this issue. I'd love to see this solved, and I'm quite
 eager to do it.

This sounds suspicious, since the order of effects is of course
important in the STM monad. Can you post an example of code you intend
to abandon due to ugliness? I'd be astonished if there's no better way
to write it.

Regards,
apfelmus

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


Re: [Haskell-cafe] When is waitForProcess not necessary?

2007-08-03 Thread Dougal Stanton
On 03/08/07, Dave Bayer [EMAIL PROTECTED] wrote:
  I'm actually calling
 Markdown.pl on tiny files (source code of lengths a human would read), and
 it is certainly sluggish enough to be a fair test.)

I had to do this recently, so you might be interested in my approach:

http://193.219.108.225/code/blogpost/BlogPost.hs

The idea here is to run arbitrary text (blog posts) through Markdown
and Smartypants before sending them out to the wider world. The code
should be pretty self-contained and easy to follow. It does use
waitForProcess but I've done my best to keep it clean. (It could still
do with being refactored though; there are still bits or repeated
code.)

The part you want is about 80% of the way down and looks like this:

educate = \s - markdown s = smartypants

markdown = convert Markdown
smartypants = convert SmartyPants

convertWith conv str = do
(hin, hout, herr, proc) - runInteractiveProcess conv [] Nothing Nothing
forkIO $ hPutStr hin str  hClose hin
str' - hGetContents hout
return (str', proc)

convert conv input = do
bracket
(convertWith conv input)
(\(_,pc) - do
ret - waitForProcess pc
return (ret==ExitSuccess))
(return . fst)


Cheers,

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


Re: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Claus Reinke
I've heard Simon (Peyton-Jones) twice now mention the desire to be able 
to embed a monadic subexpression into a monad.  That would be 
http://article.gmane.org/gmane.comp.lang.haskell.prime/2267 
..

Thoughts?


what is the problem you're trying to solve, and is it worth the 
complication in syntax? in previous threads, the answer to the
second questions seemed to be 'no', because there are easy 
workarounds (liftMn/return, or combinator-based lifting) and 
the extension would have non-local effects. 

what is particularly nasty about this extension is that it might be 
easy to add, but will interfere with just about everything else: it 
looks like an operator, and for tiny examples, it seems to have 
a local effect only, but it is really a piece of static syntax distributed 
widely over parts of a dynamic expression; the special quoting 
cannot be understood locally, as it is -namelessly- bound to the 
_next_ enclosing 'do', thereby complicating local program 
transformations, by tools or users. 

why is the syntax even bound to do (adding 'do's or switching 
from 'do' to '=' will change everything), and not to monadic 
operators (with lifting in place, there'd be more isolated monadic 
calls, without need for 'do')? wouldn't it be sufficient to lift the

parameter out of the next enclosing call (and isn't that what the
no-syntax alternatives already provide)? and what is the precise 
specification/what happens with more complex examples?


more helpful than an immediate implementation, imho, would be 
a wiki page formalising the proposed extension and discussing 
the alternatives with pros and cons. 

perhaps there are lifting operations that are missing (eg, liftMn 
lifts non-monadic functions, but how to lift monadic functions 
with non-monadic parameters?), or perhaps the combinators 
that enable lifting of complete calls (rather than functions) could 
be simplified; this issue trips up enough people that it is worth
investigating what the real show-stoppers are, or why the 
workarounds are not more widely used/known. but in the 
end,  i'd expect the no-syntax route to be just as convenient, 
and less problematic in this case.


claus

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Neil Mitchell
Hi

Perhaps we need to cool this thread down a little bit, and refocus. I
personally choose never to use ++ as anything but a statement, since
my brain works that way. Other people find different things natural,
so can pick what they choose. The one thing you can guarantee is that
discussing it isn't going to result in anyone changing their opinion!

The thread started out on monad subexpressions, with request for
helpful thoughts as to what could be done with them, and how we can
treat them syntactically. Does anyone have any further thoughts on the
syntax? We started with 4 suggestions, and as far as I can tell, are
left with only one (- ...). This is the time for people to have new
and clever thoughts, and possibly shape the future of (what I think)
will be a very commonly used Haskell syntax.

For the record, my comments on (- ...) where not objections, but
merely thoughts out loud, and I could certainly see myself using
that syntax in a day to day basis.

Thanks

Neil



On 8/3/07, Mirko Rahn [EMAIL PROTECTED] wrote:

  rewrite *p++=*q++ in haskell?

  it's one of C idioms. probably, you don't have enough C experience to
  understand it :)

 Maybe, but how can *you* understand it, when the standard is vague about it?

 It could be

 A: *p=*q; p+=1; q+=1;
 B: *p=*q; q+=1; p+=1;
 C: tp=p; tq=q; p+=1; q+=1; *tp=*tq;

 ...and so on. Which is the right version?

  result is that currently C code rewritten in Haskell becomes much
  larger and less readable.

 Larger should not be that issue and readability depends on the reader as
 your C example shows. Some Haskellers would very quickly recognize some
 common idioms, where others need some help...

 /BR

 --
 -- Mirko Rahn -- Tel +49-721 608 7504 --
 --- http://liinwww.ira.uka.de/~rahn/ ---
 ___
 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] When is waitForProcess not necessary?

2007-08-03 Thread Bryan O'Sullivan

Dougal Stanton wrote:


I had to do this recently, so you might be interested in my approach:

http://193.219.108.225/code/blogpost/BlogPost.hs

The idea here is to run arbitrary text (blog posts) through Markdown
and Smartypants before sending them out to the wider world.


Pardon me while I veer off-topic, but you could also use Pandoc to do 
this.  No forking required.

http://sophos.berkeley.edu/macfarlane/pandoc/

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Claus Reinke

can you please rewrite *p++=*q++ in haskell?


assuming these operations

   i :: V a - IO (V a)   -- incr var addr, return old addr
   r  :: V a - IO a   -- read var
   w  :: V a - a - IO () -- write var value

and this unfolded translation

   do { qv - r q; w p qv; i p; i q }

assuming further these liftings

   ap1 :: (a-m b) - (m a-m b)
   ap2 :: (a-b-m c) - (m a-m b-m c)

then we can define

   (=:) :: IO (V a) - IO a - IO ()
   mv =: ma = (ap2 w) mv ma

and get this inlined version

 i p =: (r `ap1` i q)

but one might still prefer

   do { w p = r q; i p; i q }

but whatever line-noise one prefers, this still seems a call for
better combinators in the standard libs, rather than a call for
more syntax.

claus

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Neil Mitchell
Hi

Thinking on the semantic issue for the moment:

Can you use (-) outside of a do block?

b  f (- a)

What are the semantics of

do b  f (- a)

where does the evaluation of a get lifted to?

Given:

if (- a) then f (- b) else g (- c)

Do b and c both get monadic bindings regardless of a?

if (- a) then do f (- b) else g (- c)

Does this change to make b bound inside the then, but c bound outside?
Does this then violate the rule that do x == x

Can you combine let and do?

do let x = (- a)
f x

Our best guess is that all monadic bindings get floated to the
previous line of the innermost do block, in left-to-right order.
Monadic expressions in let statements are allowed. Outside a do block,
monadic subexpressions are banned.

Despite all these complications, it's still a great idea, and would be
lovely to have!

Thanks

Neil and Tom


On 8/3/07, Neil Mitchell [EMAIL PROTECTED] wrote:
 Hi

 Perhaps we need to cool this thread down a little bit, and refocus. I
 personally choose never to use ++ as anything but a statement, since
 my brain works that way. Other people find different things natural,
 so can pick what they choose. The one thing you can guarantee is that
 discussing it isn't going to result in anyone changing their opinion!

 The thread started out on monad subexpressions, with request for
 helpful thoughts as to what could be done with them, and how we can
 treat them syntactically. Does anyone have any further thoughts on the
 syntax? We started with 4 suggestions, and as far as I can tell, are
 left with only one (- ...). This is the time for people to have new
 and clever thoughts, and possibly shape the future of (what I think)
 will be a very commonly used Haskell syntax.

 For the record, my comments on (- ...) where not objections, but
 merely thoughts out loud, and I could certainly see myself using
 that syntax in a day to day basis.

 Thanks

 Neil



 On 8/3/07, Mirko Rahn [EMAIL PROTECTED] wrote:
 
   rewrite *p++=*q++ in haskell?
 
   it's one of C idioms. probably, you don't have enough C experience to
   understand it :)
 
  Maybe, but how can *you* understand it, when the standard is vague about it?
 
  It could be
 
  A: *p=*q; p+=1; q+=1;
  B: *p=*q; q+=1; p+=1;
  C: tp=p; tq=q; p+=1; q+=1; *tp=*tq;
 
  ...and so on. Which is the right version?
 
   result is that currently C code rewritten in Haskell becomes much
   larger and less readable.
 
  Larger should not be that issue and readability depends on the reader as
  your C example shows. Some Haskellers would very quickly recognize some
  common idioms, where others need some help...
 
  /BR
 
  --
  -- Mirko Rahn -- Tel +49-721 608 7504 --
  --- http://liinwww.ira.uka.de/~rahn/ ---
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Mirko Rahn



rewrite *p++=*q++ in haskell?



it's one of C idioms. probably, you don't have enough C experience to
understand it :)


Maybe, but how can *you* understand it, when the standard is vague about it?

It could be

A: *p=*q; p+=1; q+=1;
B: *p=*q; q+=1; p+=1;
C: tp=p; tq=q; p+=1; q+=1; *tp=*tq;

...and so on. Which is the right version?


result is that currently C code rewritten in Haskell becomes much
larger and less readable.


Larger should not be that issue and readability depends on the reader as 
your C example shows. Some Haskellers would very quickly recognize some 
common idioms, where others need some help...


/BR

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Miguel Mitrofanov

 rewrite *p++=*q++ in haskell?

MR I always reject such codes when produced by my students. It is just
MR unreadable. I even do not understand what you are trying to achieve.
MR However, gcc seems it to compile to something like

MR *p = *(p+1) ; *q = *(q+1)

MR But for what is the '=' good for?

MR So rewriting it in Haskell (of any size) is a good idea to actually
MR understand the code. Please, could you do it.

MR /BR


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


Re[2]: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Bulat Ziganshin
Hello Mirko,

Friday, August 3, 2007, 3:32:57 PM, you wrote:

 rewrite *p++=*q++ in haskell?

 I always reject such codes when produced by my students. It is just 
 unreadable.

it's one of C idioms. probably, you don't have enough C experience to
understand it :)

 So rewriting it in Haskell (of any size) is a good idea to actually
 understand the code. Please, could you do it.

result is that currently C code rewritten in Haskell becomes much
larger and less readable. if you think that readIORef is more
readable than *, and x-readioref v; writeioref v (x+1) is more
readable than ++  - it's up to you :)



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Mirko Rahn



rewrite *p++=*q++ in haskell?



*p = *(p+1) ; *q = *(q+1)



If that's true then GCC has gone insane, because they are completely different.


Of course you are  right, I just observed at the wrong place..., sorry 
for that.



Though, as any C programmer knows, you really should be using
memcpy()


I like to hear that you would reject it either.

/BR

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: monad subexpressions

2007-08-03 Thread Chris Smith
Neil Mitchell [EMAIL PROTECTED] wrote:
 We started with 4 suggestions, and as far as I can tell, are
 left with only one (- ...).

 For the record, my comments on (- ...) where not objections, but
 merely thoughts out loud, and I could certainly see myself using
 that syntax in a day to day basis.

Right, I definitely didn't read your post as objecting to the syntax.

I do have concerns about it.  In particular, the section-like syntax 
suggests to me (quite misleadingly) that it is somewhat self-contained.  
I find myself half expecting to be able to rewrite (mapM f xs) as
(map (- f) xs), or something like that.  In other words, the syntax 
lies to me.

At the moment, though, I can't think of anything better.

-- 
Chris Smith

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


RE: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Simon Peyton-Jones
| Couldn't this be best done with McBride and Patterson's Applicative
| idiom notation?
|
| So the above would become
|
| [[l m (pure x) n (pure y)]]  (or something like that)
|
| It would have the advantage of being usable with any Applicative, not
| just Monads.

Does anyone have a pointer to a stand-alone description of full-scale idiom 
notation.
S
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: When is waitForProcess not necessary?

2007-08-03 Thread Dave Bayer
Bryan O'Sullivan bos at serpentine.com writes:
 
 Pardon me while I veer off-topic, but you could also use Pandoc to do 
 this.  No forking required.
 http://sophos.berkeley.edu/macfarlane/pandoc/

What I'm doing is neither Haskell nor Markdown specific; I allow any HTML
markup filter that plays nice with the direct HTML I also write (a
restriction I could easily drop), and I cooperate with language-specific
library doc generators such as Haddock.

For all the fuss one reads about Haskell-not-as-fast-as-C, it's amusing how
sluggish Markdown.pl is. Someone should write a small BSD'd Haskell version
as example code for programming in Haskell. I may, although I can't see
myself writing anything called SmartyPants.

I admire pandoc and I allow its use as an alternative to Markdown.pl, as
an external command. I don't want to link it into my code because

* It is GPL'd and I'm writing BSD'd code
* It is a library that does not come with GHC.
* It is twice the length of my code so far.

The Hackage/Cabal universe takes the perspective that one is a committed
Haskell user, and one wants the same diversity of tools enjoyed, say, in
the Perl universe. When one uses Haskell to write a tool whose use is
standalone and not Haskell-specific, there's a very good chance that
someone will come along and try to build it for a new platform, installing
and using GHC for the first time in order to do so. The barrier to entry is
easily doubled if one has to also figure out how to obtain libraries that
do not come automatically with GHC. Plenty of us have the moxie to install
a package like GHC for a single use, because we've heard that hackers can
do such things easily, but we don't really want to join each treehouse.

I've installed versions of, say, Perl, Python, Ruby, even if there was a
possibly lame installation already present. Still, their package systems
generally left me fuming. I know my audience; we mathematicians can be
smart and incredibly stupid at the same time.

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


Re: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Jules Bean

Simon Peyton-Jones wrote:

Does anyone have a pointer to a stand-alone description of full-scale idiom 
notation.


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

I think I've seen something more detailed but I don't know if it was in 
one of Conor's papers, or if it was personal conversation/ seminar...


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


Re: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Claus Reinke

to illustrate why some of us are concerned about this extension,
a few examples might help. consider:

   f (g (- mx))

does this stand for 


   (a) mx = \x- f (g x)
   (b) f (mx = \x- (g x))
   (c) none of the above, because there's no do
   (d) something else entirely

if (a/b), does the decision depend on the type of g (if g is pure,
then (a), if g is monadic itself, then (b))? if (d), what?

if (a/b), then this is no longer preprocessing, but depends on the
types, which means that the type system must work in the presence
of this extension, rather than its pre-processed form. if you want to
avoid that, you're left with (c), but is that any better?

if (c), then the following are no longer equivalent

   1. return ...
   2. do return ...

in particular, 


   do return ..

is no longer a unit of the monad (in (a/b), even return .. isn't). so
if you write

   f (do g (- mx))

you mean (b), while if you write 


   do f (g (- mx))

you mean (a), and if you write 


   f (g (- mx))

you mean either an error, if there is no surrounding 'do', or something 
else, if there is a surrounding 'do'. and woe to those who think they can 
insert some 'do' notation whereever they like - they need to check the 
subexpressions for (-) first!


now, consider nesting monadic subexpressions:

   f (- g (- mx))

surely means the same as f = (g = mx), namely 


   mx = \x- g x = \gx- f gx

right? wrong! we forgot the 'do'. without a 'do'-context, this means
nothing in (c). so if you have

   do 
   ..

   fx - f (- g (- mx))
   ..
   fx - f (- g (- mx))
   ..

and there are no free variables, then you can do the usual sharing to
improve readability, right?

   let fgmx = f (- g (- mx)) in
   do 
   ..

   fx - fgmx
   ..
   fx - fgmx
   ..

wrong again! this is syntax, not expression, so the latter variant
changes the scope the (-)s refer to (some outer 'do', if one exists).
you could have written 

   do 
   let fgmx = f (- g (- mx))

   ..
   fx - fgmx
   ..
   fx - fgmx
   ..

perhaps, and at this stage you might no longer be surprised that
do and let no longer commute. or were you? if you weren't, here's
a quick question: we've already seen the left- and right-identity
laws in danger, so what about associativity?

   do { do { a; b}; c } 


is still the same as
   
   do { a; do { b; c } }


yes? no? perhaps? sometimes? how long did it take you?

could someone please convince me that i'm painting far too
gloomy a picture here?-) 


claus

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


[Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Chris Smith
apfelmus [EMAIL PROTECTED] wrote:
 I still think that this syntax extension has profound impact and is a
 bad idea. Simon's and Neill's use case was the dreaded name-supply monad
 where the order of effects really doesn't matter up to alpha-conversion.
 The objection to that use case is that monads are not the right
 abstraction for that, they're too general.

I'm primarily interested in the two cases where one simply has no choice 
about the use of monads: and those are IO and STM.  No, this is not 
purely functional programming then; but it has some very compelling 
advantages to Haskell's implementation of these, that I'm afraid are 
currently quite hidden behind the difficult syntax.  Using something 
besides a monad is simply not an option.

A lot of what I'm thinking about Haskell now comes from my experience in 
trying to teach it to new programmers (which in turn comes from it being 
lonenly to be the only person I talk to that knows Haskell).  I'm quite 
convinced, right now, that one huge problem with adoption of Haskell has 
to do with this right here.

If there's a way to get nice syntax without modifying the compiler, that 
is certainly an advantage; but I do see it as rather small compared to 
the goal of producing something that it rather simple to understand and 
use.  I can explain desugaring rules for this idea in a short paragraph.  
The alternatives all seem to involve operators and functions that I've 
not used in about six months or more of moderate playing around with 
Haskell.  Type class hacking is way over the top; other ideas seem 
reasonable to me, but I'm concerned they won't seem very reasonable to 
anyone with much less experience using Haskell than I've got.

The other objection, though, and I'm quoting from a post in a past 
thread on this, is something like, The more tiresome monads are, the 
more incentive you have to avoid them.  Unfortunately, I'm afraid this 
cheapens work people are doing in making the necessary imperative parts 
of Haskell more useful and interesting.  Making monads distasteful is 
not a reasonable goal.

  Also, I got so frustrated that I ended up abandoning some code
  recently because STM is, in the end, so darn hard to use as a
  result of this issue. I'd love to see this solved, and I'm quite
  eager to do it.
 
 This sounds suspicious, since the order of effects is of course
 important in the STM monad. Can you post an example of code you intend
 to abandon due to ugliness? I'd be astonished if there's no better way
 to write it.

I'll dig for it later if you like.  The essence of the matter was a 
bunch of functions that looked something like this:

foo = do b' - readTVar b
 c' - readTVar c
 d' - readTvar d
 return (b' + c' / d')

In other words, a string of readTVar statements, followed by one 
computation on the results.  Each variable name has to be duplicated 
before it can be used, and the function is four lines long instead of 
one.

It's true that order of effects *can* be important in monads like IO and 
STM.  It's also true, though, that probably 50% of the time with IO, and 
95% with STM, the order does not actually matter.  Taking a hard-line 
approach on this and forcing a linear code structure is equivalent to 
ignoring what experience has taught in dozens of other programming 
languages.  Can you think of a single widely used programming language 
that forces programmers to write linear one-line-per-operation code like 
this?  IMO, Haskell gets away with this because STM and IO stuff isn't 
very common; and STM and IO will remain uncommon (and will instead be 
replaced by unsafe code written in Python or Ruby) as long as this is 
the case.

I find it hard to speculate that Haskell programmers will understand the 
alternatives, but won't understand something like monadic 
subexpressions are evaluated in the order of their closing parentheses.

-- 
Chris Smith

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


Re: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Jules Bean

Jules Bean wrote:

do
  a - m
  b - n
  l a x b y

becomes

l (- m) x (- n) y

...with, I suppose, left-to-right evaluation order. This looks 'almost 
like substitution' which is the goal.




Having read the thread SPJ pointed to, I should point out that using a 
mixture of Applicative and Monad notation, this can currently be written as:


l $ m * (return x) * n = (return y)

...where the thing that feels weirdest is having to remember to use = 
instead of * for the final 'application'.


Jules

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


[Haskell-cafe] Re: Re: monad subexpressions

2007-08-03 Thread Chris Smith
Neil Mitchell [EMAIL PROTECTED] wrote:
 Thinking on the semantic issue for the moment:
 
 Can you use (-) outside of a do block?

Good question, but my answer is a strong no!  Syntactic sugar for monads 
has always been tied to do blocks; promoting it outside of contexts 
where do announces that you'll be using syntactic sugar seems like a 
very bad idea.

 do b  f (- a)
 
 where does the evaluation of a get lifted to?

I think it's rather clear that a gets moved before b.  The example is 
confusing because the code is bad; not because of any new problems with 
this proposal.

 Given:
 
 if (- a) then f (- b) else g (- c)
 
 Do b and c both get monadic bindings regardless of a?

This is tougher, but I'd say yes.  In this case, you've chosen not to 
give then and else clauses their own do block, so this would 
evaluate both.

Certainly if/then could be made a special case... but it would be 
exactly that.  i.e., if I did this:

cond b th el = if b then th else el

do cond (- a) (f (- b)) (g (- c))

Then you'd lose.  And the fact that you'd still lose there makes me less 
than thrilled to mislead people by special-casing if/then/else.  When 
something is dangerous, it should be labelled as such as loudly talked 
about; but covered up in the hopes that no one will dig deep enough to 
hurt themselves.

 if (- a) then do f (- b) else g (- c)
 
 Does this change to make b bound inside the then, but c bound outside?
 Does this then violate the rule that do x == x

Then yes, it would.

 Can you combine let and do?
 
 do let x = (- a)
f x

Right.  In effect, as a matter of fact, the notation

x - a

would become equivalent to

let x = (- a)

 Our best guess is that all monadic bindings get floated to the
 previous line of the innermost do block, in left-to-right order.
 Monadic expressions in let statements are allowed. Outside a do block,
 monadic subexpressions are banned.

Sure.  SPJ mentioned that you wouldn't promote (- x) past a lambda.  
I'm not convinced (it seems to fall into the same category as the if 
statement), but it's worth considering.

-- 
Chris Smith

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


[Haskell-cafe] Haskell FCGI server.

2007-08-03 Thread George Moschovitis
Dear devs,

is it possible to create a FCGI server that listens to a specific port using
the Haskell FCGI library?
The front end web server would then communicate with this back end FCGI
server through this port.
A small example would be really appreciated.

thanks,
George.

-- 
http://nitroproject.org
http://phidz.com
http://blog.gmosx.com
http://cull.gr
http://www.joy.gr
http://www.me.gr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Simon Peyton-Jones
| f (g (- mx))
|
| does this stand for
|
| (a) mx = \x- f (g x)
| (b) f (mx = \x- (g x))
| (c) none of the above, because there's no do
| (d) something else entirely

For me the answer is definitely (c).  Furthermore there must be no lambda 
between the monadic splice and the do.

Given that, I think the meaning of a monadic splice is straightforward, and all 
your excellent questions have easy answers.  The question remains of whether or 
not it's valuable.

Simon

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


Re: [Haskell-cafe] When is waitForProcess not necessary?

2007-08-03 Thread Dougal Stanton
On 03/08/07, Bryan O'Sullivan [EMAIL PROTECTED] wrote:

 Pardon me while I veer off-topic, but you could also use Pandoc to do
 this.  No forking required.
 http://sophos.berkeley.edu/macfarlane/pandoc/

I'll add that to the list of things that must be done. That list
seems, necessarily, to be longer than any list things I have done.
Last time I looked at PanDoc the docs gave the impression it was not
very complete. It looks a lot better now. The idea of LaTeX embedded
in Markdown sounds awesome...

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


Re: [Haskell-cafe] Re: Re: monad subexpressions

2007-08-03 Thread Neil Mitchell
Hi

  Can you combine let and do?
 
  do let x = (- a)
 f x

 Right.  In effect, as a matter of fact, the notation

 x - a

 would become equivalent to

 let x = (- a)

Hmm, interesting. Consider:

let x = 12
let x = (- x)

Currently, in let x = ... the x is in scope on the right hand side.
Now it isn't. Changing the order of evaluation with syntactic sugar
seems fine, changing the lexical scoping seems nasty. Perhaps this is
a reason to disallow monadic expressions in a let.

  Our best guess is that all monadic bindings get floated to the
  previous line of the innermost do block, in left-to-right order.
  Monadic expressions in let statements are allowed. Outside a do block,
  monadic subexpressions are banned.

 Sure.  SPJ mentioned that you wouldn't promote (- x) past a lambda.
 I'm not convinced (it seems to fall into the same category as the if
 statement), but it's worth considering.

I'm not convinced either, a nice concrete example would let people
ponder this a bit more. What is nice to note is that all your answers
to my questions matched perfectly with what I thought should happen.

Thanks

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


[Haskell-cafe] Question about arrows

2007-08-03 Thread Lewis-Sandy, Darrell
Is there a class property of the Control.Arrow class that represents the
evaluatation of an arrow:

 

eval :: (Arrow a)=a b c-b-c

 

I am writing some higher order code that I would like to work with either
functions or partial functions (implemented as balanced binary search trees)
and don't want to write separate instances for each concrete arrow type.
For example, consider the example below:

 

divideAndConquer::( Arrow a, Bifunctor m)=(m c y-y)-a b c-(x-m b
x)-x-y

divideAndConquer combine solve divide = combine.(bimap (eval solve)
(divideAndConquer combine solve divide)).divide

 

that implements datatype generic divide and conquer.   divide encodes how to
decompose a problem of type x into subproblems, solve encodes how to solve
indivisible sub-problems, and combine encodes how to put the sub-solutions
together.  The branching strategy is encoded in the bifunctor, and the use
of eval faciliatates either evaluating a function or looking up solutions in
a table.

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


Re: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Jules Bean

Dan Piponi wrote:

On 8/3/07, Jules Bean [EMAIL PROTECTED] wrote:

do
   a - m
   b - n
   l a x b y

becomes

l (- m) x (- n) y


Couldn't this be best done with McBride and Patterson's Applicative
idiom notation?

So the above would become

[[l m (pure x) n (pure y)]]  (or something like that)

It would have the advantage of being usable with any Applicative, not
just Monads.



Well that's exactly the kind of discussion I was trying to generate.

And I did give an applicative version when I replied to myself (although 
not admittedly full scale idiom brackets)


Jules

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Bulat Ziganshin
Hello apfelmus,

Friday, August 3, 2007, 12:05:22 PM, you wrote:

 I still think that this syntax extension has profound impact and is a
 bad idea.

can you please rewrite *p++=*q++ in haskell?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Mirko Rahn



rewrite *p++=*q++ in haskell?


I always reject such codes when produced by my students. It is just 
unreadable. I even do not understand what you are trying to achieve. 
However, gcc seems it to compile to something like


*p = *(p+1) ; *q = *(q+1)

But for what is the '=' good for?

So rewriting it in Haskell (of any size) is a good idea to actually 
understand the code. Please, could you do it.


/BR

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Lutz Donnerhacke
* Bulat Ziganshin wrote:
 Hello apfelmus,
 I still think that this syntax extension has profound impact and is a
 bad idea.

 can you please rewrite *p++=*q++ in haskell?

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


Re[2]: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Miguel Mitrofanov

 rewrite *p++=*q++ in haskell?

MR I always reject such codes when produced by my students.

I don't think it's a good idea to reject working code.

MR I even do not understand what you are trying to achieve.

Well, that just means that your students are a bit smarter than you.
And I'd like to ensure you, they know this and are considering you as
a person who is afraid of smart people.

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


[Haskell-cafe] RE: monad subexpressions

2007-08-03 Thread Chris Smith
Simon Peyton-Jones [EMAIL PROTECTED] wrote:
 Furthermore there must be no lambda between the monadic splice and the do.

I'm curious about this.

One could sugar:

do tax - getTax
   return $ map (\price - price * (1 + tax)) bill

into:

do return $ map (\price - price * (1 + (- getTax))) someNums

Do you not think this is desirable?  Is there a negative side-effect 
that I'm not noticing?

I sort of see this in the same boat as Neil's example with if/then/else.  
The meaning may not be precisely what you'd expect... but mind-reading 
is hard, and it's more consistent to just say find the innermost 
containing do block than make up new rules for each piece of syntax.

Granted, a special case of it's an error is far more appealing than 
the corresponding special case for if; but I don't yet see a reason for 
this exception to the rule either.

-- 
Chris Smith

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


Re: RE [Haskell-cafe] Monad Description For Imperative

2007-08-03 Thread Greg Meredith
Haskellians,

i am delighted to see vigorous exchange that actually resulted in change of
positions. i confess i was going to give up, but glad others stepped into
the breach. This is yet another indication of what an unusual community this
is.

Best wishes,

--greg

Date: Fri, 3 Aug 2007 13:43:32 +1200
From: ok [EMAIL PROTECTED]
Subject: Re: RE [Haskell-cafe] Monad Description For Imperative
To: haskell-cafe Cafe haskell-cafe@haskell.org
Message-ID: [EMAIL PROTECTED]
Content-Type: text/plain; charset=US-ASCII; delsp=yes; format=flowed

I asked How is IO a functor?

On 3 Aug 2007, at 11:50 am, Dan Piponi wrote:
 IO is a fully paid up Monad in the categorical sense. The category is
 the category whose objects are types and whose arrows are functions
 between those types. IO is a functor. The object a maps to IO a. An
 arrow f::a-b maps to (= return . f)::IO a - IO b and that can be
 used to make IO an instance of Functor. The natural transforms eta and
 mu are called return and join.


Please go over this again, but slowly this time.
You have convinced me, but I'd like to understand the details a little
better.

I see that any type constructor TC :: * - * is halfway to being a
functor
on this category of types.  It acts on the objects in the obvious way,
so the next step is to see about the arrows.

   If f :: a - b then we want TC f :: TC a - TC b

such that TC (f . g) = TC f . TC g and TC (id::a-a) = id :: TC a -
TC a

Now this is precisely the Haskell Functor class, so TC is the object
part
and fmap is the arrow part.  You say that (= return . f) can be
used to
make [a Monad] an instance of Functor.  Try it... by golly it's true.
I see:  fmap f = (= return . f).

So why *aren't* Monads already set up using the type class machinery
to always *be* Functors in Haskell?  Isn't it bound to confuse people
if monads are functors but Monads are not Functors?

This is especially puzzling because Maybe, [], and IO already *are*
Functors, but the way this is done makes it look accidental, not like
the fundamental property of Monads it apparently is.

(By the way, I note that the on-line documentation for Control.Monad
glosses
 = as Sequentially composes two actions)


-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
505 N 72nd St
Seattle, WA 98103

+1 206.650.3740

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Sebastian Sylvan
On 03/08/07, apfelmus [EMAIL PROTECTED] wrote:
 Chris Smith wrote:
  Also, I got so frustrated that I ended up abandoning some code
  recently because STM is, in the end, so darn hard to use as a
  result of this issue. I'd love to see this solved, and I'm quite
  eager to do it.

 This sounds suspicious, since the order of effects is of course
 important in the STM monad. Can you post an example of code you intend
 to abandon due to ugliness? I'd be astonished if there's no better way
 to write it.

Just because order *technically* matters doesn't mean it *actually*
matters in a given circumstance:

mytransaction = do {
  x0 - readTVar xvar0
  x1 - readTVar xvar1
  :
  xn - readTVar xvarn
  return $ foo x0 x1 .. xn
}

Versus

mytransaction = return $ foo $(readTVar xvar0) $(readTVar xvar1) ..
$(readTVar xvarn)

Now I'm not to happy about the long names for reading variables
either, short overloaded names like get and put would look much
nicer in this example, and in other places too. And certainly,
sometimes you do want to name things for convenience. But in *lots* of
cases you just want to e.g. read N variables, in an arbitrary order,
and then do something with them. Yes the order matters to the
*compiler*, but it doesn't always matter to the *programmer*, so to
have a more convenient way to express those cases would be very nice,
IMO. And there may even be cases where the order does matter but you'd
be happy with a left-to-right ordering.

This has been a pet-peeve of mine for ages. Imperative programming in
Haskell is neat, but I really don't want to write what amounts to
almost assembly programming levels of explicitness for simple tasks.

I'd also like to reiterate my request for a notation that doesn't
require brackets around the *action* but will also work by applying it
to a function which when fully applied to its argument returns an
action (i.e.:   $foo x y + $bar z w, rather than $(foo x y) + $(bar z
w)). Function application is normally very low-noise in Haskell
(good), and it would be nice if we can keep it low-noise in this
notation too.

Maybe $ isn't a good operator though.. How about #? Maybe using angle
brackets would work.. I'd still like to have them work for functions
returning actions though ( foo x y + bar z w ). Wonder what that
would do to ordering comparisons, lexically speaking

-- 
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] Re: monad subexpressions

2007-08-03 Thread Chris Smith
Claus Reinke [EMAIL PROTECTED] wrote:
 to illustrate why some of us are concerned about this extension,
 a few examples might help.

Claus, I've been saving your message in order to respond to it when I 
have the time to look over it in detail.  I don't think there will be 
forthcoming answers from me, though.  Ultimately, it may just have to 
come down to implementing the extension, making it available as an 
extension to GHC and perhaps other Haskell compilers, and then learning 
from people's experience.

If there is a really good syntax that avoids the need for language 
changes, that would be great.  If there's one that's clearly good enough 
and pops up before I finish this, then I may even abort the work.  As it 
stands, though, I'm just not sure how to evaluate ideas without language 
changes against an alternative that doesn't exist.  This is especially 
true when we're talking about non-quantifiable ideas like convenience, 
readability, and intuitiveness.

As such, I'm happy to pursue the language change route, so that we'll 
have a real implementation and a fully developed idea, instead of a 
theory to discuss.  I suspect it will then be more productive to talk 
about the options, such as whether the language change is really needed 
or beneficial.


Neil and I just discussed some of the semantic issues you raise here in 
another subthread.  Some of them are not quite as intuitive as I'd like, 
but the meaning is at least well-defined.  As for this thread, yes I 
agree with Simon that it's necessary to choose your option c and tie 
any new syntax rather tightly to the 'do' keyword; anything else 
involves becoming a mind-reader.

 if (c), then the following are no longer equivalent
 
 1. return ...
 2. do return ...

Yes, that is true.

 if you weren't, here's
 a quick question: we've already seen the left- and right-identity
 laws in danger, so what about associativity?
 
 do { do { a; b}; c } 
 
 is still the same as
 
 do { a; do { b; c } }
 
 yes? no? perhaps? sometimes? how long did it take you?

I'm not entirely sure I understand the point here.  The monad laws are 
defined in terms of = and return.  They have never had anything to do 
with do, let, or -.  All of the monad laws still hold.

-- 
Chris Smith

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


Re: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Dan Piponi
On 8/3/07, Simon Peyton-Jones [EMAIL PROTECTED] wrote:
 | Couldn't this be best done with McBride and Patterson's Applicative
 | idiom notation?

 Does anyone have a pointer to a stand-alone description of full-scale idiom 
 notation.
 S

The full paper is here: http://www.cs.nott.ac.uk/~ctm/Idiom.pdf Is
that what you want?

It would be sweet to have the generality of Applicatives. I find the
examples of vectorised arithmetic and expression evaluators in that
paper quite compelling, besides the use of Applicatives as an
alternative way to talk to monads.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Neil Mitchell
Hi

  do { do { a; b}; c }
 
  is still the same as
 
  do { a; do { b; c } }
 
  yes? no? perhaps? sometimes? how long did it take you?

 I'm not entirely sure I understand the point here.  The monad laws are
 defined in terms of = and return.  They have never had anything to do
 with do, let, or -.  All of the monad laws still hold.

The Monad laws have never been defined in terms of do notation, but
they have always held with do notation since it was simply basic sugar
for  and =. Now do notation is no longer as simple, and the laws
do not hold on do, only on the desugared version. We have lost the
ability to manipulate do quite as easily, and gained a more compact
expression of monadic actions.

I think the trade off is worth it, but others may not.

Thanks

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Claus Reinke

mytransaction = do {
 x0 - readTVar xvar0
 x1 - readTVar xvar1
 :
 xn - readTVar xvarn
 return $ foo x0 x1 .. xn
}

Versus

mytransaction = return $ foo $(readTVar xvar0) $(readTVar xvar1) ..
$(readTVar xvarn)


ah, a concrete example. but isn't that the typical use case for ap?

mytransaction = foo `liftM` r xvar0 `ap` r xvar1 ..
   where r = readTVar

claus

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread David Roundy
On Fri, Aug 03, 2007 at 02:41:05PM +0200, Mirko Rahn wrote:
 rewrite *p++=*q++ in haskell?
 
 it's one of C idioms. probably, you don't have enough C experience to
 understand it :)
 
 Maybe, but how can *you* understand it, when the standard is vague about it?
 
 It could be
 
 A: *p=*q; p+=1; q+=1;
 B: *p=*q; q+=1; p+=1;
 C: tp=p; tq=q; p+=1; q+=1; *tp=*tq;
 
 ...and so on. Which is the right version?

Isn't that the point? It's buggy code if *q == p or *p == q, or a few other
cases perhaps, but if those are not the case, then all of those are
right, and the compiler has the choice to implement whichever it deems
most efficient.

In the cases where this is actually used, all three of those are correct,
the code is understandable, compact and unambiguous.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread david48
On 8/3/07, Neil Mitchell [EMAIL PROTECTED] wrote:

This is how I understand it:

 Can you use (-) outside of a do block?
 b  f (- a)

b  do { ta -a; f ta }
or
b  a = \ta - f ta

 What are the semantics of
 do b  f (- a)

do b  a = \ta - f ta

 Given:

 if (- a) then f (- b) else g (- c)

a = \ta - if (ta) then ( b = \tb - f tb ) else ( c = \tc - f tc )

 do let x = (- a)
 f x

No idea if that could be possible. or maybe :

do a = \ta - let x = ta in f x


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


Re: [Haskell-cafe] Re: Re: monad subexpressions

2007-08-03 Thread david48
Sorry for the double post, I posted with the wrong email address and
haskell-cafe rejected it.

On 8/3/07, Neil Mitchell [EMAIL PROTECTED] wrote:

  Right.  In effect, as a matter of fact, the notation
 
  x - a
 
  would become equivalent to
 
  let x = (- a)

 Hmm, interesting. Consider:

 let x = 12
 let x = (- x)

Wouldn't that be forbidden ?

I'd expect the x in ( - x ) have to be of type m a.

If you meant :

x - return 12
let x = ( - x )

Then I imagine it would turn into

x - return 12
x = \tx - let x = tx in 

Isn't that correct ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Chris Smith
Neil Mitchell [EMAIL PROTECTED] wrote:
  Right.  In effect, as a matter of fact, the notation
 
  x - a
 
  would become equivalent to
 
  let x = (- a)
 
 Hmm, interesting. Consider:
 
 let x = 12
 let x = (- x)

Okay, so the desugaring process wouldn't terminate in that case!  One 
could either: (a) try to retain the equivalence in theory, but make it 
illegal to use x in a monadic subexpression when defining x; (b) we 
could abandon my claim that they are equivalent.

 I'm not convinced either, a nice concrete example would let people
 ponder this a bit more.

I tried to provide something in my response to Simon.  Here it is again:

 One could sugar:

 do tax - getTax
return $ map (\price - price * (1 + tax)) bill

 into:

 do return $ map (\price - price * (1 + (- getTax))) someNums

 What is nice to note is that all your answers
 to my questions matched perfectly with what I thought should happen.

That is nice.  I'm still very uncomfortable with the - syntax (a 
complete flip for me since this morning!); and a little uneasy about the 
use of case, if, lambdas, etc.  Time to keep thinking, I guess.

I'd like to take Simon's suggestion and do a wiki page about this; but 
it should probably be on the Haskell prime wiki, no?  I'm not entirely 
clear on how to get an account there.  I could add it to HaskellWiki, 
but I think that would be the wrong place for it.

-- 
Chris Smith

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


Re: FW: RE [Haskell-cafe] Monad Description For Imperative Programmer

2007-08-03 Thread David Menendez
On 8/1/07, Jeff Polakow [EMAIL PROTECTED] wrote:
 But what about an actual object of type 'IO
   Int', say?
 
 I usually describe the type resulting from applying a monad a computation.

Same here. If m is a monad, then m a is a computation. (Of course,
computations are first-class values, like functions.) I've
occasionally called functions of type a - m b monadic functions,
but I suspect that's poor style.

I wonder how much of the confusion surrounding monads comes from the
fact that using them in Haskell involves higher-order functions, type
constructors, and type constructor classes.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Bulat Ziganshin
Hello Claus,

Friday, August 3, 2007, 8:12:13 PM, you wrote:

 f (g (- mx))

 does this stand for 

 (a) mx = \x- f (g x)

this variant. just like any imperative language (are you used any?).
idea of FORmula TRANslator is old and widely used enough to prevent
such questions


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Bulat Ziganshin
Hello Chris,

Friday, August 3, 2007, 8:09:49 PM, you wrote:

 foo = do b' - readTVar b
  c' - readTVar c
  d' - readTvar d
  return (b' + c' / d')

 It's true that order of effects *can* be important in monads like IO and
 STM.  It's also true, though, that probably 50% of the time with IO, and

90%, in my programs at least

 95% with STM, the order does not actually matter.  Taking a hard-line 
 approach on this and forcing a linear code structure is equivalent to 
 ignoring what experience has taught in dozens of other programming 
 languages.  Can you think of a single widely used programming language
 that forces programmers to write linear one-line-per-operation code like
 this?

assembler :)  it's what our opponents propose - let's Haskell be like
assembler with its simple and concise execution model :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Chris Smith
david48 [EMAIL PROTECTED] wrote:
 On 8/3/07, Neil Mitchell [EMAIL PROTECTED] wrote:
 
  Hmm, interesting. Consider:
 
  let x = 12
  let x = (- x)
 
 Wouldn't that be forbidden ?
 
 I'd expect the x in ( - x ) have to be of type m a.
 

Yes, unless of course you did:

instance (Monad m, Num n) = Num (m n)

or some such nonsense. :)

 If you meant :
 
 x - return 12
 let x = ( - x )

This would be equally wrong.  Perhaps you meant:

do let x = return 12
   let x = (- x)
   ...

Then this would become:

do let x = return 12
   t1 - x
   let x = t1
   ...

Which is, in turn:

let x = return 12 in x = (\t1 - let x = t1 in ...)

-- 
Chris Smith

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Josef Svenningsson
On 8/3/07, Chris Smith [EMAIL PROTECTED] wrote:
 Neil Mitchell [EMAIL PROTECTED] wrote:
  I'm not convinced either, a nice concrete example would let people
  ponder this a bit more.

 I tried to provide something in my response to Simon.  Here it is again:

  One could sugar:

  do tax - getTax
 return $ map (\price - price * (1 + tax)) bill

  into:

  do return $ map (\price - price * (1 + (- getTax))) someNums

I think what Simon is worried about here is that the syntax in the
latter expression suggests that the effects of getTax will be
performed every time the lambda is applied. After all getTax appears
inside the lambda. But in fact is the side effects will only be
performed once. I agree with Simon that (- getTax) shouldn't be
promoted outside a lambda.

Fwiw, I'm all in favor for some new piece of syntax for this problem.

Cheers,

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


[Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread apfelmus
Chris Smith wrote:
 I'm primarily interested in the two cases where one simply has no
 choice about the use of monads: and those are IO and STM.
 No, this is not purely functional programming then; but it has
 some very compelling  advantages to Haskell's implementation of
 these, that I'm afraid are  currently quite hidden behind the
 difficult syntax.  Using something besides a monad is simply not
 an option.

 The more tiresome monads are, the more incentive you have to
 avoid them.  Unfortunately, I'm afraid this cheapens work people
 are doing in making the necessary imperative parts of Haskell
 more useful and interesting.  Making monads distasteful is not a
 reasonable goal.

 Can you think of a single widely used programming language
 that forces programmers to write linear one-line-per-operation code
 like this?  IMO, Haskell gets away with this because STM and IO stuff
 isn't very common; and STM and IO will remain uncommon (and will
 instead be  replaced by unsafe code written in Python or Ruby) as
 long as this is the case.

I mean it in the following way: the power of Haskell is that a large
core of pure functions does the actual algorithmic work and is
surrounded by a small layer of imperative code. It's not possible to
avoid the small layer of imperative code, of course. But the more you
treat imperative code as somewhat pure, the greater the danger that the
purely functional logic will be buried inside a mess of imperative code.
In other words, the goal is exactly to make IO and STM uncommon,
otherwise you loose the power the purely functional approach offers.

What I want to say is: if you feel the urge to use the monad splicing
syntax, then I think that there's a big chance that the code you write
is in essence pure and can also be made completely pure. That's why I'd
like to see the code that made you give up. It may require much more
pondering to find a pure abstraction to the programming problem at hand.
But once found, it bests any ad-hoc code.

For example, take the HGL (Haskell Graphics Library) which actually
shows the boundary between pure and monad. The main abstraction is the type

  Graphic

that represents a graphic to be drawn on the screen. It's implemented
with a monad  Draw a  with in turns does IO to draw itself on the
screen. But the abstraction is to treat this as a purely functional
value with operations like

  emptyGraphic :: Graphic
  polygon  :: [Point] - Graphic
  overGraphic  :: Graphic - Graphic - Graphic

to create and compose graphics. To draw a graphic, you have to use IO.
But his is no reason not to offer a pure abstraction even if the
internals are littered with IO.
HGL still exports the  Draw  monad

  type Graphic = Draw ()

and I consider this a sin. It only appears as monad in the three functions

  selectBrush :: Brush - Draw Brush
  selectPen   :: Pen   - Draw Pen
  selectFont  :: Font  - Draw Font

which exist to enable the user to hand-optimize a bit since brush, font
and pen creation is expensive on Win32. But arguably, these
optimizations can be performed automatically under the hood.

An interesting example of how a purely functional data structure makes
life much easier is described in

  N. Ramsey and J. Dias.
  An Applicative Control-Flow Graph Based on Huet's Zipper
  http://www.eecs.harvard.edu/~nr/pubs/zipcfg-abstract.html

abstractWe are using ML to build a compiler that does low-level
optimization. To support optimizations in classic imperative style, we
built a control-flow graph using mutable pointers and other mutable
state in the nodes. This decision proved unfortunate: the mutable flow
graph was big and complex, and it led to many bugs. We have replaced it
by a smaller, simpler, applicative flow graph based on Huet's (1997)
zipper. The new flow graph is a success; this paper presents its design
and shows how it leads to a gratifyingly simple implementation of the
dataflow framework developed by Lerner, Grove, and Chambers
(2002)./abstract



That being said, it is of course desirable to be able to describe
genuinely imperative behavior like resource (de-)allocation elegantly in
Haskell. Not everything can be pure :) (or rather :( ). But I'm not sure
whether the linearization imposed is really an issue then.



 Ultimately, it may just have to come down to implementing the
 extension, making it available as an extension to GHC and perhaps
 other Haskell compilers.

 As it  stands, though, I'm just not sure how to evaluate ideas
 without language changes against an alternative that doesn't exist.

Hm, it seems slightly unfair to me to leave the burden of searching for
an alternative to somebody else.

 I can explain desugaring rules for this idea in a short paragraph.
 The alternatives all seem to involve operators and functions that I've
 not used in about six months or more of moderate playing around with
 Haskell.

In fact, applicative functors are a very useful and powerful abstraction
and to some extend, they exactly solve 

Re: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Dan Weston

Jules Bean wrote:

do
  a - m
  b - n
  l a x b y

becomes

l (- m) x (- n) y

...with, I suppose, left-to-right evaluation order. This looks 'almost 
like substitution' which is the goal.


Almost?

So then (flip f) (- m) (- n) does *not* equal f (- n) (- m) ?

There goes any hope of my understanding future Haskell code. (- n) sure 
looks like an operator section to me, and more importantly a first class 
Haskell object. What human parsing this would not see a mere function 
application?


And I guess this makes the following complete nonsense:

do
  let a = (- m)
  let b = (- n)
  l a x b y

What about

do
  let (b,a) = ((- n),(- m))

  -- many lines of code

  l a x b y

Who can say that b was evaluated before a?

I hope the language syntax does not evolve beyond my merely mortal 
ability to desugar it?


Dan Weston

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Claus Reinke
I'll dig for it later if you like.  The essence of the matter was a 
bunch of functions that looked something like this:


foo = do b' - readTVar b
c' - readTVar c
d' - readTvar d
return (b' + c' / d')

In other words, a string of readTVar statements, followed by one 
computation on the results.  Each variable name has to be duplicated 
before it can be used, and the function is four lines long instead of 
one.


if that happens frequently, an instance of the numeric classes 
seems called for, automating both the lifting and the readTVar,
but if there are only a couple of cases, you could lift the operations 
for the module, or even per definition:


   foo1 b c d = readTVar b + readTVar c / readTVar d
 where (+) = liftM2 (Prelude.+)
   (/) = liftM2 (Prelude./)

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Neil Mitchell
Hi

  let x = 12
  let x = (- x)

 Okay, so the desugaring process wouldn't terminate in that case!  One
 could either: (a) try to retain the equivalence in theory, but make it
 illegal to use x in a monadic subexpression when defining x; (b) we
 could abandon my claim that they are equivalent.

This example isn't intended to be about termination of the desugaring,
or about types etc - the only point is to note the change in the
lexical scoping rules that (-) gives. I'll try and state my concern
more clearly:

let x = a

In this expression, x is available for use within a, since let is
recursive. This allows us to write:

let xs = paws : xs

With the end result that xs is bound to [paws,paws,paws,paws...

Now consider:

let x = (- a)

With the proposed desugaring we obtain:

temp - a
let x = temp

Now x is NOT in scope within the expression a! We have changed the
static lexical scoping, and only within the brackets. This behaviour
is (in my opinion) horrid. A quick poll of people in my office lead us
all to believe that this issue means you should not be allowed (-)
within a do's let statement.

This leads us to a second problem, floating these monadic expressions
outside any binding:

do case x of
 [] - return 1
 (y:ys) - f (- g y)

Here, the proposed desugaring does not work, since y is not in scope
where we move the element to.

Perhaps this leads to the conclusion that monadic subexpressions
should not be allowed inside any binding group, including let, case or
lambda.

Thanks

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


[Haskell-cafe] Re: Re: monad subexpressions

2007-08-03 Thread Chris Smith
Bulat Ziganshin [EMAIL PROTECTED] wrote:
 assembler :)  it's what our opponents propose - let's Haskell be like
 assembler with its simple and concise execution model :)

I feel bad that portions of this thread have gotten a bit ugly.  I don't 
have any opponents, so far as I know.  I am just trying to discuss the 
best way to solve this problem.

-- 
Chris Smith

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Neil Mitchell
Hi

 if you write :

 let x = (-a):x

 is it possible that is desugars into :

 temp -a
 let x = temp:x

 that would'nt work ?

That would work, since 'a' doesn't refer to 'x'. I can't think of a
real example where it becomes an issue, but the scope within 'a' has
changed.

 Also :

  do case x of
   [] - return 1
   (y:ys) - f (- g y)

 Is it not possible that is desugars to

 do case x of
  [] - return 1
  (y:ys) - g y = \temp - f temp

See the rule about always binding to the previous line of a do block.
This case then violates that.

Thanks

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread david48
On 8/3/07, Neil Mitchell [EMAIL PROTECTED] wrote:

 temp - a
 let x = temp

if you write :

let x = (-a):x

is it possible that is desugars into :

temp -a
let x = temp:x

that would'nt work ?
I realize I may be asking dumb questions but being dumb never harmed
anyone so :)


Also :

 do case x of
  [] - return 1
  (y:ys) - f (- g y)

Is it not possible that is desugars to

do case x of
 [] - return 1
 (y:ys) - g y = \temp - f temp



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

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


Re: [Haskell-cafe] Re: HDBC or HSQL

2007-08-03 Thread Alex Jacobson
Will be pushing out the refactored happs repos in the next 2 weeks.  The 
gist is:


* HAppS.IxSet provides efficient query operations on haskell sets.
* HAppS.State provides ACID, replicated, and soon sharded access to your
  application state.
* HAppS.Network will provide server side HTTP functionality from which 
to access your replicated state.


-Alex-

Bulat Ziganshin wrote:

Hello Alex,

Wednesday, August 1, 2007, 8:34:23 AM, you wrote:


I am asking because I am trying to make HAppS a reasonable replacement
for all contexts in which you would otherwise use an external relational
database except those in which an external SQL database is a specific 
requirement.


where i can read about such usage?




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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Neil Mitchell
Hi

   do case x of
[] - return 1
(y:ys) - g y = \temp - f temp

  See the rule about always binding to the previous line of a do block.
  This case then violates that.

 I assumed that the example was equivalent to :

 do case x of
  [] - return 1
  (y:ys) - do f (- g y)

 Shouldn't the rule work then ?

If the do was inserted, then yes, this would work. Without it, it
doesn't. Perhaps this makes a restriction to not inside
case/let/lambda not that severe, since usually an additional do could
be inserted.

Thanks

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


[Haskell-cafe] Re: When is waitForProcess not necessary?

2007-08-03 Thread Dave Bayer
So I stared at the documentation in Control-Concurrent, learned about
finally and MVar variables, and crossed the genes from the suggestions here
to come up with

runCommand ::  String - String - IO (String,Bool)
runCommand cmd input = do
 (inp,out,err,pid) - runInteractiveCommand cmd
 let get h = do
mvar - newEmptyMVar
let put xs = seq (length xs) (putMVar mvar xs)
forkIO $ finally (hGetContents h = put) (put [])
takeMVar mvar
 if null input then return () else hPutStr inp input
 output - get out
 errmsg - get err
 exit   - waitForProcess pid
 case exit of
  ExitSuccess - return (output,True)
  ExitFailure _ - do
hPutStrLn stderr errmsg
return (errmsg,False)

which seems to work well; I haven't beat on it. I like the return type for
my needs, e.g. I can write

(out,ok) - runCommand mark doc
if ok then write out src
 else hPutStr stderr out 

So why don't the MVar examples in this thread bracket somehow, e.g. with
finally as Control-Concurrent suggests:

Note that we use finally from the Control.Exception module to make
sure that the MVar is written to even if the thread dies or is killed
for some reason.

It seems to me that this could happen, with waitForProcess doing fine, yet
the MVar never getting written. (I haven't written a test example to
exercise this.)


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


Re: [Haskell-cafe] Re: HDBC or HSQL

2007-08-03 Thread Alex Jacobson
Have you looked at the HAppS.DBMS.IxSet?  It gives you a type safe way 
to query indexed collections.


-Alex-

Isto Aho wrote:

Hi,

I'd like to store small matrices into a db. Number of rows and columns 
may vary in a way not
known in advance. One might use a relation (matrixId, col, row, value) 
or something like that
but if it is possible to put a matrix in one command into db, some 
queries will be easier.
E.g., one relation can store several matrices and it would be easy to 
query, how many
matrices are stored currently. With that above four tuple you can find 
out the number of unique

matrixId's, too, but it is not as easy as with matrices.

Anyhow, now I'm not sure if I should stick with HSQL any more... Earlier 
comments on this
thread made me think that maybe it would be a better idea to try to 
learn enough HDBC.


This would be used in a server application. Is HAppS applicable here?

e.g. after some tweaking the following works with HSQL:

addRows = do
dbh - connect server database user_id passwd
intoDB dbh ([555,111, 50, 1000]::[Int]) 
([21.0,22.0,23.0,24.0]::[Double])
intoDB dbh ([556,111, 50, 1000]::[Int]) 
([21.0,22.0,23.0,24.0]::[Double])

intoDB dbh ([]::[Int]) ([]::[Double])
   where
intoDB dbh i_lst d_lst =
catchSql (do
let cmd = INSERT INTO trial (intList, dList) 
VALUES ( ++
toSqlValue i_lst ++ , ++ toSqlValue 
d_lst ++ )

execute dbh cmd
)
(\e - putStrLn $ Problem:  ++ show e)


Similarly, queries can handle matrices and I like that it is now
possible to select those columns or rows from the stored matrix that
are needed.  E.g.

retrieveRecords2 :: Connection - IO [[Double]]
retrieveRecords2 c = do
-- query c select dList[1:2] from trial = collectRows getRow
query c select dList from trial = collectRows getRow
where
getRow :: Statement - IO [Double]
getRow stmt = do
lst   - getFieldValue stmt dList
return lst
readTable2 = do
dbh - connect server database user_id passwd
values - retrieveRecords2 dbh
putStrLn $ dLists are :  ++ (show values)


br,
Isto


2007/8/1, Alex Jacobson [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED]:


Out of curiosity, can I ask what you are actually trying to do?

I am asking because I am trying to make HAppS a reasonable replacement
for all contexts in which you would otherwise use an external relational
database except those in which an external SQL database is a specific
requirement.

-Alex-



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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Dan Doel
On Friday 03 August 2007, Sebastian Sylvan wrote:
 On 03/08/07, Claus Reinke [EMAIL PROTECTED] wrote:
  ah, a concrete example. but isn't that the typical use case for ap?
 
  mytransaction = foo `liftM` r xvar0 `ap` r xvar1 ..
  where r = readTVar

 I really find it difficult to articulate why this isn't acceptable,
 because it seems so obvious to me! It's short yes, but I really don't
 think it's very clear...
 I have a hard time believing that anyone finds that natural. After
 lots and lots of mind-bending forays into various branches of
 mathematics, then yes maybe you can get used to it, but it's hardly as
 natural as saying add this one symbol to your values to extract
 monadic values left-to-right.

Note that if this is the example we're using, idiom brackets solve things:

  mytransaction = [[ foo (r xvar0) (r xvar1) ...]]
where r = readTVar

and are, possibly, less fraught with peril, considering all the discussions 
about where the desugaring should place the implicit binding, and what 
happens if there isn't an enclosing do and so on (as idiom brackets desugar 
to the foo `liftM` r xvar0 `ap` r xvar1 ... mentioned above, and the entire 
expression is delimited, there are no such questions to be pondered, I 
think).

Also, note, if you use the operators in Control.Applicative, then:

  return $ foo $(bar1) $(bar2) $(bar3) ...

can be:

  return foo * bar1 * bar2 * bar3 ...

or:

  foo $ bar1 * bar2 * bar3

I don't (personally) see how that's any more cryptic than placing brackets 
around around the monadic values themselves. In either case, there's some 
magic going on that the user may or may not understand. In the applicative 
case, it's using a different kind of (Monadic/Applicative) function 
application via an operator. In the monad brackets case, it's doing a macro 
expansion. I, personally find the former clearer, but perhaps that's because 
I understand Applicative fairly well, but only have a vague idea of what, 
specifically, the macro will be doing so far.

To get outside the scope of idiom brackets/applicative, you'd need a use case 
like:

  if $(mexpr) then branch1 else branch2

or (lest that be to easy):

  case $(mexpr) of
  p1 - branch1
  p2 - branch2
  ...

In other words, something where you're not simply applying a pure function to 
a bunch of monadic arguments. I can't say I've run into such patterns much 
myself, but I've been told they're common in xmonad, and may be elsewhere.

In general, I guess you'd need the monad brackets when you'd need to interact 
with other syntax (since it isn't first-class). Record update would probably 
be another example. But applications of pure functions to monadic values 
doesn't seem like a particularly compelling motivator, in my opinion.

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Brandon Michael Moore
much snipping

 Also, note, if you use the operators in Control.Applicative, then:
 
   return $ foo $(bar1) $(bar2) $(bar3) ...
 
 can be:
 
   return foo * bar1 * bar2 * bar3 ...
 
 or:
 
   foo $ bar1 * bar2 * bar3
 
 I don't (personally) see how that's any more cryptic than placing brackets 
 around around the monadic values themselves. 
 ...

Seconded. The main difference with brackes is that the application to pure
values looks the same as normal application.

 
 To get outside the scope of idiom brackets/applicative, you'd need a use case 
 like:
 
   if $(mexpr) then branch1 else branch2
 
 or (lest that be to easy):
 
   case $(mexpr) of
   p1 - branch1
   p2 - branch2
   ...
 
 In other words, something where you're not simply applying a pure function to 
 a bunch of monadic arguments. I can't say I've run into such patterns much 
 myself, but I've been told they're common in xmonad, and may be elsewhere.

General purpose brackets are overkill here. I would really like a simple
monadic case. What's so bad about

caseM mexpr of
  p1 - branch1
  p2 - branch2



(mexpr = \e - case e of
  p1 - branch1
  p2 - branch2)

It's simple sugar for working with monadic code, much like do notation.
(indeed, it seems to plug a gap - we have do for sequencing, liftM and
so on for application, but no sugar for case discrimination)

It's a much simpler sort of thing than this fancy sugar for intermixing
code in various monads people have been talking about (so far it seems
assumed that one is just Identity...)

Brandon

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Stefan O'Rear
On Fri, Aug 03, 2007 at 05:48:18PM -0700, Brandon Michael Moore wrote:
 General purpose brackets are overkill here. I would really like a simple
 monadic case. What's so bad about
 
 caseM mexpr of
   p1 - branch1
   p2 - branch2
 
 
 
 (mexpr = \e - case e of
   p1 - branch1
   p2 - branch2)
 
 It's simple sugar for working with monadic code, much like do notation.
 (indeed, it seems to plug a gap - we have do for sequencing, liftM and
 so on for application, but no sugar for case discrimination)
 
 It's a much simpler sort of thing than this fancy sugar for intermixing
 code in various monads people have been talking about (so far it seems
 assumed that one is just Identity...)

I think the CaseLambda proposal on the Haskell' wiki solves this one
nicely.

mexpr = case of
  p1 - branch1
  p2 - branch2

You still have to use =, but you don't have to name the scrutinee (and
names are expensive cognitively).

Stefan


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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Antoine Latter
On 8/3/07, Chris Smith [EMAIL PROTECTED] wrote:
 Yes, unless of course you did:

 instance (Monad m, Num n) = Num (m n)

 or some such nonsense. :)

I decided to take this as a dare - at first I thought it would be easy
to declare (Monad m, Num n) = m n to be an instance of Num (just lift
or return the operators as necessary), but I ran into trouble once I
realized I needed two things I wasn't going to get:

An instance of Eq (m n), and an instance of Show (m n) for all monads
m.  Eq would need a function of the form:

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

and Show would need a function of type m a - String

There's no way I'm getting a function of those types using return and
join to operate on the monad.

So, there went that idea.

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Twan van Laarhoven

Antoine Latter wrote:


On 8/3/07, Chris Smith [EMAIL PROTECTED] wrote:


Yes, unless of course you did:

   instance (Monad m, Num n) = Num (m n)

or some such nonsense. :)



I decided to take this as a dare - at first I thought it would be easy
to declare (Monad m, Num n) = m n to be an instance of Num (just lift
or return the operators as necessary), but I ran into trouble once I
realized I needed two things I wasn't going to get:

An instance of Eq (m n), and an instance of Show (m n) for all monads
m.  Eq would need a function of the form:

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

and Show would need a function of type m a - String


What about Eq1 and Show1 classes? In the same vein as Typeable1:

 class Eq1 f where
  eq1  :: Eq a = f a - f a - Bool
  neq1 :: Eq a = f a - f a - Bool

 class Show1 f where
  show1  :: Show a = f a - String
  showsPrec1 :: Show a = Int - f a - ShowS

Now you can declare the Num instance:

 instance (Monad m, Eq1 m, Show1 m, Num n) = Num (m n) where
  (+) = liftM2 (+)
  (-) = liftM2 (-)
  (*) = liftM2 (*)
  abs = liftM abs
  signum = liftM signum
  negate = ligtM negate
  fromInteger = return . fromInteger

And just to show that such instances can exist:

 instance Eq1 [] where
   eq1  = (==)
   neq1 = (/=)

 instance Show1 [] where
   show1 = show
   showsPrec1 = showsPrec


Note: All of this is untested code.

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


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Bulat Ziganshin
Hello apfelmus,

Saturday, August 4, 2007, 12:22:53 AM, you wrote:

 avoid the small layer of imperative code, of course. But the more you
 treat imperative code as somewhat pure, the greater the danger that the
 purely functional logic will be buried inside a mess of imperative code.
 In other words, the goal is exactly to make IO and STM uncommon,
 otherwise you loose the power the purely functional approach offers.

it's point of view of theoretical purist. i consider Haskell as
language for real world apps and need to write imperative code appears
independently of our wishes. in paricular, it's required to write very
efficient code, to interact with existing imperative APIs, to make
programs which has explicit memory control (as opposite to lazy
evaluation with GC)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[4]: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Bulat Ziganshin
Hello Claus,

Friday, August 3, 2007, 7:29:32 PM, you wrote:

 how about *Object.File.Line.CurPtr++ = *AnotherObject.File.Line.CurPtr++  ? 
 ;)

 what's the difference?-)

 let p = Object.File.Line.CurPtr
 let q = AnotherObject.File.Line.CurPtr
 do { w p = r q; i p; i q }

back to the assembler future? :)  so-called high-level languages
started with the idea that you don't need to give explicit names to
intermediate results

 the problem with Haskell is that we need to split C expression into
 several statements and explicitly specify execution order even when we
 know that it doesn't matter. ideally, it should be possible to define
 
 ++x = modifyIORef x (+1)  readIORef x
 *x  = readIORef x

 apart from the prefix symbols (i used one-letter prefix names), you 
 can (as i'm sure you know). and the point of my little exercise was to
 show that instead of doing the splitting by hand at each usage site, 
 we can write lifting combinators that do the splitting behind the scenes.
 what gives haskell aspirations to be a fine imperative language is that
 its abstraction mechanisms work as well for imperative code as for
 functional code.

can you give translation you mean? i don't have anything against
combinators, they just need to be easy to use, don't forcing me to
think where i should put one, as i don't think with lazy code and C
imperative code. and they shouldn't clatter the code, too. just try to
write complex expression using C and these combinators


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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