I'm coming from a less-informed background than most people, but isn't the fact that we need parentheses in the first place a bit odd?

  If Haskell's grammar went something like expression := (literal+) | doBlock, wouldn't the presence of the `do` keyword be enough for the parser to acknowledge the presence of a do block, and use the curly brackets inserted by the indent parser step to denote where the expression ends? In that case , it seems like that would solve the need for the $ issue, and make the parser simpler...

  Apologies if this is what's actually happening in this extension, but most people against this extension seem to say that it adds complexity. Could someone point out how things end up being more complex?
  
   My impression is that in the current state there's a difference in treatment between a do block and other expressions that is more complex than it should be.



On Mon, Sep 7, 2015 at 8:44 AM Tikhon Jelvis <tikhon@jelv.is> wrote:
+1 from me. At a high level, one of the things that attracts me to Haskell over other languages is that it's willing to change and improve at a faster rate (although, in absolute terms, it's still pretty slow and concerned about backwards compatibility). Assuming a tweak makes sense, rolling it out as an extension and then folding it into the language (maybe as part of the mythical Haskell 2020 standard :)) is perfect. DoAndIfThenElse is a reasonable point of comparison and seems to be a good deal.

And I *do* think this tweak makes sense. The new behavior is more inline with my expectations. I feel that do and lambdas are self-contained expressions and inherently group their contents together; needing an extra set of parentheses or a $ does not make sense. A good way to think about it is that I see do as having braces semantically even when they're syntactically optional. I think most people would agree that requiring parentheses aroud

    foo (do { x; y; z })

is redundant and not useful.

However, I would feel even better if this applied evenly to *all* syntactic elements that worked this way including case expressions. Were they left out just to make the proposal simpler? If you could change the grammar to support this for all the relevant syntactic constructions and it worked reasonably well, I would be significantly more enthusiastic about it. That would feel like a significant simplification of the syntax.

Also, it's worth noting that, as somebody pointed out in the Reddit thread, this extension would make the impredicativity magic around $ less necessary, which feels like a pointer that it *is* a simpler design.

On Sun, Sep 6, 2015 at 3:08 PM, Francesco Ariis <fa-ml@ariis.it> wrote:
On Sun, Sep 06, 2015 at 02:33:28PM -0430, Manuel Gómez wrote:
> It seems to me that lately the community’s visible attitude has
> shifted toward a heightened value of stability and uniformity for
> Haskell and its software ecosystem, and experimentation, fragmentation
> and diversity in styles and dialects are now viewed as threatening.
> This drives us to reject the process of gradual improvement that has
> made Haskell great over the years.  Other similarly purely syntactic
> extensions seem to me to have been met with less resistance in the
> past.  It appears we’re now far more concerned with the pursuit of
> success.
>
> +1

Hello Manuel,
    your post made me clearly realise why I am sometimes unhappy about
syntactic extensions, so I'll take advantage of this discussion to
illustrate my point.

I don't recall the exact details, but a few months ago I was writing a
small patch for a Haskell project I liked. Datatypes were simple, e.g.:

    data SomeData = SomeData {
        somedataName :: String
      , somedataVersion :: Int
      , somedataSynopsis :: Maybe String
      , somedataDescription :: Maybe String
      , somedataHomepage :: Maybe String
      , somedataBugReports :: Maybe String
      -- etc, etc.

In the where part of the (long) top level function, I found an
expression similar to this:

    -- there was no type sig there
    alfa = ("version", somedataVersion)

A tuple with a String and an accessor `SomeData -> Int`, ok.
Somewhere else this pops out:

    let beta = 7 + snd alfa

What? For sure something is wrong, this program shouldn't compile! It
should be:

    let beta = 7 + (snd alfa) myData

I fired ghci, loaded the project and it turns out I was right and ghc wrong!

    λ> :t ("s", somedataVersion)
    ("s", somedataVersion) :: (String , SomeData -> Int)

What was happening? A conspicuous bug in ghc (which was exploited in
a weird way by the project developer)? Hallucinations? Not really!
It turns out that in the top of the file, which looked like:

    {-# LANGUAGE CPP #-}
    {-# LANGUAGE OverloadedStrings #-}
    {-# LANGUAGE QuasiQuotes #-}
    {-# LANGUAGE RecordWildCards #-}
    {-# LANGUAGE ViewPatterns #-}

I missed the `RecordWildCards` extension. RecordWildCards allows these
kind of patterns:

    f (C {a = 1, ..}) = b + c + d
        -- shame on me for not checking extensions first!

This long introduction to make my point :P

> It seems to me that lately the community’s visible attitude has
> shifted toward a heightened value of stability and uniformity for
> Haskell and its software ecosystem, and experimentation, fragmentation
> and diversity in styles and dialects are now viewed as threatening.
> This drives us to reject the process of gradual improvement that has
> made Haskell great over the years.

Even though they aren't as 'dangerous' as other well known extensions,
5 small syntactic extensions potentially create 31 dialects which will
make me trip in many different ways. One of the reason I like Haskell is
because it's a joy to read other people's code (unlike other languages
where I don't even try, so daunting is the challenge).

I think it is healthy to have a thorough discussion for each one of the
proposed extensions and most importantly study what we are trying to
accomplish and see if there is a way to reach the same goal(s) with a
smaller set of orthogonal changes.
And yes, to err on the conservative side and say 'no' if the benefit
isn't worth the additional fragmentation.

I understand the fact that Haskell is meant to be an always evolving
language: this is awesome and I like it. I like it even more when
the community goes forward *together*! [1]


Sorry for the long rant (phew, it took more words than necessary)!
As written above, your message cleared my mind so I decided to share my
thoughts, maybe they can be helpful to the discussion.


[1] be it a Standard like H2010, a well thought out migration-path
    for changes like BPP, a stricter and curated selection for
    extensions, etc.


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe