Re: [Haskell] Extensible records: Static duck typing

2008-02-10 Thread Jason Dusek
On Feb 5, 2008 2:28 AM, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 this principle allows to build programs in quick and easy way: we just
 add to objects implementations of all the methods required:

 e = new Entry {label := Hi,
color := blue,
getValue := getEntryValue,
setValue := setEntryValue}

 e.display  -- uses color/label properties
 e.saveToFile   -- uses getValue property

I'm new to all this -- I can't figure out why we want to put
methods inside of records. Why don't we define a module instead?

module EntryModule where

data Entry = Entry String Color

display (Entry s c) = do someIOMagic

saveToFile (Entry s c) = do someOtherIOMagic

If we want a more generic approach -- where a function excepts
one of many kinds of data -- than is a type class not suitable?

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-10 Thread Jason Dusek
On Feb 5, 2008 4:24 AM, John Meacham [EMAIL PROTECTED] wrote:
 now when it came to record selection I was deciding between a couple.

   ...snip.../

 ...declare that any identifier that _begins_ with ' always
 refers to a label selection function

 'x point

Say we go with 'x and allow it to pick the x field out of
records. All records. Then we have implicitly defined a function
'x that accepts things in the HasAnX class. This class is also
implicitly defined -- and things are added to it implicitly,
too, by giving them an x.

So, in a way, this is cool -- it's like structs but way less
verbose. On the other hand, it seems awfully like something that
could be handled as a templating thing. Since we already have
templates, couldn't we just add a few default ones to GHC and be
done with it?

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-08 Thread John Meacham
On Tue, Feb 05, 2008 at 08:01:07AM -0500, Cale Gibbard wrote:
 I also like this idea. Retaining the ability to treat selection as a
 function easily is quite important, and this meets that criterion
 nicely. Also, in which case does this cause a program to break? It
 seems that you're only reinterpreting what would be unterminated
 character literals.

Ah, you are right. for some reason I was thinking we allowed identifiers
to start with ', but yeah. this seems fully backwards compatable. while
we are at it, we should allow ' in infix operators to.

a *' b = almostMultiply a b

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Extensible records: Static duck typing

2008-02-08 Thread Dan Weston

Ouch. How would a human parse [apple'*'pear]

