RE: updating labelled fields

2002-05-10 Thread Simon Peyton-Jones

| So, as it stands the proposal is to add the following pieces of sugar:
| 
|   1)  ({assignments}) becomes  \x-x{assignments}
|   2)  x{as, field =, bs}  becomes  \y-x{as, field = y, bs}
|   3)  x{as, field, bs}becomes  \f-x{as, field = f (field x), bs}

...
 
| Assuming I can ever get my cvs'd copy of ghc to compile 
| (sigh), I would be willing to implement this if there are no 
| objections...

Hal, it's fine for you to modify and distribute your copy of GHC, of
course,
but I'm not yet convinced that Simon and I want to put this change in
the mainstream
GHC.  It's easier to add a feature than to remove it, and GHC already 
arguably suffers from feature-itis.  (Perhaps, though, people will love
your
change and nag us to put it in. The more people that ask the keener we
are
to do something.)

While you are thinking about implementation, don't forget the type
checking
part.  I recall that correct type checking of Haskell records was a bit
harder
than it looked.

Incidentally, I'm working with Tim Shead on a sort of meta-programming
facility (somewhat like a fully-integrated Drift, only typechecked) that
would
let you generate update functions for each field automatically; that
might help towards the same goal.

Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: updating labelled fields

2002-05-09 Thread Hal Daume III

 [SNIP]

 I don't think this is ambigous -- do is a keyword, so no record field update
 can be assumed after it.

Okay, I thought about it some more and I agree.

So, as it stands the proposal is to add the following pieces of sugar:

  1)  ({assignments}) becomes  \x-x{assignments}
  2)  x{as, field =, bs}  becomes  \y-x{as, field = y, bs}
  3)  x{as, field, bs}becomes  \f-x{as, field = f (field x), bs}

So then if we see:

  ({field=})

this gets desugared to

  \x - x{field=}

which gets again desugared to

  \x - \y - x{field = y}

Similarly,

  ({field})

becomes

  \x - x{field}

becomes

  \x - \f - x{field = f (field x)}

The only problem i see with this is that I would probably want the
lambda terms to be in the other order, so, just as you would write:

  apField f x

you would write:

  ({field}) f x

But this is backwards...putting a call to flip in sort of defeats the
purpose.

One thing that could be done would be to rewrite the rules as:

  1)  {field=}  becomes  \y - ({field=y})
  2)  {field}   becomes  \f - ({field $= f})   -- assuming $= exists
  3)  {stuff}   becomes  \x - x{stuff}
where stuff has no dangling = and $= and stuf flike that

If we go this route, I would suggest that instead of just {field} in #2,
we make it {field $=} to keep parallelism with the $= thingy and to make
it clear that we're doing function application.

So, again, 

  {field =}
==   \y - {field=y}  -- rule 1, there's a dangling =
==   \y - \x - x{field=y}   -- rule 3, no dangling things

and similarly:

  {field $=}
==   \f - {field $= f}   -- rule 2, there's a dangling $=
==   \f - \x - x{field $= f}-- rule 3, no dnagling things

I believe this is still amenable to fitting in the syntax without pouncing
on anything.

Assuming I can ever get my cvs'd copy of ghc to compile (sigh), I would be
willing to implement this if there are no objections...

 - Hal





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



Re: updating labelled fields

2002-05-07 Thread Jorge Adriano

On Tuesday 07 May 2002 02:07, John Meacham wrote:
 DrIFT which i am now maintaining can derive such utility functions out
 of the box. just add a {-!deriving: update -} to get update functions
 for every labeled field in a datatype. quite useful, I have not updated
 the web page yet, but the new DrIFT homepage will be at

 http://homer.netmar.com/~john/computer/haskell/DrIFT/

Very nice :)
I'll check it out.

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



updating labelled fields

2002-05-06 Thread Hal Daume III

Hi,

I often create structures like:

data MyData = MyData { foo :: ..., bar :: ...,  }

and most of the time i do one of two things:

  1) read values from the structure, as in:
 let x = (foo myData) in ... 
  2) update values in the structure, as in:
 let myData' = myData { foo = (foo myData)+1 }

