Re: A possible alternative to dot notation for record access

2013-07-11 Thread Mike Ledger
6 even:

foo :: (Maybe :: * -> *) Foo -> Bar
foo (fromMaybe def -> x) = \x -> case x of
Foo x -> x->y->z

On Mon, Jul 1, 2013 at 4:27 PM, John Wiegley  wrote:

> > Edward Kmett  writes:
>
> > If you really want to hunt for unused syntax and we wind up needing a (.)
> > analogue then (->) is currently a reserved operator, so opening it up for
> > use at the term level could be made to work, and there is a precedent
> with
> > c/c++ pointer dereferencing.
>
> Imagine this possible code:
>
> foo :: Maybe Foo -> Bar
> foo (fromMaybe def -> x) = \x -> case x of
> Foo x -> x->y->z
>
> I think it might get a bit ugly to give it a 5th meaning.
>
> --
> John Wiegley
> FP Complete Haskell tools, training and consulting
> http://fpcomplete.com   johnw on #haskell/irc.freenode.net
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A possible alternative to dot notation for record access

2013-07-01 Thread Edward A Kmett
Sure. I'd rather have nothing, but at least unlike the (.) proposals it doesn't 
break existing code.

That said I don't think we need either.

On Jul 1, 2013, at 2:27 AM, "John Wiegley"  wrote:

>> Edward Kmett  writes:
> 
>> If you really want to hunt for unused syntax and we wind up needing a (.)
>> analogue then (->) is currently a reserved operator, so opening it up for
>> use at the term level could be made to work, and there is a precedent with
>> c/c++ pointer dereferencing.
> 
> Imagine this possible code:
> 
>foo :: Maybe Foo -> Bar
>foo (fromMaybe def -> x) = \x -> case x of
>Foo x -> x->y->z
> 
> I think it might get a bit ugly to give it a 5th meaning.
> 
> -- 
> John Wiegley
> FP Complete Haskell tools, training and consulting
> http://fpcomplete.com   johnw on #haskell/irc.freenode.net
> 
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A possible alternative to dot notation for record access

2013-06-30 Thread John Wiegley
> Edward Kmett  writes:

> If you really want to hunt for unused syntax and we wind up needing a (.)
> analogue then (->) is currently a reserved operator, so opening it up for
> use at the term level could be made to work, and there is a precedent with
> c/c++ pointer dereferencing.

Imagine this possible code:

foo :: Maybe Foo -> Bar
foo (fromMaybe def -> x) = \x -> case x of
Foo x -> x->y->z

I think it might get a bit ugly to give it a 5th meaning.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A possible alternative to dot notation for record access

2013-06-30 Thread Edward Kmett
If you really want to hunt for unused syntax and we wind up needing a (.)
analogue then (->) is currently a reserved operator, so opening it up for
use at the term level could be made to work, and there is a precedent with
c/c++ pointer dereferencing.

-Edward

On Mon, Jul 1, 2013 at 1:10 AM, Edward Kmett  wrote:

