Re: Scope of committee (can we do *new* things?)

2016-05-12 Thread Andres Loeh
I think we all agree that in general, we should focus on existing
language extensions that have an implementation, and expect language
extensions to be implemented for them to be seriously considered for
inclusion in the standard.

But I think it would be wrong to turn this into a hard rule. Language
extensions are usually looked at in isolation, whereas the standard is
supposed to be a whole. There may be things that fit in well, are
useful generalizations of extensions we want to adopt, and so on that
are worth discussing. Also, extensions should perhaps be modified or
changed in some cases. If we say in advance that we can only
standardize things that GHC already implements, and only in exactly
this way, then it is a bit too limiting, and this would be throwing
away the chance to clean up a few issues.

The other side of this is that if we really arrive at the conclusion
that something should be different from the current GHC
implementations in any significant way, we should at least try to get
it implemented during, and not just after, the standardization process
so that we can still get practical feedback, and to prevent ending up
with a standard that will never be implemented.

Also (I think I've said this before), we should keep in mind that the
whole process for Haskell 2020 can have more outputs than just the new
standard itself. We can make progress towards standardization of
features in future versions of Haskell even if they don't yet make it.
We can make statements that we would in principle like to see certain
features in the standard, and identify the issues that currently
prevent them from being included.

Cheers,
  Andres

On Thu, May 12, 2016 at 9:46 PM, Iavor Diatchki
 wrote:
> I disagree that we should be standardizing language features that have not
> been implemented.
>
> I think having an implementation is important because:
>1. the act of implementing a feature forces you to work out details that
> you may not have thought of ahead of time.  For example, for a small
> syntactic extension, the implementation would have to work out how to fit it
> in the grammar, and how to present the new feature in, say, error messages.
>2. having an implementation allows users to try out the extension and
> gain some empirical evidence that the extension is actually useful in
> practice (this is hard to quantify, I know, but it is even harder if you
> can't even use the extension at all).
>
> If some feature ends up being particularly useful, it could always be
> standardized in the next iteration of the language, when we've gained some
> experience using it in practice.
>
> -Iavor
>
>
>
> On Wed, May 11, 2016 at 11:17 AM, John Wiegley 
> wrote:
>>
>> > Gershom B  writes:
>>
>> > While such changes should definitely be in scope, I do think that the
>> > proper
>> > mechanism would be to garner enough interest to get a patch into GHC
>> > (whether through discussion on the -prime list or elsewhere) and have an
>> > experimental implementation, even for syntax changes, before such
>> > proposals
>> > are considered ready for acceptance into a standard as such.
>>
>> Just a side note: This is often how the C++ committee proceeds as well: a
>> language proposal with an experimental implementation is given much higher
>> credence than paperware. However, they don't exclude paperware either.
>>
>> So I don't think we need to rely on implementation before considering a
>> feature we all want, but I do agree that seeing a patch in GHC first
>> allows
>> for much testing and experimentation.
>>
>> --
>> John Wiegley  GPG fingerprint = 4710 CF98 AF9B 327B B80F
>> http://newartisans.com  60E1 46C4 BD1A 7AC1 4BA2
>> ___
>> Haskell-prime mailing list
>> Haskell-prime@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime
>
>
>
> ___
> Haskell-prime mailing list
> Haskell-prime@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime
>
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime


Re: Are there GHC extensions we'd like to incorporate wholesale?

2016-05-03 Thread Andres Loeh
Hi.

Just to add a few general points. There are different dimensions to
evaluate GHC extensions for inclusion in the standard, and just making
lists does not really reflect that. The two most important ones, I
think, are:

1. Whether we think they're actually a good idea or not.

2. Whether we think they're feasible to specify in a sensible way.

There are variations of these points (extensions that are perhaps
possible to specify, but ugly in their current form; extensions that
have subtle interactions with others; ...)

In general, I am in favour on working on extensions for which we
believe they're good ideas, and try to make progress, even if we
cannot include them yet. So just as an example, if we think GADTs (and
not just GADTSyntax) are in principle a good idea and should be in a
future standard, then perhaps we can try to work out what exactly we
feel would be needed to include them, but is still missing. Then even
in times when no standardization process is active, people can look at
this list of issues and try to work on them. I also think that we
should be careful with straight-forward looking syntax extensions.
Just because an extension is easy to specify should not make it an
automatic accept either. The complexity of the language is already
high.

All this being said, I still have a personal list:

BangPatterns
ConstrainedClassMethods
ConstraintKinds (?)
Derive* (?)
EmptyCase
ExistentialQuantification
ExplicitForAll
ExplicitNamespaces
ExtendedDefaultRules (?)
FlexibleContexts
FlexibleInstances
GADTSyntax
InstanceSigs
KindSignatures
NullaryTypeClasses
Overloaded* (?)
PartialTypeSignatures (?)
RankNTypes
ScopedTypeVariables
StandaloneDeriving (?)
TypeSynonymInstances
TypeOperators (?)

I probably forgot a few. For the ones listed with (?), I am aware of
some problems, but I'd still be very happy to at least have some
discussions about them and make some progress in the direction of
future standardization, as I indicated above.

Cheers,
  Andres

On Tue, May 3, 2016 at 7:32 AM, M Farkas-Dyck  wrote:
> On 02/05/2016, Cale Gibbard  wrote:
>> Are there extensions which ought to stop being extensions?
>
>> It may also be best to leave the answer up to the implementations. It is much
>> easier to argue for something like that once the extension has been on by
>> default in GHC and all other implementations for a while and most everyone
>> seems happy leaving it on.
>
> I think in many cases that would defeat the purpose of extensions.
> ___
> Haskell-prime mailing list
> Haskell-prime@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime


Re: Infrastructure & Communication

2016-04-29 Thread Andres Loeh
Hi.

I'm ok with the general proposals made by Herbert. I'm not a huge fan
of github myself, but it seems like the most pragmatic choice right
now, and I wouldn't know anything else that is clearly better, so I'm
in favour. I'd somewhat prefer to have everything (wiki etc) in one
place then, but I don't have strong opinions on this topic.

Cheers,
  Andres
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime


Re: Update on Haskell Prime reboot?

2016-04-22 Thread Andres Loeh
Hi.

I've been talking to Herbert from time to time, and I know he's having
a draft announcement lying around, and is still planning on properly
starting the process soon, and has (this is my opinion, not his) just
been falling into the trap of waiting for a "good moment" which then
never comes.

I'm personally still eager to get the discussions about a new standard started.

While it's true that the old Haskell Prime committee has been doing
good work in creating some sort of catalogue of issues and extensions
at the time, it's still far from proper standardization. And indeed, I
think the bulk of the work that goes into a new standard in my opinon
is to work out all the corner cases and the actual specification of
the extensions. It's less important which ones ultimately go in or
stay out, but actually specfiying them properly is already going to be
a good step forward.

Cheers,
  Andres


On Fri, Apr 22, 2016 at 7:55 PM, José Manuel Calderón Trilla
 wrote:
> Hi Richard,
>
>> As a concrete suggestion, I wonder if we should have two goals:
>>
>> 1. Write down an updated standard for Haskell.
>>
>> 2. Write down pre-standards for several extensions.
>
> I agree with both of these. It may even be useful to use goal 2 as a
> stepping stone to determine what extensions should receive the extra
> attention necessary (if any) to be part of goal 1. Were you thinking
> that these pre-standards would look something like Mark Jones's
> 'Typing Haskell in Haskell' paper? A simplified and clear
> specification in the form of a Haskell program would go a long way in
> clarifying the meaning of certain extensions. To use your example, you
> could imagine an implementation of GADTs that forms the baseline of
> what the GADT extension should mean (implementations should accept at
> least what this one does). That might be too ambitious though.
>
> A lot of the 'obvious' extensions were discussed that last time the
> Haskell Prime committee was active, so a lot of groundwork has been
> laid already. The most important step right now is empowering people
> to move forward with the process.
>
> Herbert Valerio Riedel is the chair of the reboot, and as such gets
> final say on who is a member of the committee and any timeline for
> deciding. That being said, I think the aim should be to have the
> committee membership decided soon and start discussing what the
> priorities should be. I'm partial to suggesting a face to face meeting
> at ICFP, but realize that it is difficult for many to attend to ICFP.
>
> Cheers,
>
> José
>
>
> On Fri, Apr 22, 2016 at 9:33 AM, Richard Eisenberg  wrote:
>> I stand by ready to debate standards and would enjoy moving this process 
>> forward. However, I'm not in a position where I can lead at the moment -- 
>> just too consumed by other tasks right now.
>>
>> As a concrete suggestion, I wonder if we should have two goals:
>>
>> 1. Write down an updated standard for Haskell.
>>
>> 2. Write down pre-standards for several extensions.
>>
>> About (2): I'm very sympathetic to a recent post on Haskell-cafe about 
>> having formal descriptions of language extensions. It is not our purview to 
>> document GHC. However, several extensions are in very common use, but might 
>> not be quite ready for a language standard. Chief among these, in my 
>> opinion, is GADTs. GADTs are problematic from a standardization standpoint 
>> because it's quite hard to specify when a GADT pattern-match type-checks, 
>> without resorting to discussion of unification variables. For this reason, I 
>> would be hesitant about putting GADTs in a standard. On the other hand, it 
>> shouldn't be too hard to specify some sort of minimum implementation that 
>> individual compilers can build on. I'm calling such a description a 
>> "pre-standard".
>>
>> Thoughts?
>>
>> Richard
>>
>> On Apr 21, 2016, at 5:22 PM, José Manuel Calderón Trilla  
>> wrote:
>>
>>> Hello all,
>>>
>>> I'm curious if there is any progress on the reboot of the Haskell
>>> Prime committee. It has been six months since the closing of
>>> nominations and there hasn't been any word that I'm aware of. I've
>>> also spoken to a few others that have self-nominated and they too have
>>> not heard any news.
>>>
>>> Personally, I feel that a new standard is very important for the
>>> future health of the community. Several threads on the mailing list
>>> and posts on the web, such as one on reddit today [1], show a desire
>>> from the community for a major consolidation effort.
>>>
>>> If there is any way that I can help the process along I would be glad
>>> to do so. It would be a shame to allow for the enthusiasm for a new
>>> committee fade away.
>>>
>>> Cheers,
>>>
>>> José
>>>
>>>
>>> [1]: 
>>> https://www.reddit.com/r/haskell/comments/4fsuvu/can_we_have_xhaskell2016_which_turns_on_the_most/
>>> ___
>>> Haskell-prime mailing list
>>> Haskell-prime@haskell.org
>>> 

Re: help from the community?

2007-01-31 Thread Andres Loeh
 Just a little remark on the side: 'If' and 'case' demand exactly one
 expression. In such cases allowing zero expressions is not a
 generalization but an unnecessary complication. 'Let' and 'where'
 allow any number of bindings, so allowing zero bindings (instead of
 demanding at least one) is a simplification.
 
 I meant the branches of a case (the report specifies at least 1).
 
 I think it's important to keep some possibility for the compiler to detect 
 probable errors as syntax errors. If all syntax is inhabited by strange 
 defaults then this just means simple errors will go undetected eg:
 
let a = case foo of
 
 Here, the user has probably got sidetracked into editing some other part of 
 the program and just forgotten to get back to fill in the cases for the 
 case construct. Allowing zero cases means the user will get a strange 
 runtime error instead as the function part of the case is undefined.

I agree. On the other hand, if there are uninhabited types (modulo _|_), it
might be nice to have an empty case as an explicit eliminator.

let z = \y (foo y)
 
 Here, it seems clear that the user has just forgotten to type the - which 
 means a simple syntax error would get transformed into a much more puzzling 
 (esp for a newbie) type error.

Again, for the lambda I obviously meant the case of 0 variables, i.e. something
like (\ - y) which would then just be equivalent to y. I think this case is
probably the one that's most comparable to the situation in question (whether
to allow empty forall's). Since the designers of previous Haskell versions
obviously thought it's a good idea to disallow empty lambdas, let's disallow
empty forall's as well.

Cheers,
  Andres
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: help from the community?

2007-01-30 Thread Andres Loeh
  The only reasons that I could see in favor of allowing empty foralls
  is that it might be easier to automatically generate code. Haskell
  seems to be a bit inconsistent in how it treats empty constructs. For
  example, empty let and empty where seems to be allowed, but not an
  empty case?
 
 Just a little remark on the side: 'If' and 'case' demand exactly one
 expression. In such cases allowing zero expressions is not a generalization
 but an unnecessary complication. 'Let' and 'where' allow any number of
 bindings, so allowing zero bindings (instead of demanding at least one) is
 a simplification.

I meant the branches of a case (the report specifies at least 1). Similarly,
the report specifies that lambdas must have at least one argument, infix
declarations must not be empty and datatype declarations must not be empty
(the latter will definitely be fixed).

Cheers,
  Andres
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: help from the community?

2007-01-29 Thread Andres Loeh
 I cannot see how an empty list of tyvars is useful or desirable in
 practice:
 data Foo = Foo (forall . Int)
 is equivalent to just
 data Foo = Foo Int
 so why bother to permit the former?  It probably indicates some error in
 the thinking of the programmer, so the compiler should bring it to her
 attention.

The only reasons that I could see in favor of allowing empty foralls
is that it might be easier to automatically generate code. Haskell
seems to be a bit inconsistent in how it treats empty constructs. For
example, empty let and empty where seems to be allowed, but not an
empty case?

 On the other hand, I can imagine a use for phantom type variables in the
 quantifier (especially if they occur in multi-parameter predicates, but
 not in the type).  So I think accepting them with a warning is
 reasonable.
 
 I can also imagine predicates that do not mention locally-quantified
 variables - the assumption must be that they mention variables bound on
 the LHS of the datatype decl instead?  e.g. the Show predicate here:
 
 data Foo a b = Foo a b
  | Bar (forall c . (Show b, Relation b c) = (b,c))
 
 Hmm, maybe a simpler version of this example would illustrate what you
 mean by the proposal (first of the three bullets) to allow an empty
 quantifier list:
 
 data Foo a b = Foo a b
  | Bar (forall . Show b = b)
 
 In which case, does this even count as a polymorphic component at all?
 Is it not rather GADT-like instead?
 
 data Foo a b where
   Foo :: a - b - Foo a b
   Bar :: Show b = b - Foo a b

Would these two have the same meaning? I have a feeling what the GADT
is, but no idea what the former type means.

  Constructor that have polymorphic components cannot appear in the
  program without values for their polymorphic fields.
 
 I didn't fully understand this requirement.  If Haskell-prime gets
 rank-2 or rank-n types, then do we need to restrict constructors in this
 way?

Ok, this really boils down to the question of whether we do rank-2 or
rank-n types. I'm biased, because I actually use rank-n types
frequently, and feel somewhat limited by the rank-2 restrictions.  I
don't know how many people actually do, though. I can understand
Iavor's points that rank-2 might be easier to explain, but at least
GHC's rank-n extension has a very detailed paper explaining it, so I
guess it's one of the better documented extensions.

I very much agree that nested patterns for polymorphic components
should be disallowed.

Cheers,
  Andres
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: recent changes to draft haskell prime report

2007-01-15 Thread Andres Loeh
 I have fiddled with the build system, to enable the current state of the
 Report in the darcs repository to be generated into (at least) HTML,
 (hopefully also PDF and PS soon) automatically as every patch is checked

do we still need PS?

 in.  In theory, the following link should always give you the most
 up-to-date version of the text:
 
 http://darcs.haskell.org/haskell-prime-report/report/haskell-prime-draft.html
 
 (I am wondering whether to make this a 'darcs test' thing, so if the
 Report fails to build, your patch will be rejected.  Any opinions?)

Good idea.

Cheers,
  Andres
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: writing / status teams - call for volunteers

2006-09-28 Thread Andres Loeh
 Would anyone else like to volunteer to write a section of the report for
 specific proposals below?
 
  In
  ==
  
  #74: add some kind of concurrency: SM, HN, IJ
  #35: add ForeignFunctionInterface: MC, SM
  #49: add multi parameter type classes: MS
  #60: add RankNTypes or Rank2Types: AL
  #57: add polymorphic components: AL
  #26: add ExistentialQuantification (existential components): AL, MS, SJT
  #24: add HierarchicalModules: BH, IJ
  #25: add EmptyDataDeclarations: BH, HN
  #23: fix common pitfall with the do-notation and if-then-else: SM, HN, 
  #42: fix comment syntax grammar: SM
  #56: add Pattern Guards: :(
  #78: Add infix type constructors: BH, AL
  Help w/ libraries (yay!): IJ, BH, SM, RP, DS

I would like to start writing a new section on the syntax of data type
declarations. All the proposals I've put my name on are somewhat related
to this area, most of all existential quantification and infix type
constructors.

Have we already discussed how we produce new text for the report? Is this
supposed to be all on the Wiki, or are we going to modify the TeX sources
of the Haskell-98 report? Is the plan to keep the general style and structure
of the Haskell-98 report, or are we going to rewrite and restructure the
whole report?

Cheers,
  Andres
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Exceptions

2006-09-01 Thread Andres Loeh
Hi Ashley.

Thanks for your interest in open data types. As one of the authors of
the open data types paper, I'd like to comment on the current
discussion.

You comment Simon's upcoming HW paper on extensible exceptions:

 You write:
 
  Compared to our approach, theirs requires new extensions to the language 
  (although not deep),
 
 Typeable is an extension to Haskell, and a rather ugly one at that. 
 The open datatypes extension is both cleaner and more general.

I think the stress here is on *new* extensions. I agree that an open
type of type representations might be a more beautiful solution to the
problem that Typeable solves. Nevertheless, the fact is that Simon's
solution can be used in current GHC without further implementation work.

  and has difficulties with separate compilation.
 
 They claim to solve this I think, though I haven't examined it really 
 carefully. You may know better, of course.

I've discussed this with Simon PJ. Apart from minor technical problems,
everything seems doable in GHC, but it is quite some work and it's not clear
that I will have the time to study GHC closely enough to do it in the
near future. I hope I can say more after the Hackathon ...

  Arguably the open data types approach is more direct and more accessible,
 
 Yes,
 
  as is often the case with extensions designed to solve a particular problem.
 
 That's not fair. Open datatypes have other applications. A general file 
 interpreter for instance, that given a MIME type string and a list of 
 bytes yields an object. Or a collection of variable resources of 
 various types that could be passed to a program. Or a hierarchy of UI 
 widgets. Or anything that Typeable and Dynamic are currently used for, 
 but more cleanly. Hs-plugins, for instance.
 
 It's the missing piece.

True, open data types have never been invented as a solution to the
problem of extensible exceptions. It is an application that we found
afterwards.

  Still, the argument for adding open data types to the language is weakened 
  by 
  the fact that they are subsumed by type classes: in fact the authors give 
  an 
  encoding of open data types into type classes,
 
 Well not really. The encoding involves lifting everything from values 
 to types, which means a function still can't return a value of an open 
 type determined at run-time.

Even if both approaches would be equally expressive, the type class encoding
still has a lot of syntactic overhead. Moving from a closed to an open data
type encoded by type classes requires changing your whole program, whereas
with open data types, it is a local change.

Apart from this discussion however, open data types are clearly not
Haskell' material, because the proposal is new and currently
unimplemented.

The extensions required for Simon's approach to exceptions have a good
chance of being included in Haskell'.

Cheers,
  Andres
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Parallel list comprehensions

2006-02-04 Thread Andres Loeh
 I noticed ticket #55--add parallel list comprehensions--which according to
 the ticket, will probably be adopted. I would argue against.

[Several good points removed.]

I agree.

Cheers,
  Andres
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime