Am Montag, 8. August 2005 11:30 schrieb Bulat Ziganshin:
> [...]
> constructor gives you type-safety! without constructor there is no
> difference between Point and (Float, Float), only constructor give you
> syntax difference between these two types!
>
> newtype Point = Point (Float, Float)
> unP
Hello mt,
Sunday, August 07, 2005, 10:26:07 PM, you wrote:
m> check5 = do { 5 <- m ; return 0 }
i think the actual translation is:
m >>= (\var -> case var of
5 -> return 0
_ -> fail)
where fail = Nothing for Maybe monad
m> second one:
m> is it possible to wr
Am Sonntag, 7. August 2005 20:40 schrieb Lemmih:
> [...]
> > second one:
> > is it possible to write something like
> > type Point = (Float, Float)
> > type Vector = (Float, Float)
> > and still have type safety (i.e. not be able to mix Point and Vector)
> > (and still have (*,*) without construct
t; with its reason are important
> for me to understand monads and do notation, so maybe someone can rephrase
> "there is nothing magic with do" and explain the exposed behavior?
The actual translation is a bit more complex to deal with (surprise!)
pattern-match failures, lik
quot;Exception: Non-exhaustive patterns" (which is what i've expected).
>
> the sentence "there is nothing magic with do" with its reason are important
> for me to understand monads and do notation, so maybe someone can rephrase
> "there is nothing magic with do&qu
rn 0 }
check5' = m >>= \5 -> return 0
the first check5 is ok and return Nothing while the second check5' will raise
an "Exception: Non-exhaustive patterns" (which is what i've expected).
the sentence "there is nothing magic with do" with its reason a
Simon Marlow wrote:
| This whole discussion is a red herring. The Haskell
| report doesn't say anything about sharing - it doesn't
| even mandate laziness (look in the index - you won't
| find the term "lazy" :-).
I was not suggesting that the Haskell'98 report should
change or even give a
mple
f = do
regardless of whether the translation uses >> or >>=, because GHC
implements full laziness (when -O is turned on).
So you might reasonably argue that Haskell should provide more control
over such things, and I might well agree. But there's no poi
> I don't believe that it will break many programs. How many programs
> produce large *input independent* output, that is not already
> literally in the source, in a caf with a long life-time?
That sounds like a description of all the animation programs in Paul
Hudak's School of Expression book
> I do not understand what full laziness has to do with all
> this! The big question is, in the following:
>
> f = do
>
>
> Should be shared among different calls to f? It is
> clear that will, but will not be shared,
> using the current translation used by GHC and Hugs.
Well,
he current translation used by GHC and Hugs.
Maybe I should be a bit more concrete; Here is a little
example program:
>>>
main =
do print "start"
writeFile "apa" (show [1..])
<<<
When translating the do-notation using >>, we blow out of
heap space (in
"Simon Peyton-Jones" <[EMAIL PROTECTED]> writes:
> | So, changing the translation in GHC might actually introduce
> | a very nasty space leak in existing programs!
>
> It might, conceivably. But the H98 report doesn't seem the right
> place to try to tweak full laziness. So I'm going to leave
| So, changing the translation in GHC might actually introduce
| a very nasty space leak in existing programs!
It might, conceivably. But the H98 report doesn't seem the right
place to try to tweak full laziness. So I'm going to leave the report
as it is. Hugs and GHC have changed to match.
On Sun, Apr 14, 2002, Koen Claessen wrote:
>
> | do {e ; stmts} = e >> do {stmts}
>
> With the risk of being late at this, and with the risk of
> repeating something that has already been said (because I
> have been away), I will give my two euro-cents.
>
> I remember a discussion at the
| do {e ; stmts} = e >> do {stmts}
With the risk of being late at this, and with the risk of
repeating something that has already been said (because I
have been away), I will give my two euro-cents.
I remember a discussion at the Haskell mailing list about
the possibility of creating a n
Folks
Following a good deal of email I now propose to
DO NOTHING
to the rules defining do-notation in the Haskell 98 Report.
That means that GHC and Hugs, and nhc perhaps, should
change so that they actually implement the do-notation
translation rule
do {e ; stmts} = e >&
he Report says "use >>" then
implementations
should. So either GHC and Hugs have to change or the Report does.
So the question remains: what would be best for programmers:
A: the predictability that desugaring do-notation
uses only (>>=) and return,
similar to the
one against type checking. That /you/ can get it right
doesn't encourage me to believe that J Random Hacker isn't
going to abuse the facility. It's not as if you couldn't
define >!= and >! for something that's nearly a monad,
hese considerations are the reasons compilers are typically prohibited
from taking advantage of such laws, and why the translation from the
'do' notation should be the obvious one (using '>>').
Best,
Dylan Thurston
msg10610/pgp0.pgp
Description: PGP signature
>> and >>=, would be unreasonable.
Here's the problem. Your argument sounds very similar to the
one against type checking. That /you/ can get it right
doesn't encourage me to believe that J Random Hacker isn't
going to abuse the facility. It's not as if you couldn
>If (as a human reader of a programme) I see
>
>do a <- thing1
>
>
>and I notice (perhaps after some modifications) that a is
>not present in , then I /really/ don't want a
>change to
>
>do thing1
>
On Sat, 30 Mar 2002, Richard Uhtenwoldt wrote:
> The bottom line is a social one: language communities compete fiercely
> for programmers. There is no shortage of languages with open-sourced
> implementations in which James could have written his program. (Er,
> actually James is embedding a DS
>If (as a human reader of a programme) I see
>
>do a <- thing1
>
>
>and I notice (perhaps after some modifications) that a is
>not present in , then I /really/ don't want a
>change to
>
>do thing1
>
>
>to change the meaning of the programme.
That's understandable, just like it's understanda
Here's my short manifesto on ">>" and "do" notation. It is based on the
precedent set with "negate", a precedent that I also support.
">>" should be a member of the "Monad" class, just as "negate" is a
member of the
Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote:
> It shouldn't be syntactic suger but at most an operator which does not belong
> to the monad class. One could define (>>) just as an ordinary function
> instead of a class member.
That sounds to me like the best idea so far.
If (as a human reader of
he latter instead of the former
to realize do expressions. But I would prefer implementations using (>>).
> [...]
> ">>" should no longer be a class function with a default value that can be
> changed; it should be syntactic sugar built into Haskell, like "do"
> notation.
It sh
> Yes, but in that case the specific implementations are required to be
> denotationally equal to the default versions.
Yes, obviously. My only point was that I believe (>>) should remain
a class operation.
/Henrik
--
Henrik Nilsson
Yale University
Department of Computer Science
[EMAIL PROTECT
Ross Paterson wrote:
> Yes, but in that case the specific implementations are required to be
> denotationally equal to the default versions. And surely that was
> the original intention here. Section 6.3.6 of the Report needs an
> additional equation:
>
> m >> k = m >>= \_ -> k
>
> T
On Thu, Mar 28, 2002 at 11:48:25AM -0500, [EMAIL PROTECTED] wrote:
> Incidentally, similar concerns occur in the context of the arrows framework.
> Ross Paterson, in response to a request from us at Yale, recently changed
> some derived arrow combinators into default methods of the arrow classes i
>
> > However, James implies that in his monad (>>) has a different meaning
> > than its usual one, and Haskell 98 allows that because (>>) is one of
> > the class operations (not a good design choice I think). I'm quite
> > reluctant to make the meanin
gt;>) has a different meaning
> than its usual one, and Haskell 98 allows that because (>>) is one of
> the class operations (not a good design choice I think). I'm quite
> reluctant to make the meaning of do-notation dependent on such
> differences.
I disagree. Hugs sh
Simon Peyton-Jones wrote:
> However, James implies that in his monad (>>) has a different meaning
> than its usual one, and Haskell 98 allows that because (>>) is one of
> the class operations (not a good design choice I think). I'm quite
> reluctant to ma
James White has noticed that the draft Haskell 98 report
gives the following translation for do-notation:
do {e}= e
do {e;stmts} = e >> do {stmts}
do {p <- e; stmts} = let ok p = do {stmts}
ok
Sebastien Carlier wrote:
>
> > import Monad
> > ...
> > do y <- liftM unzip m1
>
> Thanks.
>
> I'm constantly amazed by the number of tricks one has
> to know before he can write concise code using the
> do-notation (among other things, I used
Sebastien Carlier wrote:
> Sometimes I need to write code which looks like this:
> >do x <- m1
> > let y = unzip x
> > ... -- never using x anymore
>
> I thinks the following extension to do-notation would be useful:
> >pat <- exp
Sebastien Carlier wrote:
> I'm constantly amazed by the number of tricks one has
> to know before he can write concise code using the
> do-notation [...]
In my experience it is not the do-notation itself, but the mixture
of monadic actions and higher-order functions. But after
> import Monad
> ...
> do y <- liftM unzip m1
Thanks.
I'm constantly amazed by the number of tricks one has
to know before he can write concise code using the
do-notation (among other things, I used to write
"x <- return $ m" instead of "let x = m&quo
Sun, 7 Jan 2001 15:03:07 +0100, Sebastien Carlier <[EMAIL PROTECTED]> pisze:
> Does this extension already exist ?
Yes.
import Monad
...
do y <- liftM unzip m1
--
__("< Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
\__/
^^ SYGNATURA ZASTÊPCZA
QRC
On Sun, 7 Jan 2001, Sebastien Carlier wrote:
>
> Sometimes I need to write code which looks like this:
> >do x <- m1
> > let y = unzip x
> > ... -- never using x anymore
>
> I thinks the following extension to do-notation would be useful:
Sometimes I need to write code which looks like this:
>do x <- m1
> let y = unzip x
> ... -- never using x anymore
I thinks the following extension to do-notation would be useful:
>pat <- exp1 # exp2 ; exp3
would be rewritten as
>exp2 >>=
40 matches
Mail list logo