> (#) is a legal operator today and is used in a number of libraries.
>
>
> On Sun, Jun 30, 2013 at 11:38 PM,  wrote:
>
>> As long as we're bikeshedding...
>>
>> Possibly '#' is unused syntax -- Erlang uses it for its records too, so
>> we wouldn't be pulling it out of thin air. E.g. "person#firstName"
>>
>> Tom
>>
>>
>> El Jun 30, 2013, a las 22:59, AntC 
>> escribió:
>>
>> >> Carter Schonwald  gmail.com> writes:
>> >>
>> >> indeed, this relates / augments record puns syntax already in
>> > GHC http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-
>> > extns.html#record-puns.
>> >
>> > Uh-oh. That documentation gives an example, and it exactly explains the
>> > weird type-level error I got when I tried to use the proposed syntax
>> > myself:
>> >
>> >Note that:
>> >
>> >*   Record punning can also be used in an expression, writing, for
>> > example,
>> >
>> >let a = 1 in C {a}-- !!!
>> >
>> >instead of
>> >
>> >let a = 1 in C {a = a}
>> >
>> >The expansion is purely syntactic, so the expanded right-hand
>> side
>> > expression refers to the nearest enclosing variable that is spelled the
>> > same as the field name.
>> >
>> > IOW the proposal _does_ conflict with existing syntax. (And I guess I
>> can
>> > see a use for the example. Note that outside of that let binding, `a`
>> > would be a field selector function generated from the data decl in which
>> > field `a` appears -- that's the weirdity I got.)
>> >
>> > I suppose the existing syntax has a data constructor in front of the
>> > braces, whereas the proposal wants a term. But of course a data
>> > constructor is a term.
>> >
>> > So the proposal would be a breaking change. Rats! Is anybody using that
>> > feature?
>> >
>> >>
>> >> On Sun, Jun 30, 2013 at 2:59 AM, Judah Jacobson 
>> > gmail.com> wrote:
>> >>
>> >> Unlike dot notation, this is unambiguous and doesn't conflict with any
>> > existing syntax (AFAIK). ...
>> >
>> >
>> > ___
>> > Glasgow-haskell-users mailing list
>> > Glasgow-haskell-users@haskell.org
>> > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>
>> ___
>> Glasgow-haskell-users mailing list
>> Glasgow-haskell-users@haskell.org
>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>
>
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A possible alternative to dot notation for record access

2013-06-30 Thread Edward Kmett
(#) is a legal operator today and is used in a number of libraries.

On Sun, Jun 30, 2013 at 11:38 PM,  wrote:

> As long as we're bikeshedding...
>
> Possibly '#' is unused syntax -- Erlang uses it for its records too, so we
> wouldn't be pulling it out of thin air. E.g. "person#firstName"
>
> Tom
>
>
> El Jun 30, 2013, a las 22:59, AntC 
> escribió:
>
> >> Carter Schonwald  gmail.com> writes:
> >>
> >> indeed, this relates / augments record puns syntax already in
> > GHC http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-
> > extns.html#record-puns.
> >
> > Uh-oh. That documentation gives an example, and it exactly explains the
> > weird type-level error I got when I tried to use the proposed syntax
> > myself:
> >
> >Note that:
> >
> >*   Record punning can also be used in an expression, writing, for
> > example,
> >
> >let a = 1 in C {a}-- !!!
> >
> >instead of
> >
> >let a = 1 in C {a = a}
> >
> >The expansion is purely syntactic, so the expanded right-hand side
> > expression refers to the nearest enclosing variable that is spelled the
> > same as the field name.
> >
> > IOW the proposal _does_ conflict with existing syntax. (And I guess I can
> > see a use for the example. Note that outside of that let binding, `a`
> > would be a field selector function generated from the data decl in which
> > field `a` appears -- that's the weirdity I got.)
> >
> > I suppose the existing syntax has a data constructor in front of the
> > braces, whereas the proposal wants a term. But of course a data
> > constructor is a term.
> >
> > So the proposal would be a breaking change. Rats! Is anybody using that
> > feature?
> >
> >>
> >> On Sun, Jun 30, 2013 at 2:59 AM, Judah Jacobson 
> > gmail.com> wrote:
> >>
> >> Unlike dot notation, this is unambiguous and doesn't conflict with any
> > existing syntax (AFAIK). ...
> >
> >
> > ___
> > Glasgow-haskell-users mailing list
> > Glasgow-haskell-users@haskell.org
> > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A possible alternative to dot notation for record access

2013-06-30 Thread amindfv
As long as we're bikeshedding...

Possibly '#' is unused syntax -- Erlang uses it for its records too, so we 
wouldn't be pulling it out of thin air. E.g. "person#firstName"

Tom


El Jun 30, 2013, a las 22:59, AntC  escribió:

>> Carter Schonwald  gmail.com> writes:
>> 
>> indeed, this relates / augments record puns syntax already in
> GHC http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-
> extns.html#record-puns.
> 
> Uh-oh. That documentation gives an example, and it exactly explains the 
> weird type-level error I got when I tried to use the proposed syntax 
> myself:
> 
>Note that: 
> 
>*   Record punning can also be used in an expression, writing, for 
> example, 
> 
>let a = 1 in C {a}-- !!!
> 
>instead of 
> 
>let a = 1 in C {a = a}
> 
>The expansion is purely syntactic, so the expanded right-hand side 
> expression refers to the nearest enclosing variable that is spelled the 
> same as the field name. 
> 
> IOW the proposal _does_ conflict with existing syntax. (And I guess I can 
> see a use for the example. Note that outside of that let binding, `a` 
> would be a field selector function generated from the data decl in which 
> field `a` appears -- that's the weirdity I got.)
> 
> I suppose the existing syntax has a data constructor in front of the 
> braces, whereas the proposal wants a term. But of course a data 
> constructor is a term. 
> 
> So the proposal would be a breaking change. Rats! Is anybody using that 
> feature?
> 
>> 
>> On Sun, Jun 30, 2013 at 2:59 AM, Judah Jacobson 
> gmail.com> wrote:
>> 
>> Unlike dot notation, this is unambiguous and doesn't conflict with any
> existing syntax (AFAIK). ...
> 
> 
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A possible alternative to dot notation for record access

2013-06-30 Thread AntC
> Carter Schonwald  gmail.com> writes:
> 
> indeed, this relates / augments record puns syntax already in 
GHC http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-
extns.html#record-puns.
> 

Uh-oh. That documentation gives an example, and it exactly explains the 
weird type-level error I got when I tried to use the proposed syntax 
myself:

Note that: 

*   Record punning can also be used in an expression, writing, for 
example, 

let a = 1 in C {a}-- !!!

instead of 

let a = 1 in C {a = a}

The expansion is purely syntactic, so the expanded right-hand side 
expression refers to the nearest enclosing variable that is spelled the 
same as the field name. 

IOW the proposal _does_ conflict with existing syntax. (And I guess I can 
see a use for the example. Note that outside of that let binding, `a` 
would be a field selector function generated from the data decl in which 
field `a` appears -- that's the weirdity I got.)

I suppose the existing syntax has a data constructor in front of the 
braces, whereas the proposal wants a term. But of course a data 
constructor is a term. 

So the proposal would be a breaking change. Rats! Is anybody using that 
feature?

> 
> On Sun, Jun 30, 2013 at 2:59 AM, Judah Jacobson  
gmail.com> wrote:
> 
> Unlike dot notation, this is unambiguous and doesn't conflict with any 
existing syntax (AFAIK). ...


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A possible alternative to dot notation for record access

2013-06-30 Thread Ben Franksen
Judah Jacobson wrote:
> I had a quick idea about record field syntax as specified in the GSoC
> project plan:
> 
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Plan
> .
> 
> Instead of "f.x" (to access field x of record f), maybe we could write
> "f{x}" as the record selection.  That is, we'd reuse the brace notation
> which is already in place for record updates.  Unlike dot notation, this 
is
> unambiguous and doesn't conflict with any existing syntax (AFAIK).  It
> would also generalize to "f{x}{y}{z}" instead of "f.x.y.z".
> 
> This proposal would add two new forms of expressions:
> 
> f{x} to access field x of data f
> ({x}) = \f -> f{x} as a field access section
> 
> Additionally, it seems like record mutation expressions could also have
> sections:
> 
> ({x=2}) = \f -> f{x=2}
> 
> That actually seems useful by itself, regardless of whether we use dot
> notation for field access.

I think this is a pretty nice idea. (Disclaimer: I haven't spent any time on 
checking corner cases; also I firmly belong to the anti-further-overloading-
of-dot faction). In any case it is light-weight enough to be actually 
useful, it is readable and suggestive, and (at least conceptually) fits well 
in the existing record syntax.

This deserves a fully fleshed-out proposal for Haskell' IMO.

Cheers
-- 
Ben Franksen
()  ascii ribbon campaign - against html e-mail 
/\  www.asciiribbon.org   - against proprietary attachm€nts


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A possible alternative to dot notation for record access

2013-06-30 Thread Roman Cheplyaka
* Carter Schonwald  [2013-06-30 03:26:22-0400]
> Otoh, would there be any ambiguity wrt applying functions to blocks?
> 
> eg
> f = (+ 1)
> h= f {let x = 7 in 3*x},
> would that trip up the syntax?

This is not valid Haskell anyway (there's no such thing as "applying
functions to blocks"). You can write

  h = f (let {x = 7} in 3*x)

or

  h = f $ let {x = 7} in 3*x

Roman

> On Sun, Jun 30, 2013 at 2:59 AM, Judah Jacobson 
> wrote:
> 
> > Hi all,
> >
> > I had a quick idea about record field syntax as specified in the GSoC
> > project plan:
> > http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Plan
> > .
> >
> > Instead of "f.x" (to access field x of record f), maybe we could write
> > "f{x}" as the record selection.  That is, we'd reuse the brace notation
> > which is already in place for record updates.  Unlike dot notation, this is
> > unambiguous and doesn't conflict with any existing syntax (AFAIK).  It
> > would also generalize to "f{x}{y}{z}" instead of "f.x.y.z".
> >
> > This proposal would add two new forms of expressions:
> >
> > f{x} to access field x of data f
> > ({x}) = \f -> f{x} as a field access section
> >
> > Additionally, it seems like record mutation expressions could also have
> > sections:
> >
> > ({x=2}) = \f -> f{x=2}
> >
> > That actually seems useful by itself, regardless of whether we use dot
> > notation for field access.
> >
> > Best,
> > -Judah
> >
> > ___
> > Glasgow-haskell-users mailing list
> > Glasgow-haskell-users@haskell.org
> > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> >
> >

> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A possible alternative to dot notation for record access

2013-06-30 Thread Carter Schonwald
indeed, this relates / augments record puns syntax already in GHC
http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#record-puns
.

Otoh, would there be any ambiguity wrt applying functions to blocks?


eg
f = (+ 1)
h= f {let x = 7 in 3*x},
would that trip up the syntax?




On Sun, Jun 30, 2013 at 2:59 AM, Judah Jacobson wrote:

> Hi all,
>
> I had a quick idea about record field syntax as specified in the GSoC
> project plan:
> http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Plan
> .
>
> Instead of "f.x" (to access field x of record f), maybe we could write
> "f{x}" as the record selection.  That is, we'd reuse the brace notation
> which is already in place for record updates.  Unlike dot notation, this is
> unambiguous and doesn't conflict with any existing syntax (AFAIK).  It
> would also generalize to "f{x}{y}{z}" instead of "f.x.y.z".
>
> This proposal would add two new forms of expressions:
>
> f{x} to access field x of data f
> ({x}) = \f -> f{x} as a field access section
>
> Additionally, it seems like record mutation expressions could also have
> sections:
>
> ({x=2}) = \f -> f{x=2}
>
> That actually seems useful by itself, regardless of whether we use dot
> notation for field access.
>
> Best,
> -Judah
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users