If this doesn't immediately scan as [ (*') (apple') (pear) ] to you (it 
doesn't to me) then maybe allowing ' in infix operators may not be the 
best thing.


John Meacham wrote:

On Tue, Feb 05, 2008 at 08:01:07AM -0500, Cale Gibbard wrote:

I also like this idea. Retaining the ability to treat selection as a
function easily is quite important, and this meets that criterion
nicely. Also, in which case does this cause a program to break? It
seems that you're only reinterpreting what would be unterminated
character literals.


Ah, you are right. for some reason I was thinking we allowed identifiers
to start with ', but yeah. this seems fully backwards compatable. while
we are at it, we should allow ' in infix operators to.

a *' b = almostMultiply a b

John




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


Re: [Haskell] Extensible records: Static duck typing

2008-02-08 Thread Jonathan Cast

On 8 Feb 2008, at 4:43 PM, Dan Weston wrote:


Ouch. How would a human parse [apple'*'pear]


In this context, `parse error, tricky syntax'.

In general?  Not as sure.

jcc

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-08 Thread John Meacham
On Fri, Feb 08, 2008 at 04:43:43PM -0800, Dan Weston wrote:
 Ouch. How would a human parse [apple'*'pear]

 If this doesn't immediately scan as [ (*') (apple') (pear) ] to you (it 
 doesn't to me) then maybe allowing ' in infix operators may not be the best 
 thing.

Oh, I was thinking they would only be allowed at the end of infix
expressions, I'd even restrict them to the end of regular identifiers
too actually if it didn't break backwards compatability. that would make
everything unambiguous to parse. Id's like Id's are cute, but I do a
double take every time I try to parse one with my brain :). 

 John



 John Meacham wrote:
 On Tue, Feb 05, 2008 at 08:01:07AM -0500, Cale Gibbard wrote:
 I also like this idea. Retaining the ability to treat selection as a
 function easily is quite important, and this meets that criterion
 nicely. Also, in which case does this cause a program to break? It
 seems that you're only reinterpreting what would be unterminated
 character literals.

 Ah, you are right. for some reason I was thinking we allowed identifiers
 to start with ', but yeah. this seems fully backwards compatable. while
 we are at it, we should allow ' in infix operators to.

 a *' b = almostMultiply a b

 John



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


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Extensible records: Static duck typing

2008-02-08 Thread Brandon S. Allbery KF8NH

[hm.  should this discussion move to -cafe?]

On Feb 8, 2008, at 20:15 , Jonathan Cast wrote:


On 8 Feb 2008, at 4:43 PM, Dan Weston wrote:


Ouch. How would a human parse [apple'*'pear]


In this context, `parse error, tricky syntax'.


I kinda have that problem anyway given ' being permitted in  
identifiers at all.  Given that I expect it now, the above isn't a  
whole lot worse (I've already parsed (token apple') when I hit the  
(token *'), the only question is whether the extension in use  
attaches the ' to the operator or to the following identifier.


(Although I would assume the latter if I ran into it without prior  
knowledge, based on ' normally being a word-identifier character when  
it can't be a Char literal.)


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


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


RE: [Haskell] Extensible records: Static duck typing

2008-02-06 Thread Simon Peyton-Jones

This sort of disagreement means that nothing gets done. After my
experience with the wiki page, I don't believe anything will get done
until one of the core ghc developers makes some arbitrary decisions
and implements whatever they want to, which will then eventually
become part of the standard by default.


This is the sort of situation where a benign dictator is needed. I have no 
strong feelings about which of all of these (all very good) proposals get 
implemented, but I do have a strong opinion that the lack of proper records 
is hurting Haskell quite a bit.

Any of them will do, just get it in there! I'm assuming that Simon {PJ,M} et 
al. won't make an obviously terrible choice, and GHC seems to be the de facto 
standard anyway, so if they just implemented something in GHC that would be 
good enough for me, and a shoe-in for a future standard.

Since you are taking my name in vain, I had better respond!  I wish I felt as 
confident of my good taste as you do. My last attempt to implement records 
(with Umut Acar, more or less the design in the proposal for records paper) 
involved rather significant changes to the type checker, and I was reluctant to 
commit to them without stronger evidence that it was a good design.

I'm not so despondent about the Wiki page. It's already a good start.  Don't 
give up too soon!

You say that lack of proper records is hurting Haskell.   I think it'd help 
to give much more structure to that statement.  proper records means 
different things to different people.   After all Haskell already has somethng 
you can call records but they obviously aren't proper for you.

So it might be interesting to do several things.

1.  List the interested parties.  The Wiki page doesn't say who's interested in 
this so it's hard to judge whether the hurting is a widely held opinion or 
not.

2. List the possible features that records might mean.  For example:

* Anonymous records as a type.  So {x::Int, y::Bool} is a type.  (In 
Haskell as it stands, records are always associated with a named data type.

* Polymorphic field access.  r.x accesses a field in any record with 
field x, not just one record type.

* Polymorphic extension

* Record concatenation

* Are labels first-class?

* etc
Give examples of why each is useful.   Simply writing down these features in a 
clear way would be a useful exercise.  Probably some are must have for some 
people, but others might be optional.

3.  Cross-tabulate, for each of the current proposals, say which features they 
have.

4. Reflect on how invasive each proposal would be, given the existence of type 
functions.


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


RE: [Haskell] Extensible records: Static duck typing

2008-02-06 Thread Simon Peyton-Jones
So to clarify that statement. Honestly the number one problem I have with the 
current records system is that labels share the same namespace. This makes 
interfacing with any C library using structs quite painful. This is why I say 
that I don't really care which gets implemented. The current system is 
*painful* IMO, so anything which improves on it would be welcome (even if just 
puts the record accessors in a per-record namespace, where with syntactic sugar 
to avoid having to qualify it).

You do know about: 
http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#disambiguate-fields
don't you?

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-06 Thread Sebastian Sylvan
On Feb 6, 2008 11:33 AM, Simon Peyton-Jones [EMAIL PROTECTED] wrote:



 This sort of disagreement means that nothing gets done. After my
 experience with the wiki page, I don't believe anything will get done
 until one of the core ghc developers makes some arbitrary decisions
 and implements whatever they want to, which will then eventually
 become part of the standard by default.




 This is the sort of situation where a benign dictator is needed. I have
 no strong feelings about which of all of these (all very good) proposals get
 implemented, but I do have a strong opinion that the lack of proper
 records is hurting Haskell quite a bit.



 Any of them will do, just get it in there! I'm assuming that Simon {PJ,M}
 et al. won't make an obviously terrible choice, and GHC seems to be the de
 facto standard anyway, so if they just implemented something in GHC that
 would be good enough for me, and a shoe-in for a future standard.



 Since you are taking my name in vain, I had better respond!  I wish I felt
 as confident of my good taste as you do. My last attempt to implement
 records (with Umut Acar, more or less the design in the proposal for
 records paper) involved rather significant changes to the type checker, and
 I was reluctant to commit to them without stronger evidence that it was a
 good design.



 I'm not so despondent about the Wiki page. It's already a good start.
 Don't give up too soon!



 You say that lack of proper records is hurting Haskell.   I think it'd
 help to give much more structure to that statement.  proper records means
 different things to different people.   After all Haskell already has
 somethng you can call records but they obviously aren't proper for you.




So to clarify that statement. Honestly the number one problem I have with
the current records system is that labels share the same namespace. This
makes interfacing with any C library using structs quite painful. This is
why I say that I don't really care which gets implemented. The current
system is *painful* IMO, so anything which improves on it would be welcome
(even if just puts the record accessors in a per-record namespace, where
with syntactic sugar to avoid having to qualify it).

Now, I do think that if we're going to remedy that situation, we might as
well take the opportunity to make them lightweight (i.e. not require a data
type), with polymorphic fields etc, but those all of those things are
distant second priority to the one showstopper for the current records,
IMO.
Sebastian
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Extensible records: Static duck typing

2008-02-06 Thread Sebastian Sylvan
On Feb 6, 2008 12:19 PM, Simon Peyton-Jones [EMAIL PROTECTED] wrote:

So to clarify that statement. Honestly the number one problem I have
 with the current records system is that labels share the same namespace.
 This makes interfacing with any C library using structs quite painful. This
 is why I say that I don't really care which gets implemented. The current
 system is *painful* IMO, so anything which improves on it would be welcome
 (even if just puts the record accessors in a per-record namespace, where
 with syntactic sugar to avoid having to qualify it).



 You do know about:
 http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#disambiguate-fields

 don't you?


I did not! This is great and takes care of my immediate concerns.
I do still think that all that other stuff is worthwhile, particularly I
like the low overhead of using tuples, and wouldn't mind if records were
similarly convenient.



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


Re: [Haskell] Extensible records: Static duck typing

2008-02-06 Thread Barney Hilken

2. List the possible features that “records” might mean.  For example:

· Anonymous records as a type.  So {x::Int, y::Bool} is a  
type.  (In Haskell as it stands, records are always associated with  
a named data type.


· Polymorphic field access.  r.x accesses a field in any  
record with field x, not just one record type.


· Polymorphic extension

· Record concatenation

· Are labels first-class?

· etc

Give examples of why each is useful.   Simply writing down these  
features in a clear way would be a useful exercise.  Probably some  
are “must have” for some people, but others might be optional.


This is what I was trying to do with the wiki page. I stopped because  
the only other contributor decided he could no longer contribute, and  
I felt I was talking to myself. If we want to be rational about the  
design, we need real examples to demonstrate what is genuinely useful,  
and I don't have that many of them.


Barney.

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


[Haskell-cafe] Re: [Haskell] Extensible records: Static duck typing

2008-02-06 Thread Tim Chevalier
[redirecting to haskell-cafe]
On 2/6/08, Barney Hilken [EMAIL PROTECTED] wrote:
 This is what I was trying to do with the wiki page. I stopped because
 the only other contributor decided he could no longer contribute, and
 I felt I was talking to myself. If we want to be rational about the
 design, we need real examples to demonstrate what is genuinely useful,
 and I don't have that many of them.

It's obvious that records are a language feature that people besides
just you care about. And so everybody would benefit from your effort
if you chose to continue adding more examples to the wiki page.

Records clearly seem to be an important issue if so many people have
replied to your thread, and your comment expressing frustration at
arbitrary decisions getting made about design seems to suggest you
have some passion about the issue. On the other hand, if you can't
think of real examples offhand, and no one else can either, maybe it's
not that important... (Examples don't have to be very complicated to
be useful, by the way. Simpler is better.)

Cheers,
Tim

-- 
Tim Chevalier * http://cs.pdx.edu/~tjc * Often in error, never in doubt
If pots couldn't call kettles black, there'd be a lot less talking
going on.  -- Larissa Ranbom
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Extensible records: Static duck typing

2008-02-05 Thread Cale Gibbard
On 05/02/2008, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 saveToFile x = writeToFile data (show x.getValue)

Heh, I had to read this a couple times to figure out that it wasn't
just a blatant type error, and that (.) there doesn't mean function
composition. :)

On the matter of extensible records, I really like the semantics of
Daan Leijen's proposal here:
http://research.microsoft.com/users/daan/download/papers/scopedlabels.pdf

However, the syntax could use some work. Using (.) as a record
selector is out of the question. Personally, I think pt{x} for
extracting the x field of pt seems not-so-unreasonable, and meshes
well with the existing syntax for record updates.

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


[Haskell] Extensible records: Static duck typing

2008-02-05 Thread Bulat Ziganshin
Hello haskell,

the principle of duck typing used in dynamic OOP languages such as
Ruby and Python, is simple: if some object supports Quack method, then
it can be passed to any routine that expects an object of some Duck type

this principle allows to build programs in quick and easy way: we just
add to objects implementations of all the methods required:

e = new Entry {label := Hi,
   color := blue,
   getValue := getEntryValue,
   setValue := setEntryValue}

e.display  -- uses color/label properties
e.saveToFile   -- uses getValue property

of course, drawback of duck typing that when we forgot to setup some
field, this will be detected only at runtime - as usual for dynamic
typing


Haskell can provide benefits of both static and duck typing with type
inference by means of extensible records. type of 'e' in this case
will be {Entry | getValue::IO String, setValue::String-IO()}, i.e.
Entry record type extended with getValue/setValue fields.

serialization function may look like this:

saveToFile x = writeToFile data (show x.getValue)

and its implementation infers its type:

saveToFile :: {...| getValue::(Show a) = a-IO() } - IO ()

where {...| getValue::a} means any record type which includes getValue
field of type a.

type of our 'e' conforms to this type signature, so `e` can be passed
to saveToFile in safe manner and this is completely checked at compile
time without any explicitly written type signatures


this becomes even more important when we want to create objects
belonging to more than one object hierarchy. by requiring that each
possible property should be explicitly declared, we may ensure that
properties used in different modules can't be mixed up:

module A:  property getValue
module B:  property getValue
module C:  import A; import B -- conflict: from where getValue should be 
imported?


it may be interesting to compare extensible records with OOP and type
classes approaches - it seems that e.r. is just like type class instances
created at the place and linked to the concrete object rather than
whole type


so, implementation of extensible records in haskell compilers would
allow to

1) give us simple, natural way to make bindings to various OOP
libraries. i've seen bindings in gtk2hs/wxHaskell and now they use a
lot of type hackery

2) compete with dynamic OOP languages in the areas of scripting, fast
prototyping, web programming and even make possible to use the same
techniques in larger apps, again increasing programmers productivity


also, extensible records may be useful for merging haskell into jvm/.net
world - as a way to provide haskell access to their OOP libs


ps: there are many papers on adding extensible records to Haskell, in particular
you can read http://research.microsoft.com/Users/simonpj/Papers/recpro.ps.gz

-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-05 Thread Cale Gibbard
On 05/02/2008, Barney Hilken [EMAIL PROTECTED] wrote:

 Should {label := Hi, color := blue} and {color := blue, label :=
 Hi} have the same type?


The scoped labels paper has an interesting feature in this regard:
labels with different names can be swapped at will, but labels having
the same name (which is allowed) maintain their order. The types are
equivalent in either case though.

This is part of the general means by which the system avoids the need
for lacks-predicates, and as a bonus, allows each field name of a
record to act a bit like a stack.

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-05 Thread Cale Gibbard
On 05/02/2008, Cale Gibbard [EMAIL PROTECTED] wrote:
 Personally, I think pt{x} for extracting the x field of pt seems 
 not-so-unreasonable, and meshes
 well with the existing syntax for record updates.

I should clarify -- this is only if we can't somehow keep the existing
function syntax for record extraction.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Extensible records: Static duck typing

2008-02-05 Thread Barney Hilken
Everyone wants to add extensible records to Haskell. The problem is  
that, in a formally defined language like Haskell, we need to agree  
how they should behave, and there are too many conflicting ideas.


I was involved recently in an attempt to try to sort out some of the  
alternatives (recorded here: http://hackage.haskell.org/trac/ghc/wiki/ExtensibleRecords) 
 which collapsed because of argument over a fundamental question:


	Should {label := Hi, color := blue} and {color := blue, label :=  
Hi} have the same type?


One of the main contributors felt that the answer was no (because it  
allows more different records to be represented, and makes  
implementation simpler), and that we should say so. I felt that most  
people would consider that the answer was yes, and that we shouldn't  
make such a fundamental design decision without some evidence about  
what is best in practice.


The result was that our attempt to sort things out stopped.

This sort of disagreement means that nothing gets done. After my  
experience with the wiki page, I don't believe anything will get done  
until one of the core ghc developers makes some arbitrary decisions  
and implements whatever they want to, which will then eventually  
become part of the standard by default.


Barney.

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-05 Thread Barney Hilken




The scoped labels paper has an interesting feature in this regard:
labels with different names can be swapped at will, but labels having
the same name (which is allowed) maintain their order.

- Cale


Yes, I know. The problem is that there are TOO MANY proposals, and  
they are all fundamentally incompatible. The scoped labels idea is  
interesting, but is it useful? No-one has written enough code with ANY  
of the proposals to say what their strengths and weaknesses are.


Barney.

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-05 Thread Johannes Waldmann

 Everyone wants to add extensible records to Haskell. 

well ... sure records are better than tuples ...
but interfaces (uh, classes) are still better IMHO

but anyway, is it possible to steal the
design of C#'s anonymous types (classes)?

if not, then why? (this might help
to clarify what we want, or not).

best regards, J.W.

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-05 Thread Sebastian Sylvan
On Feb 5, 2008 11:08 AM, Barney Hilken [EMAIL PROTECTED] wrote:


 This sort of disagreement means that nothing gets done. After my
 experience with the wiki page, I don't believe anything will get done
 until one of the core ghc developers makes some arbitrary decisions
 and implements whatever they want to, which will then eventually
 become part of the standard by default.



This is the sort of situation where a benign dictator is needed. I have no
strong feelings about which of all of these (all very good) proposals get
implemented, but I do have a strong opinion that the lack of proper
records is hurting Haskell quite a bit.

Any of them will do, just get it in there! I'm assuming that Simon {PJ,M} et
al. won't make an obviously terrible choice, and GHC seems to be the de
facto standard anyway, so if they just implemented something in GHC that
would be good enough for me, and a shoe-in for a future standard.
On 05/02/2008, Cale Gibbard [EMAIL PROTECTED] wrote:

 On 05/02/2008, Cale Gibbard [EMAIL PROTECTED] wrote:
  Personally, I think pt{x} for extracting the x field of pt seems
 not-so-unreasonable, and meshes
  well with the existing syntax for record updates.

 I should clarify -- this is only if we can't somehow keep the existing
 function syntax for record extraction.


Only if they get a separate namespace for each record, rather than
overlapping, which would probably be confusing as they would *look* like
functions, but they wouldn't really be function... That said, I like the
record{field} syntax. It's sort of like array accessors in C style
languages, but follows the flavour of the rest of the record syntax. I
like the dot better, though, but I agree that it's too overloaded as it is.

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-05 Thread John Meacham
On Tue, Feb 05, 2008 at 05:57:24AM -0500, Cale Gibbard wrote:
 On 05/02/2008, Bulat Ziganshin [EMAIL PROTECTED] wrote:
  saveToFile x = writeToFile data (show x.getValue)
 
 Heh, I had to read this a couple times to figure out that it wasn't
 just a blatant type error, and that (.) there doesn't mean function
 composition. :)
 
 On the matter of extensible records, I really like the semantics of
 Daan Leijen's proposal here:
 http://research.microsoft.com/users/daan/download/papers/scopedlabels.pdf
 
 However, the syntax could use some work. Using (.) as a record
 selector is out of the question. Personally, I think pt{x} for
 extracting the x field of pt seems not-so-unreasonable, and meshes
 well with the existing syntax for record updates.

The backwards compatable (and more clean conceptually IMHO) syntax I
came up with for implementing the scoped labels proposal for jhc (sadly,
not complete) was something like:

new record (x = 3,y = 4)
subtraction \r - ( x = 3 | r - x)
replacement \r - (x := 3 | r) (equivalent to the above) 
type (x::Int,y::Char)

degenerate cases:
empty record (|)
subtracting a label (| r - x)

a record can always be determined by the presence of a '|' within
parenthesis.

note that these are unambigious because '=' and '|' are both reserved
characters and cannot appear in parenthesis is this position otherwise.

now when it came to record selection I was deciding between a couple.

choice 1: use '.' as the current proposal suggests, but only when there
is no space around it.

choice 2: use ', declare that any identifier that _begins_ with ' always
refers to a label selection function

'x point

choice 3: use '#'.

none are fully backwards compatable. I am still not sure which I like
the best, ' has a lot of appeal to me as it is very simple to type and
lightweight visually.


note that instead of {} we use parens, the reason is that scoped labels
have much more in common with tuples than the current labeld field
mechanism so parens are a much more natural choice. you can think of
tuples as 'anonymous positional data types' and records as 'anonymous
labeled data types'. when thought about that way, parenthesis make a lot
more sense.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Extensible records: Static duck typing

2008-02-05 Thread Cale Gibbard
On 05/02/2008, John Meacham [EMAIL PROTECTED] wrote:

 choice 2: use ', declare that any identifier that _begins_ with ' always
 refers to a label selection function

 'x point

 (snip)

 none are fully backwards compatible. I am still not sure which I like
 the best, ' has a lot of appeal to me as it is very simple to type and
 lightweight visually.

I also like this idea. Retaining the ability to treat selection as a
function easily is quite important, and this meets that criterion
nicely. Also, in which case does this cause a program to break? It
seems that you're only reinterpreting what would be unterminated
character literals.

Did you consider any options with regard to the syntax for variants as
introduced in the paper? Perhaps something like (: and  :) brackets
could be used in place of the \langle and \rangle brackets used in the
paper. Labels would still start with single quotes. We wouldn't need
the decomposition syntax, just case, altered to agree with Haskell's
existing syntax for case. Pattern matching against labels (whose names
start with a single quote) unambiguously makes it clear that we're
working with variants.

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


Re: [Haskell] Extensible records: Static duck typing

2008-02-05 Thread Barney Hilken

new record (x = 3,y = 4)
subtraction \r - ( x = 3 | r - x)
replacement \r - (x := 3 | r) (equivalent to the above)
type (x::Int,y::Char)

degenerate cases:
empty record (|)
subtracting a label (| r - x)

a record can always be determined by the presence of a '|' within
parenthesis.



One of the advantages of the systems with richer polymorphism and more  
predicates is that they need less syntax. It is possible (once you  
have solved the permutation/scoping problem) to use constructors as  
labels, and define all the basic operators on records as standard  
Haskell functions. With this approach you can even treat labels as  
first-class citizens and write polymorphic record zip:


	labelZip :: ({n :: a} `Disjoint` {m :: b}) = n - m - [a] - [b] -  
[{n :: a, m :: b}]

labelZip n m = zipWith (\x y - {n := x, m := y})

But no-one knows whether this extra expressive power has an  
unacceptable cost in terms of extra complexity, because no-one has  
implemented and used these systems seriously.


Barney.

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