RE: Make it possible to evaluate monadic actions when assigning record fields

2007-07-11 Thread Simon Peyton-Jones
Another alternative (which I got from Greg Morrisett) that I'm toying with is 
this.  It's tiresome to write

do { x - stuff1
   ; y - sutff2
   ; f x y }

In ML I'd write simply

f stuff1 stuff2

So Greg's idea (or at least my understanding thereof) is to write it like this:

do { f $(stuff1) $(stuff2) }

The idea is that a splice $e must be lexically enclosed by a 'do', with no 
intervening lambda.  It's desugared to the code above; that is, each splice it 
pulled out, in lexically left-right order, and given a name, which replaces the 
splice.

Of course it doesn't have to look like the above; the rule applies to any do:

do { v - this; foo $(h v); y - f $(t v v); ...etc }

The linearise the splices rule is quite general.

Don't burn any cycles on concrete syntax; I know the $ notation is used for 
Template Haskell; one would need to think of a good syntax.  But the idea is to 
make it more convenient to write programs that make effectful calls, and then 
use the result exactly once.

Anyway, this'd do what the original proposer wanted, but in a much more general 
way.

Just a thought -- I have not implemented this.

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Adde
| Sent: 10 July 2007 21:40
| To: [EMAIL PROTECTED]
| Cc: haskell-prime@haskell.org
| Subject: Re: Make it possible to evaluate monadic actions when assigning 
record fields
|
| On Tue, 2007-07-10 at 17:04 +, [EMAIL PROTECTED] wrote:
|  Isaac Dupree [EMAIL PROTECTED] wrote:
|   
|Adde wrote:
|  tmp - foo
|  return Bar {
|barFoo = tmp
|  }
|   
|There is a feature being worked on in GHC HEAD that would let you do
|   
|  do
|   tmp - foo
|   return Bar{..}
|   
|which captures fields from everything of the same name that's in scope.
|  I think this would also satisfy your desire.
|   
| 
|  I guess this means I could write:
| 
| 
|  data D = C {field1 :: Bool, field2 :: Char}
| 
|  f x = do
|field1 - foo1
|field2 - foo2
|field3 - foo3
|other stuff
|return C{..}
| 
| 
|  instead of
| 
| 
|  f x = do
|tmp1 - foo1
|tmp2 - foo2
|field3 - foo3
|other stuff
|return $ C { field1 = tmp1, field2 = tmp2 }
| 
| 
|  This has a dangerous feel to it ---
|  extending the definition of D to include a field field3
|  may have quite unintended consequences.
| 
| 
|  What I am missing most in the record arena
|  is a functional notation for record update, for example:
| 
|  {^ field1 }  =  \ f r - r {field1 = f (field1 r)}
|
| I agree, capturing variables without asking is just scary.
| While I'm pretty biased I still think my suggestion solves the problem
| in a cleaner, more consistent way.
|
| /Adde
|
| ___
| Haskell-prime mailing list
| Haskell-prime@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-prime
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Make it possible to evaluate monadic actions when assigning record fields

2007-07-11 Thread Wouter Swierstra


On 11 Jul 2007, at 08:38, Simon Peyton-Jones wrote:

Another alternative (which I got from Greg Morrisett) that I'm  
toying with is this.  It's tiresome to write


do { x - stuff1
   ; y - sutff2
   ; f x y }

In ML I'd write simply

f stuff1 stuff2


Using Control.Applicative you could already write:

f $ x * y

I don't see the immediate need for more syntactic sugar - this is  
about as concise as it can get and it does not require compiler  
extensions.


All the best,

  Wouter

This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

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


Re: Make it possible to evaluate monadic actions when assigning record fields

2007-07-11 Thread apfelmus
Wouter Swierstra wrote:
 
 On 11 Jul 2007, at 08:38, Simon Peyton-Jones wrote:
 
 Another alternative (which I got from Greg Morrisett) that I'm toying
 with is this.  It's tiresome to write

 do { x - stuff1
; y - sutff2
; f x y }

 In ML I'd write simply

 f stuff1 stuff2
 
 Using Control.Applicative you could already write:
 
 f $ x * y

