Re: Easiest way to extend CAS (casMutVar#) to boxed/unboxed Vector elements?

2012-01-12 Thread Simon Marlow

On 10/01/2012 17:19, Ryan Newton wrote:

Hello there,

I was wondering what the recommendations would be for getting CAS on
[mutable] vector elements?

I thought that as a first step I might create an a library that does the
trick only for unboxed vectors, by using bits-atomic (i.e. FFI + GCC
intrinsics).

Roman Leshchinskiy recommended against depending on GCC. He thought,
therefore, that not only boxed arrays but unboxed ones would need an
extra PrimOp to be handled properly:


 You can't rely on gcc extensions because code is usually compiled with the
 native code generator nowadays and doesn't go through gcc. The dependency
 on gcc will (hopefully) be dropped eventually anyway. So you'd probably
 also want primops for unboxed arrrays and Addr#.


Any advice?


For boxed arrays you need a PrimOp of course (like catMutVar#).  For 
unboxed arrays you could get away with FFI, but a PrimOp would be better 
because it could be inline.  But to get it inline would mean modifying 
the native and LLVM backends to support CAS operations.


If I were you I would use FFI for now.  The cost of the out-of-line call 
is much less than the cost of the CAS anyway.  A gcc dependency is not a 
big deal, it's available on all Unix-like platforms and I don't see us 
removing it from the Windows installs any time soon.


Cheers,
Simon

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


Re: Records in Haskell

2012-01-12 Thread Matthew Farkas-Dyck
On 09/01/2012, Greg Weber g...@gregweber.info wrote:
 Thank you for all your feedback! I updated the wiki page accordingly.

 Let us stop and take note of what this feedback is about: the most
 convenient syntax for manipulating records, and much of this feedback
 applies to any records proposal. That is, there are no fundamental
 objections to the implementation of this records implementation. If you
 give this kind of general feedback then I assume you are fine with the
 name-spacing records implementation.

 At this point I feel we are largely waiting on feedback from implementers
 to give the implementation critiques or a green light.

 But that does not need to stop us from continuing our discussion of the
 best syntax for using records.
 For the left-right, right-left issue, I added a discussion and potential
 solution through partial application:

 Partial application provides a potential solution:

(b . .a) r

 So if we have a function f r = b r.a then one can write it points-free:

b . .a

 Our longer example from above:

e . d . .c . .b . .a

 At first glance it may look odd, but it is starting to grow on me. Let us
 consider more realistic usage with longer names:

echo . delta . .charlie . .beta . .alpha

 Is there are more convenient syntax for this? b .a
 Note that a move to a different operator for function composition
 (discussed in dot operator section) would make things easier to parse:

b ~ .a

 where the unicode dot might be even nicer.

I told you so (^_^)

Unicode dot (∘) would be optimal, since that's what it's for. If to
type '∘' is awkward, then one can use (Control.Category.). We need
not (and, in my opinion, should not) define another operator.

 On Mon, Jan 9, 2012 at 3:15 AM, wren ng thornton w...@freegeek.org wrote:

 quux (y . (foo.  bar).baz (f . g)) moo
 It's not that easy to distinguish from
 quux (y . (foo.  bar) . baz (f . g)) moo



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


Re: Records in Haskell

2012-01-12 Thread Matthew Farkas-Dyck
On 09/01/2012, Isaac Dupree m...@isaac.cedarswampstudios.org wrote:
 You mean this wiki page, right?:
 http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing

 That is, there are no fundamental
 objections to the implementation of this records implementation.

 I think that might be overly optimistic... I think there's a risk that
 SPJ finds an irritating complication to type inference  the rest of us
 aren't type-system-savvy enough to continue trying to guess at that :)
 But I think you're referring to whether we object to ad-hoc overloading
 of record field names (neither parametric nor class-based polymorphism),
 if no difficulties crop up.  Some of the concerns on
 http://www.haskell.org/haskellwiki/TypeDirectedNameResolution apply --
 I'm not sure to what extent, but address those concerns rather than
 require those people to repeat themselves again! :)

 (If we dodge all those obstacles, well, a better record system is better!)


 Regardless, I think the proposal needs more precision, so I tried for
 syntax.  And got this thousand word email just about syntax, in several
 sections of reasoning, sorry!

 --so here are my conclusions/suggestions up front in case you prefer,
 most complicated first - look later for details in a different order,
 referenced by [number].


 Given that type inference for expr.field decides between several
 different possible meanings of field, which fields in scope count as
 possibilities?  I concluded All identifiers 'field' in top-level scope
 (i.e. declared in this module or imported unqualified from another
 module), but no local let/lambda bindings. [1]

 I have an unrelated record/module system tweak suggestion to prevent
 leaks of the field-ness of exports meant only as functions. [2]

 .field, for any identifier field, is a postfix operator that binds
 more tightly than function application. [1]

 I don't care whether the expression and .field are permitted to be
 separated by whitespace or not. [4]

 (.field) as a section: should it always require parentheses? (assuming
 there is a way to type-inference the unapplied dot operator usefully at
 all). [3]

 The Type.{...} / expr.{...} variations look probably fine (Syntax for
 updates in the wiki). [5]

 Allow TyCon.field for selecting a specific version of field, but
 only if there isn't a module in scope as TyCon in which case it's
 interpreted as Module.field. [7]

 Allow expr.TyCon.field / expr.Module.field wherever expr.field is
 allowed. [8]

 I bikesheddily suggest field@expr rather than expr.field (I'd be
 alright with either/both). [6]




 = Defining the basic dot syntax for record field selection =

 [1]
 .x, for any identifier x, is a postfix operator that binds more tightly
 than function application.  This operator does not constrain the type of
 its operand or its result.  After regular type inference, the type
 system collects in-scope xs and does something to try to choose one.

 (As a non-type-system-expert, I'm not addressing what does something
 means in this email, besides capitalizing TYPE INFERENCE where I suspect
 there might (or might not) be extra problems.  Anyway, I wish the
 algorithm do the right thing for expr.x.y.z.)


 But which in-scope xes does it collect?  Regular Haskell scope would
 completely break let x = var.x if we wished to allow let x = var.x.

 How about: all record fields 'x' declared in this module or imported
 (qualified[??] or unqualified) from another module.

 [[[
 Should qualified ones be allowed?
 Pro: if you import Data.Map qualified, as is common (let's just pretend
 that Maps have members), then someMap.field works.

 Pro: it's like allowing qualified imports for instance declaration
 class-member-definitions.

 Con: it's not really like that. It makes qualified imports a weaker
 protection, as the class/instance exception can lead to no ambiguity,
 but this can lead to ambiguity.  The PVP would make a sad face.

 Con: using unqualified import with (..) would easily bring the field
 names into scope.  Fictitiously, import qualified Data.Map as Map;
 import Data.Map(Map(..)).

 Observation: allowing qualified imports, but not following the
 class/instance system's style of including everything in the transitive
 closure of imported modules, still prevents you (Pro) from breaking
 intentional abstraction barriers, but (Con?) requires you to import the
 operators for types you receive but don't import.

 Opinion: only unqualified imports should be part of the selection process.
 ]]]

 [[[
 Problem: Restricting the selection to only record fields further
 compromises an existing imperfect property of Haskell:
 module Library (Type, constructor, deconstructor) where
 data Type = Constructor { deconstructor :: Int }
 -- let's pretend it's a bounds-limited int or such.
 constructor int | int = 3  int  17 = Constructor int

 Currently, importers of the module can observe that 'deconstructor' is a
 record-field by importing Library(Type(..)) and getting 

Re: Records in Haskell

2012-01-12 Thread Greg Weber
I added this and your Control.Category. to the wiki.

I am not sure about the tuple proposal - tuples normally imply an ordering,
which would imply that all record fields must be accounted for at least
with an empty comma or an underscore, particularly if updating the last
field in a record. For records we want a syntax where we can pick out one
or many fields to update and ignore the rest.

My feeling on  is that ~ is slightly more intuitive than  because it
looks like an arrow which I equate with functions, and  is more
difficult to parse because I have to recognize three in a row of the same
character . However, if everyone likes using the unicode dot, then it
doesn't matter what the non-unicode symbol is, and re-using existing
symbols is certainly advantageous.



On Thu, Jan 12, 2012 at 10:02 AM, Matthew Farkas-Dyck
strake...@gmail.comwrote:

 On 09/01/2012, Isaac Dupree m...@isaac.cedarswampstudios.org wrote:
  You mean this wiki page, right?:
  http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
 
  That is, there are no fundamental
  objections to the implementation of this records implementation.
 
  I think that might be overly optimistic... I think there's a risk that
  SPJ finds an irritating complication to type inference  the rest of us
  aren't type-system-savvy enough to continue trying to guess at that :)
  But I think you're referring to whether we object to ad-hoc overloading
  of record field names (neither parametric nor class-based polymorphism),
  if no difficulties crop up.  Some of the concerns on
  http://www.haskell.org/haskellwiki/TypeDirectedNameResolution apply --
  I'm not sure to what extent, but address those concerns rather than
  require those people to repeat themselves again! :)
 
  (If we dodge all those obstacles, well, a better record system is
 better!)
 
 
  Regardless, I think the proposal needs more precision, so I tried for
  syntax.  And got this thousand word email just about syntax, in several
  sections of reasoning, sorry!
 
  --so here are my conclusions/suggestions up front in case you prefer,
  most complicated first - look later for details in a different order,
  referenced by [number].
 
 
  Given that type inference for expr.field decides between several
  different possible meanings of field, which fields in scope count as
  possibilities?  I concluded All identifiers 'field' in top-level scope
  (i.e. declared in this module or imported unqualified from another
  module), but no local let/lambda bindings. [1]
 
  I have an unrelated record/module system tweak suggestion to prevent
  leaks of the field-ness of exports meant only as functions. [2]
 
  .field, for any identifier field, is a postfix operator that binds
  more tightly than function application. [1]
 
  I don't care whether the expression and .field are permitted to be
  separated by whitespace or not. [4]
 
  (.field) as a section: should it always require parentheses? (assuming
  there is a way to type-inference the unapplied dot operator usefully at
  all). [3]
 
  The Type.{...} / expr.{...} variations look probably fine (Syntax for
  updates in the wiki). [5]
 
  Allow TyCon.field for selecting a specific version of field, but
  only if there isn't a module in scope as TyCon in which case it's
  interpreted as Module.field. [7]
 
  Allow expr.TyCon.field / expr.Module.field wherever expr.field is
  allowed. [8]
 
  I bikesheddily suggest field@expr rather than expr.field (I'd be
  alright with either/both). [6]
 
 
 
 
  = Defining the basic dot syntax for record field selection =
 
  [1]
  .x, for any identifier x, is a postfix operator that binds more tightly
  than function application.  This operator does not constrain the type of
  its operand or its result.  After regular type inference, the type
  system collects in-scope xs and does something to try to choose one.
 
  (As a non-type-system-expert, I'm not addressing what does something
  means in this email, besides capitalizing TYPE INFERENCE where I suspect
  there might (or might not) be extra problems.  Anyway, I wish the
  algorithm do the right thing for expr.x.y.z.)
 
 
  But which in-scope xes does it collect?  Regular Haskell scope would
  completely break let x = var.x if we wished to allow let x = var.x.
 
  How about: all record fields 'x' declared in this module or imported
  (qualified[??] or unqualified) from another module.
 
  [[[
  Should qualified ones be allowed?
  Pro: if you import Data.Map qualified, as is common (let's just pretend
  that Maps have members), then someMap.field works.
 
  Pro: it's like allowing qualified imports for instance declaration
  class-member-definitions.
 
  Con: it's not really like that. It makes qualified imports a weaker
  protection, as the class/instance exception can lead to no ambiguity,
  but this can lead to ambiguity.  The PVP would make a sad face.
 
  Con: using unqualified import with (..) would easily bring the field
  names into scope.  

Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Isaac Dupree

On 01/12/2012 07:06 AM, Matthew Farkas-Dyck wrote:

On 09/01/2012, Greg Weber g...@gregweber.info wrote:

Note that a move to a different operator for function composition
(discussed in dot operator section) would make things easier to parse:

b~ .a

where the unicode dot might be even nicer.


I told you so (^_^)

Unicode dot (∘) would be optimal, since that's what it's for. If to
type '∘' is awkward, then one can use (Control.Category.). We need
not (and, in my opinion, should not) define another operator.


Is ∘ (U+2218 RING OPERATOR)* in Prelude yet? We should propose that.**

I checked my compose-key (Linux)
and it can produce middle-dot · (U+00B7 MIDDLE DOT) with Compose . -, 
but not ∘ in any way***.  If we use the proper Unicode operator ∘, then 
let's make a wiki page for all the common OSes/input methods, saying how 
to input it (aside from copy/paste).  Is there anything on the Web 
somewhere already?  Did Perl do this ( - I think they introduced some 
Unicode-based syntax)?  There's 
http://www.haskell.org/haskellwiki/Unicode-symbols , which has some 
information (none of which let me write ∘ in an e-mail without using 
copy/paste).


* found out using http://www.decodeunicode.org/
** (negate ∘ (+ 1)) 3 doesn't work in my ghci 7.0.3 with no 
command-line options (and a UTF-8 system locale and UTF-8-compatible 
terminal, as is typical these days).

*** I checked the list in /usr/share/X11/locale/en_US.UTF-8/Compose

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


Re: Unboxed mutable variables (was: Easiest way to extend CAS (casMutVar#) to boxed/unboxed Vector elements?)

2012-01-12 Thread Simon Marlow

On 12/01/2012 17:55, Johan Tibell wrote:

On Thu, Jan 12, 2012 at 12:54 AM, Simon Marlowmarlo...@gmail.com  wrote:

For boxed arrays you need a PrimOp of course (like catMutVar#).  For unboxed
arrays you could get away with FFI, but a PrimOp would be better because it
could be inline.  But to get it inline would mean modifying the native and
LLVM backends to support CAS operations.

If I were you I would use FFI for now.  The cost of the out-of-line call is
much less than the cost of the CAS anyway.  A gcc dependency is not a big
deal, it's available on all Unix-like platforms and I don't see us removing
it from the Windows installs any time soon.


In a recent project (http://hackage.haskell.org/package/ekg) I found
myself wanting unboxed mutable integers with CAS semantics (to
implement simple counters). What would be required to support

  (1) unboxed mutable variables, and
  (2) CAS semantics for these.

I guess (2) is easy once you have (1). Just add some new primops.


I think by (1) you mean mutable variables containing unboxed values, right?

I normally use an unboxed array of length 1 for these.  There's not much 
overhead - only an extra word in the heap compared to implementing them 
natively.  I'm guessing you care more about the overhead of the 
operations than the space overhead of the counter itself, and a 
1-element unboxed array should be just fine in that respect.


Cheers,
Simon

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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Brandon Allbery
On Thu, Jan 12, 2012 at 13:20, Isaac Dupree
m...@isaac.cedarswampstudios.orgwrote:

 way***.  If we use the proper Unicode operator ∘, then let's make a wiki
 page for all the common OSes/input methods, saying how to input it (aside
 from copy/paste).  Is there anything on the Web somewhere already?  Did
 Perl do this ( - I think they introduced some Unicode-based syntax)?
  There's 
 http://www.haskell.org/**haskellwiki/Unicode-symbolshttp://www.haskell.org/haskellwiki/Unicode-symbols,
  which has some information (none of which let me write ∘ in an e-mail
 without using copy/paste).


Most platforms have some way to define new keys:  on Unix with X11 you can
use Xkb or xmodmap (the keysym for a Unicode character is the codepoint
expressed as a hex constant, so 0x2218 for ∘), and there are a handful of
Xkb editors out there; on OS X you can use keyboard substitutions (Language
 Text  Text) or use a program such as Ukelele to modify the keyboard
layout; I don't know specifics for Windows, but at its lowest level there
are registry tweaks and there should also be programs to do those tweaks in
people-comprehensible ways.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Unboxed mutable variables (was: Easiest way to extend CAS (casMutVar#) to boxed/unboxed Vector elements?)

2012-01-12 Thread Johan Tibell
On Thu, Jan 12, 2012 at 10:25 AM, Simon Marlow marlo...@gmail.com wrote:
 I think by (1) you mean mutable variables containing unboxed values, right?

Yes.

 I normally use an unboxed array of length 1 for these.  There's not much
 overhead - only an extra word in the heap compared to implementing them
 natively.  I'm guessing you care more about the overhead of the operations
 than the space overhead of the counter itself, and a 1-element unboxed array
 should be just fine in that respect.

I will run some benchmarks. If it turns out that using an unboxed
array is costly, what would it take to get real mutable variables
containing unboxed values?

-- Johan

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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Evan Laforge
 I told you so (^_^)

 Unicode dot (∘) would be optimal, since that's what it's for. If to
 type '∘' is awkward, then one can use (Control.Category.). We need
 not (and, in my opinion, should not) define another operator.


 Is ∘ (U+2218 RING OPERATOR)* in Prelude yet? We should propose that.**

 I checked my compose-key (Linux)
 and it can produce middle-dot · (U+00B7 MIDDLE DOT) with Compose . -, but
 not ∘ in any way***.  If we use the proper Unicode operator ∘, then let's

OS X makes a MIDDLE DOT with option-shift-9: ·

However, changing the composition operator from (.) will involve huge
amounts of changes to source code.  It can mean changing a large
percentage of all the lines in each file---I for one use (.) quite
heavily.  With a haskell parser the rename could happen automatically,
but we're still talking about a wall in source control where every
single line was changed by one person.  Groups that are reluctant to
make formatting changes for fear of confusing revision history are
really going to hate that one.

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


Re: Unboxed mutable variables

2012-01-12 Thread Simon Marlow

On 12/01/2012 18:37, Johan Tibell wrote:

On Thu, Jan 12, 2012 at 10:25 AM, Simon Marlowmarlo...@gmail.com  wrote:

I think by (1) you mean mutable variables containing unboxed values, right?


Yes.


I normally use an unboxed array of length 1 for these.  There's not much
overhead - only an extra word in the heap compared to implementing them
natively.  I'm guessing you care more about the overhead of the operations
than the space overhead of the counter itself, and a 1-element unboxed array
should be just fine in that respect.


I will run some benchmarks. If it turns out that using an unboxed
array is costly, what would it take to get real mutable variables
containing unboxed values?


It'd need a new heap object type, which is fairly invasive (lots of RTS 
changes).  Not prohibitive, but more invasive than adding a primop for 
example.


Cheers,
Simon

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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Donn Cave
Quoth Evan Laforge qdun...@gmail.com,
...
 ...  Groups that are reluctant to
 make formatting changes for fear of confusing revision history are
 really going to hate that one.

I think a lively discussion would also be possible over whether exotic
characters are suitable at all.

But this is a more or less academic discussion, taking place on
ghc-users, nominally out of view of the general Haskell community,
right?  So I don't need to intrude with mundane objections of
that nature.

Donn

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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Evan Laforge
 But this is a more or less academic discussion, taking place on
 ghc-users, nominally out of view of the general Haskell community,
 right?  So I don't need to intrude with mundane objections of
 that nature.

True, true, there is that.

However, I think there's at least a little bit in the idea that we
could put this back into haskell to help with the record problem.

Otherwise I was going to say that further academic discussion can
inform future language design, but of course it occurs to me that
languages like agda already provide a living example of lots of
unicode.  So the discussion need not be academic, just write some agda
:)  After all, they've failed to take hold in haskell but history and
culture play a large role so it's not a level playing field.

And to add further to the academic discussion *ahem* :)  I tried a vim
script a while back that turned - and :: and (.) and whatnot into
unicode versions.  I eventually decided that many of these require
variable width fonts to look nice, or maybe it's just that the common
fixed width fonts haven't payed much attention to those little-used
characters, but the result is that they turn into a lot of little
misshapen blobs.  = looks like a blobbier -, etc.  For example, on
the mac 11 pt menlo, (.) is a nice solid 4 pixel square, while · is a
single pixel with some anti-aliasing fluff.  I'd have to crank up the
font size on everything else.  So I turned it off.  I mention it
because I haven't seen anyone else mention variable width as a
prerequisite for using unicode operators.

I enjoyed writing with variable width fonts on acme back in the day
but in the end I'm just too comfortable with vim keys and vim doesn't
like variable width.  Given infinite time I'd fix up yi for variable
width, improve its vi keys, get a really high DPI monitor, and give it
a shot.

Of course a significant part is that unfamiliar symbols haven't
engraved themselves into the instant pattern recognition part of the
brain so much, maybe after a year of using them exclusively they'd
look like perfectly clear little blobs.

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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Malcolm Wallace

On 12 Jan 2012, at 18:41, Evan Laforge wrote:

 Unicode dot (∘) would be optimal, since that's what it's for.
 
 Is ∘ (U+2218 RING OPERATOR)* in Prelude yet? We should propose that.**
 
 However, changing the composition operator from (.) will involve huge
 amounts of changes to source code. 

Indeed.  It strikes me that it should be the _new_ feature that takes the new 
syntax, rather than stealing the old syntax and disrupting all the existing 
code that happily uses . for function composition.

So, who is up for proposing centred dot as the new record-field syntax?

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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Donn Cave
Quoth Greg Weber g...@gregweber.info,
 On Thu, Jan 12, 2012 at 6:23 PM, Malcolm Wallace 
 malcolm.wall...@me.comwrote:
 So, who is up for proposing centred dot as the new record-field syntax?

 We don't need to make this change overnight. The new records system will be
 turned on by an extension. If you use the new records system, then you will
 be forced to place spaces around the dot composition operator, or use the
 unicode dot or an alternative operator.

The point seems pretty well taken.  If many programmers will actually
want the records extension, then they'll want to use it without
breaking their code, and the above proposal would help with that.

Changing the compose notation to some other character would break
practically all Haskell code, so it's hard to take that seriously.

Spaces or unicode would be the worst idea yet, but hopefully that
isn't what you meant.

Donn

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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Brandon Allbery
On Thu, Jan 12, 2012 at 17:14, Donn Cave d...@avvanta.com wrote:

 Spaces or unicode would be the worst idea yet, but hopefully that
 isn't what you meant.


Thing is, I think the spaces idea is considered acceptable because it's
*already there*.  Take a look at how GHC decides whether (.) is the
composition operator or a module qualification.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2012-01-12 Thread Matthew Farkas-Dyck
On 12/01/2012, Greg Weber g...@gregweber.info wrote:
 I added this and your Control.Category. to the wiki.

Thanks.

 I am not sure about the tuple proposal - tuples normally imply an ordering,
 which would imply that all record fields must be accounted for at least
 with an empty comma or an underscore, particularly if updating the last
 field in a record. For records we want a syntax where we can pick out one
 or many fields to update and ignore the rest.

Sorry, my proposal was unclear. This is not what I meant; rather, I
meant that one could write
let r.(x, y) = (x', y')
whatever other fields might be in r. I clarify further on the wiki.

That said, I notice now that this syntax is quite verbose, far more so
than the .{} syntax, which is a loss. I think the brevity worth the
added complexity.

 My feeling on  is that ~ is slightly more intuitive than  because it
 looks like an arrow which I equate with functions, and  is more
 difficult to parse because I have to recognize three in a row of the same
 character . However, if everyone likes using the unicode dot, then it
 doesn't matter what the non-unicode symbol is, and re-using existing
 symbols is certainly advantageous.



 On Thu, Jan 12, 2012 at 10:02 AM, Matthew Farkas-Dyck
 strake...@gmail.comwrote:

 On 09/01/2012, Isaac Dupree m...@isaac.cedarswampstudios.org wrote:
  You mean this wiki page, right?:
  http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
 
  That is, there are no fundamental
  objections to the implementation of this records implementation.
 
  I think that might be overly optimistic... I think there's a risk that
  SPJ finds an irritating complication to type inference  the rest of us
  aren't type-system-savvy enough to continue trying to guess at that :)
  But I think you're referring to whether we object to ad-hoc overloading
  of record field names (neither parametric nor class-based polymorphism),
  if no difficulties crop up.  Some of the concerns on
  http://www.haskell.org/haskellwiki/TypeDirectedNameResolution apply --
  I'm not sure to what extent, but address those concerns rather than
  require those people to repeat themselves again! :)
 
  (If we dodge all those obstacles, well, a better record system is
 better!)
 
 
  Regardless, I think the proposal needs more precision, so I tried for
  syntax.  And got this thousand word email just about syntax, in several
  sections of reasoning, sorry!
 
  --so here are my conclusions/suggestions up front in case you prefer,
  most complicated first - look later for details in a different order,
  referenced by [number].
 
 
  Given that type inference for expr.field decides between several
  different possible meanings of field, which fields in scope count as
  possibilities?  I concluded All identifiers 'field' in top-level scope
  (i.e. declared in this module or imported unqualified from another
  module), but no local let/lambda bindings. [1]
 
  I have an unrelated record/module system tweak suggestion to prevent
  leaks of the field-ness of exports meant only as functions. [2]
 
  .field, for any identifier field, is a postfix operator that binds
  more tightly than function application. [1]
 
  I don't care whether the expression and .field are permitted to be
  separated by whitespace or not. [4]
 
  (.field) as a section: should it always require parentheses? (assuming
  there is a way to type-inference the unapplied dot operator usefully at
  all). [3]
 
  The Type.{...} / expr.{...} variations look probably fine (Syntax for
  updates in the wiki). [5]
 
  Allow TyCon.field for selecting a specific version of field, but
  only if there isn't a module in scope as TyCon in which case it's
  interpreted as Module.field. [7]
 
  Allow expr.TyCon.field / expr.Module.field wherever expr.field is
  allowed. [8]
 
  I bikesheddily suggest field@expr rather than expr.field (I'd be
  alright with either/both). [6]
 
 
 
 
  = Defining the basic dot syntax for record field selection =
 
  [1]
  .x, for any identifier x, is a postfix operator that binds more tightly
  than function application.  This operator does not constrain the type of
  its operand or its result.  After regular type inference, the type
  system collects in-scope xs and does something to try to choose one.
 
  (As a non-type-system-expert, I'm not addressing what does something
  means in this email, besides capitalizing TYPE INFERENCE where I suspect
  there might (or might not) be extra problems.  Anyway, I wish the
  algorithm do the right thing for expr.x.y.z.)
 
 
  But which in-scope xes does it collect?  Regular Haskell scope would
  completely break let x = var.x if we wished to allow let x = var.x.
 
  How about: all record fields 'x' declared in this module or imported
  (qualified[??] or unqualified) from another module.
 
  [[[
  Should qualified ones be allowed?
  Pro: if you import Data.Map qualified, as is common (let's just pretend
  that Maps have members), then 

Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Donn Cave
Quoth Brandon Allbery allber...@gmail.com,
 On Thu, Jan 12, 2012 at 17:14, Donn Cave d...@avvanta.com wrote:

 Spaces or unicode would be the worst idea yet, but hopefully that
 isn't what you meant.


 Thing is, I think the spaces idea is considered acceptable because it's
 *already there*.  Take a look at how GHC decides whether (.) is the
 composition operator or a module qualification.

Sure, but I mean:  given that f . g continues to be composition,
but a record notation takes over the unspaced dot, breaking an
existing f.g ...

... what is the rationale for an additional unicode dot?

That's why I more or less assume that wasn't what he meant, that
both  .  and unicode dot would be supported at the same time
for composition, but rather just that one or the other would be
chosen.

Donn

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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Brandon Allbery
On Thu, Jan 12, 2012 at 17:33, Donn Cave d...@avvanta.com wrote:

 Quoth Brandon Allbery allber...@gmail.com,
  On Thu, Jan 12, 2012 at 17:14, Donn Cave d...@avvanta.com wrote:
  Spaces or unicode would be the worst idea yet, but hopefully that
  isn't what you meant.
 
  Thing is, I think the spaces idea is considered acceptable because it's
  *already there*.  Take a look at how GHC decides whether (.) is the
  composition operator or a module qualification.

 ... what is the rationale for an additional unicode dot?

 That's why I more or less assume that wasn't what he meant, that
 both  .  and unicode dot would be supported at the same time
 for composition, but rather just that one or the other would be
 chosen.


Seems obvious to me:  on the one hand, there should be a plain-ASCII
version of any Unicode symbol; on the other, the ASCII version has
shortcomings the Unicode one doesn't (namely the existing conflict between
use as composition and use as module and now record qualifier).  So, the
Unicode one requires support but avoids weird parse issues.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Donn Cave
 Quoth Brandon Allbery allber...@gmail.com,
...
 Seems obvious to me:  on the one hand, there should be a plain-ASCII
 version of any Unicode symbol; on the other, the ASCII version has
 shortcomings the Unicode one doesn't (namely the existing conflict between
 use as composition and use as module and now record qualifier).  So, the
 Unicode one requires support but avoids weird parse issues.

OK.  To me, the first hand is all you need - if there should be a
plain-ASCII version of any Unicode symbol anyway, then you can avoid
some trouble by just recognizing that you don't need Unicode symbols
(let alone with different parsing rules.)

Donn

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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Brandon Allbery
On Thu, Jan 12, 2012 at 18:15, Donn Cave d...@avvanta.com wrote:

  Quoth Brandon Allbery allber...@gmail.com,
 ...
  Seems obvious to me:  on the one hand, there should be a plain-ASCII
  version of any Unicode symbol; on the other, the ASCII version has
  shortcomings the Unicode one doesn't (namely the existing conflict
 between
  use as composition and use as module and now record qualifier).  So, the
  Unicode one requires support but avoids weird parse issues.

 OK.  To me, the first hand is all you need - if there should be a
 plain-ASCII version of any Unicode symbol anyway, then you can avoid
 some trouble by just recognizing that you don't need Unicode symbols
 (let alone with different parsing rules.)


What?  The weird parsing rules are part of the ASCII one; it's what the
Unicode is trying to *avoid*. We're just about out of ASCII, weird parsing
is going to be required at some point.

I also wish to note that I have never been a member of the anything beyond
plain ASCII is fundamental evil set; if we're going to think that way,
just go back to BAUDOT and punched cards.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Evan Laforge
 I also wish to note that I have never been a member of the anything beyond
 plain ASCII is fundamental evil set; if we're going to think that way, just
 go back to BAUDOT and punched cards.

Well, it's similar to the 80 columns debate.  You have to draw the
line somewhere.  It's not about fundamental evil vs. punch cards, but
rather n vs. n+1.  ASCII is a particularly well worn value of 'n'.

In the case of records, we're not really out of symbols, there is
still @, #, , etc.  It's just that we like the look of a dot, and we
are out of dot lookalikes :)

For that matter we have a high'dot though it would mess up the x' = f
x convention.  But it has fine precedent in perl 4 if I'm remembering
correctly :)

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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Brandon Allbery
On Thu, Jan 12, 2012 at 22:32, Morten Brodersen 
morten.broder...@constrainttec.com wrote:

 Requiring unicode characters for the Haskell syntax to solve a
 *relatively* simple problem is a bad bad idea.


Nobody said anything about requiring it.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Morten Brodersen
Even if Unicode is not required, there is still a fallout. Let's look at 
a simple scenario:


Somebody uploads a nice useful Haskell module that include a number of 
Unicode symbols.


Unfortunately most unix/windows/tools/source controls/editors out there 
are Ascii only.


So people who wants to use the module now potentially need to convert 
the code to Ascii (and potentially back again) in order to use it with 
non-Unicode tools.


Yes it is *of course* doable but all of that just because of a 
*relatively simple problem to do with how you access record fields? Really?


That is IMHO a clear example of shooting birds with nuclear rockets.

Let me suggest that a simple non-nuclear alternative would be for people 
interested in Unicode symbols to use an editor that auto converts from 
Haskell Ascii to Haskell Unicode when loading and (of course) back again 
when saving. You can do that today. You can even pick your own Ascii 
from/to Unicode mapping. No need to argue about whether a symbol is 
prettier than another. All of this without forcing the rest of the 
(couldn't care less about record access syntax) Haskell community to 
have to deal with Unicode :-)


Morten

On 13/01/12 14:43, Brandon Allbery wrote:
On Thu, Jan 12, 2012 at 22:32, Morten Brodersen 
morten.broder...@constrainttec.com 
mailto:morten.broder...@constrainttec.com wrote:


Requiring unicode characters for the Haskell syntax to solve a
*relatively* simple problem is a bad bad idea.


Nobody said anything about requiring it.

--
brandon s allbery allber...@gmail.com mailto:allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms



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