Simon Marlow:
> Not to mention overlap with sections:  (!i).  Even with just bang
> patterns, we have some interesting parsing problems due to the overlap
> with infix '!'.  eg., now 
> 
>   arr ! x = indexArray arr x
> 
> will probably parse as
> 
>   arr (!x) = indexArray arr x
> 
> which means that in order to define (!) you have to use the prefix form:
> (!) arr x = ...
> 
> GHC's implementation of bang pattern parsing has some ugliness to deal
> with this.  In the report, we will have to be very careful to make sure
> the syntax doesn't have any ambiguities in this area, which will
> probably mean adding special cases to the grammar.
> 
> My suggestion is to avoid these problems by removing infix '!' from the
> syntax:
> 
> http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/ArrayIndex
> ing
> 
> I realise this is a code-breaking change, but I consider the special
> cases introduced to the syntax by bang patterns to be rather warty.
> Also, since I think many of us envisage Haskell moving towards having
> more strictness annotations in the future, it makes sense to
> consistently use the '!' operator to mean "strict".

I agree that the use of ! for indexing is a bad choice, actually a very
bad choice.  As arrays are not used that much and (!) isn't even
exported from the Prelude, I like the idea of changing the indexing
syntax.  I am less convinced that it is wise to change the syntax of
function composition, as this will break a huge set of programs.  I
actually also don't see that this affects the array proposal.  (.#)
would be a valid and free operator anyway, wouldn't it?  What about list
indexing? Use (.##)?  (Doesn't look very nice, but transfers the (!) for
arrays and (!!) for lists idea.)  A change to list indexing will
probably break more programs than a change to array indexing.

Apart from the syntactic issues, does anybody else support the idea of
strict tuples as proposed?  I just want to know whether I am alone on
this before putting it on the wiki.

Manuel

> On 19 March 2006 02:35, Manuel M T Chakravarty wrote:
> > Loosely related to Ticket #76 (Bang Patterns) is the question of
> > whether we want the language to include strict tuples.  It is related
> > to bang patterns, because its sole motivation is to simplify enforcing
> > strictness for some computations.  Its about empowering the programmer
> > to choose between laziness and strictness where they deem that
> > necessary without forcing them to completely re-arrange
> > sub-expressions (as seq does).
> > 
> > So what are strict tupples?  If a lazy pair is defined in pseudo code
> > as 
> > 
> >   data (a, b) = (a, b)
> > 
> > a strict pair would be defined as
> > 
> >   data (!a, b!) = ( !a, !b )
> > 
> > Ie, a strict tuple is enclosed by bang parenthesis (! ... !).  The use
> > of the ! on the rhs are just the already standard strict data type
> > fields.
> > 
> > Why strict tuples, but not strict lists and strict Maybe and so on?
> > Tuples are the Haskell choice of returning more than one result from a
> > function.  So, if I write
> > 
> >   add x y = x + y
> > 
> > the caller gets an evaluated result.  However, if I write
> > 
> >   addmul x y = (x + y, x * y)
> > 
> > the caller gets a pair of two unevaluated results.  Even with bang
> > patterns, I still have to write
> > 
> >   addmul x y = let !s = x + y; !p = x * y in (s, p)
> > 
> > to have both results evaluated.  With strict tuples
> > 
> >   addmul x y = (!x + y, x * y!)
> > 
> > suffices.
> > 
> > Of course, the caller could invoke addmul using a bang patterns, as in
> > 
> >   let ( !s, !p ) = addmul x y
> >   in ...
> > 
> > but that's quite different to statically knowing (from the type) that
> > the two results of addmul will already be evaluated.  The latter
> > leaves room for more optimisations.
> > 
> > Syntax issues
> > ~~~~~~~~~~~~~
> > * In Haskell (,) is the pair constructor.  What should be use for
> >   strict tuples?  (!,!) ?
> > * With strict tuples (! and !) would become some sort of
> >   reserved/special symbol.  That interferes with bang patterns, as
> >   (!x, y!) would be tokenized as (! x , y !).  We could use ( ... !)
> >   for strict tuples to avoid that conflict, or just requires that the
> >   user write ( !x, !y ) when they want a bang pattern.  (Just like you
> >   cannot write `Just.x' to mean `Just . x' as the former will always
> >   be read as a qualified name and not the application of function
> >   composition.
> 

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

Reply via email to