No, since f is not a pure function, it's f :: x - y - m c. The correct
form would be

  join $ f $ x * y

(Why doesn't haddock document infix precedences?) But maybe some
type-class hackery can be used to eliminate the join.

In any case, I'm *strongly against* further syntactic sugar for monads,
including #1518. The more tiresome monads are, the more incentive you
have to avoid them.

Regards,
apfelmus

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


Re[2]: Make it possible to evaluate monadic actions when assigning record fields

2007-07-11 Thread Bulat Ziganshin
Hello Simon,

Wednesday, July 11, 2007, 11:38:31 AM, you wrote:

 So Greg's idea (or at least my understanding thereof) is to write it like 
 this:

 do { f $(stuff1) $(stuff2) }

Simon, it is thing i dreamed for a years! Haskell has serious drawback
for imperative programming compared to C - each action should be
written as separate statement and this makes program too wordy - just
try to rewrite something like x[i] += y[i]*z[i] in Haskell

i need a way to perform actions and read data values inside
calculations. there are two possible ways:

* write pure expressions like we do in C and let's ghc guess yourself
where evaluation should be added:

x - newIORef 1
y - newIORef 1
z - newIORef 1
f x (y*z)

this means that any expression of type IORef a or IO a automatically
translated into evaluation. the same should work for arrays, hashes
and so on, so it probably should be a class. the problem, of course, is
that IO/IORef/.. is a first class values so it's hard to distinguish
where it should be evaluated and where used as is. another problem is
its interaction with type inference - we may not know which concrete
type this expression has


* add an explicit operation which evaluates data, as you suggests.
again, it should be a class which allows to add evaluation support for
hashes/...

actually, ML has something similar - it uses . operation to evaluate
variable values


=
and, while we on this topic, another problem for imperative
programming style usability is control structures. how we can rewrite
the following:

delta=1000
while (delta0.01)
  x = ...
  if (x0) break
  delta = abs(n-x*x)

=
btw, proposal of prefix expressions also simplifies imperative
programs a bit: now we should write something like this:

when (a0) $ do
  .

while this proposal allows to omit $ and make program look a bit more
natural

=
one more complaint: the syntax

for list $ \item - do
  

doesn't look too natural compared to other languages. it will be great to
write it as
  
for item in list do
  

- of course, with 'for' still a plain function defined by user


=
may be, i should collect all these ideas on imperative programming
page?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Make it possible to evaluate monadic actions when assigning record fields

2007-07-11 Thread Donald Bruce Stewart
ctm:
 Indeed it can. Ignoring conventional wisdom about dirty linen, here are
 idiom brackets
 
  class Applicative i = Idiomatic i f g | g - f i where
idiomatic :: i f - g
 
  iI :: Idiomatic i f g = f - g
  iI = idiomatic . pure
 
  data Ii  =  Ii
 
  instance Applicative i= Idiomatic i x (Ii - i x) where
idiomatic xi Ii = xi
  instance Idiomatic i f g  = Idiomatic i (s - f) (i s - g) where
idiomatic sfi si= idiomatic (sfi * si)
 
 So that
 
   iI f x y Ii = f $ x * y
 
 Now add
 
  data Ji = Ji
 
  instance (Monad i, Applicative i)= Idiomatic i (i x) (Ji - i  
 x) where
idiomatic xii Ji = join xii
 
 and you've got
 
   iI f x y Ji = join $ f $ x * y

Very nice! Just so we don't forget this, I created a wiki page,

http://haskell.org/haskellwiki/Idiom_brackets

-- Don
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Make it possible to evaluate monadic actions when assigning record fields

2007-07-11 Thread Adde
Monads are a part of Haskell. The more tiresome monads are to use, the
more tiresome Haskell is to use. I suggest we leave the decision of
where and when to use them to each individual user of the language.

/Adde

 In any case, I'm *strongly against* further syntactic sugar for
 monads,
 including #1518. The more tiresome monads are, the more incentive you
 have to avoid them.
 
 Regards,
 apfelmus

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