Only very rarely (usually only during intializization) do I actually put
values into the structure that *don't* depend on their previous value.  I
end up with expresions like:

... myData { foo = (foo myData) + 1 ;
 bar = (bar myData) ++ bar ;
 ick = (ick myData) ! n ; ... }

I was wondering if there existed any sort of update syntax.  Obviously
not real update, but enough to get rid of the (foo myData) parts of my
epxression which really serve to just clutter up with expression.  Perhaps
something like:

... myData { foo - (+1) ; bar - (++bar) ; ick - (!n) ; ... }

or the like, where x { ... y - e ... } is translated to x { ... y = e
(y x) ... }  (i only use - because that seems to be the default
extension symbol, i guess because we don't want to trample symbols people
might actually use.)

Anyway, does such a thing exist, and, if not, is there any chance it could
exist, or is it just syntactic salt to too many people? :)

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume


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



Re: updating labelled fields

2002-05-06 Thread Jorge Adriano


 I often create structures like:
 data MyData = MyData { foo :: ..., bar :: ...,  }
That makes 2 of us :-)

 and most of the time i do one of two things:
   1) read values from the structure, as in:
  let x = (foo myData) in ...
   2) update values in the structure, as in:
  let myData' = myData { foo = (foo myData)+1 }

1) 
I've used datatypes with labeled fields mostly to pass around implicit values.
If that is your case then there is a way around it.

Declare the datatype as 
 data MyData = MyData { foo_ :: fooType, bar_ :: ...,  }

and then declare
 foo :: (?implicitdata :: MyData)= fooType
 foo = foo_ ?yourdata

So when you work in a contex that depends on some implicit data you can just 
use foo. I've used this *a lot* lately.


2)
Yes. My method now is declaring set and apply functions to every field of my 
data structure.
fooAp f ni=ni{foo=f(foo ni)}
fooSet x = fooAp (const x)



 Only very rarely (usually only during intializization) do I actually put
 values into the structure that *don't* depend on their previous value.  I
 end up with expresions like:

 ... myData { foo = (foo myData) + 1 ;
  bar = (bar myData) ++ bar ;
  ick = (ick myData) ! n ; ... }

Yeap quite ugly isn't it?  :-)


 I was wondering if there existed any sort of update syntax.  Obviously
Nope, not that I know of. 

 not real update, but enough to get rid of the (foo myData) parts of my
 epxression which really serve to just clutter up with expression.  Perhaps
 something like:

 ... myData { foo - (+1) ; bar - (++bar) ; ick - (!n) ; ... }

Yes looks nice, thought about something like that before too.

 or the like, where x { ... y - e ... } is translated to x { ... y = e
 (y x) ... }  (i only use - because that seems to be the default
 extension symbol, i guess because we don't want to trample symbols people
 might actually use.)

Anyway I'd prefer to have some way to 'derive' apply and set functions.
Something like 
 data MyData = MyData { foo :: fooType, bar :: ...,  }
  deriving (Set, Apply)

Using the keyword deriving would probably be a bad idea though :)
The set and apply functions could be derived with a standard postfix or maybe 
prefix... fooAp or apFoo.
Maybe we could introduce sintax to specify it...
 deriving (Set with set, Apply with ap)

I don't know... I'm just brainstorming right now.
Having actual functions is important. I don't think I have to explain why to 
people in this mailing list :-)

 Anyway, does such a thing exist, and, if not, is there any chance it could
 exist, or is it just syntactic salt to too many people? :)
I whish you better luck than I've had so far whenever making posts about this 
same issue ;)

J.A.

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



Re: updating labelled fields

2002-05-06 Thread Hal Daume III

I just fudgeted around in the ghc source code and this doesn't seem to be
a change that would require a lot of work.  Briefly, the changes that
would need to be made would be:

  1) In the parser, change bind so that in addition to 
qname '=' exp
 you can also have
qname 'somefunkysymbol' exp
 And change the return type from (a,b,Bool) to (a,b, Either
 () Bool) and then for the normal case, returh Right False and for the
 update case return Left ().

  2) in the mkRecConstrOrUpdate function, when you have a conid
 applied to an update, make sure there are no Left () guys
 in the list; otoh, if the guy sitting in from of the { is
 an exp, do a map (mkRecUpdate exp) on the list where this
 function is something like:

  mkRecUpdate exp (a,b,Right c) = (a,b,c)
  mkRecUpdate exp (a,b,Left ()) = (a,HsApp b (HsApp (HsVar a) exp),False)
  -- warning, this isn't 100% correct, but it's the basic idea

  3) recompile ghc

I wouldn't at all mind making this addition if I had a sense that it would
actually be accepted and that people weren't going to go crazy over the
syntax.  Would something like - be preferred or something like $=?

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Tue, 7 May 2002, Bryn Humberstone wrote:

 Hi Hal,
 
2) update values in the structure, as in:
   let myData' = myData { foo = (foo myData)+1 }
   
 I do this a lot too, and think it would be lovely to have some sugar for
 it. My original idea for the syntax was something like 
 myData = myData { foo $= (+1),
   bar $= (*2) }
 just because $ is a bit reminiscent of function application. But I'm not
 really fussed; as long as some syntax for it appeared in the language.
 
 -- Bryn
 
 -- 
 Bryn Humberstone
   + Email [EMAIL PROTECTED] 
   + Web   http://bryn.alphalink.com.au/
 


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



Re: updating labelled fields

2002-05-06 Thread David Feuer

On Mon, May 06, 2002, Hal Daume III wrote:
 I wouldn't at all mind making this addition if I had a sense that it would
 actually be accepted and that people weren't going to go crazy over the
 syntax.  Would something like - be preferred or something like $=?
 
  - Hal

Why not $= ?
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: updating labelled fields

2002-05-06 Thread Jorge Adriano

On Monday 06 May 2002 23:28, Hal Daume III wrote:
 I wouldn't at all mind making this addition if I had a sense that it would
 actually be accepted and that people weren't going to go crazy over the
 syntax.  Would something like - be preferred or something like $=?

I'd still prefer having some way to automaticly derive 'apply' functions.
There is already nice syntax for setting a field value and I always end up 
defining 'set' functions to each and every field because I want to pass them 
as arguments. 

Imagine you have an STRef to a labeled datatype, lets call it stdata.  
You want to apply some function g to field foo of that structure.
 modifySTRef (fooAp g) stdata

Changing its value to x
 modifySTRef (fooSet x) stdata

With syntatic sugar only you'd have to read the reference, apply the function 
to the field and then update it. 

IMO, 'set field' and 'apply to field' functions are as usefull as the 'field 
projection' functions that are derived from the definition of the labeled 
datatype. Anyway I agree that it would be nice to have special syntax for 
updates. I'll use it if I have it available. 

On Monday 06 May 2002 23:42, David Feuer wrote:
 Why not $= ?
Yeap very nice in deed. I'd vote for this one.

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: updating labelled fields

2002-05-06 Thread John Meacham

DrIFT which i am now maintaining can derive such utility functions out
of the box. just add a {-!deriving: update -} to get update functions
for every labeled field in a datatype. quite useful, I have not updated
the web page yet, but the new DrIFT homepage will be at

http://homer.netmar.com/~john/computer/haskell/DrIFT/

On Mon, May 06, 2002 at 07:36:30PM +0100, Jorge Adriano wrote:
 Anyway I'd prefer to have some way to 'derive' apply and set functions.
 Something like 
  data MyData = MyData { foo :: fooType, bar :: ...,  }
   deriving (Set, Apply)
 
 Using the keyword deriving would probably be a bad idea though :)
 The set and apply functions could be derived with a standard postfix or maybe 
 prefix... fooAp or apFoo.
 Maybe we could introduce sintax to specify it...
  deriving (Set with set, Apply with ap)
 
 I don't know... I'm just brainstorming right now.
 Having actual functions is important. I don't think I have to explain why to 
 people in this mailing list :-)
 
  Anyway, does such a thing exist, and, if not, is there any chance it could
  exist, or is it just syntactic salt to too many people? :)
 I whish you better luck than I've had so far whenever making posts about this 
 same issue ;)
 

-- 
---
John Meacham - California Institute of Technology, Alum. - [EMAIL PROTECTED]
---
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell