Re: PROPOSAL: Literate haskell and module file names

2014-03-26 Thread Simon Marlow

On 17/03/2014 13:08, Edward Kmett wrote:

Foo+rst.lhs does nicely dodge the collision with jhc.

How does ghc do the search now? By trying each alternative in turn?


Yes - see compiler/main/Finder.hs

Cheers,
Simon







On Sun, Mar 16, 2014 at 1:14 PM, Merijn Verstraaten
mer...@inconsistent.nl mailto:mer...@inconsistent.nl wrote:

I agree that this could collide, see my beginning remark that I
believe that the report should provide a minimal specification how
to map modules to filenames and vice versa.

Anyhoo, I'm not married to this specific suggestion. Carter
suggested Foo+rst.lhs on IRC, other options would be Foo.rst+lhs
or Foo.lhs+rst, I don't particularly care what as long as we pick
something. Patching tools to support whatever solution we pick
should be trivial.

Cheers,
Merijn

On Mar 16, 2014, at 16:41 , Edward Kmett wrote:

One problem with Foo.*.hs or even Foo.md.hs mapping to the module
name Foo is that as I recall JHC will look for Data.Vector in
Data.Vector.hs as well as Data/Vector.hs

This means that on a case insensitive file system
Foo.MD.hs matches both conventions.

Do I want to block an change to GHC because of an incompatible
change in another compiler? Not sure, but I at least want to raise
the issue so it can be discussed.

Another small issue is that this means you need to actually scan
the directory rather than look for particular file names, but off
my head really I don't expect directories to be full enough for
that to be a performance problem.

-Edward



On Sun, Mar 16, 2014 at 8:56 AM, Merijn Verstraaten
mer...@inconsistent.nl mailto:mer...@inconsistent.nl wrote:

Ola!

I didn't know what the most appropriate venue for this
proposal was so I crossposted to haskell-prime and
glasgow-haskell-users, if this isn't the right venue I welcome
advice where to take this proposal.

Currently the report does not specify the mapping between
filenames and module names (this is an issue in itself, it
essentially makes writing haskell code that's interoperable
between compilers impossible, as you can't know what directory
layout each compiler expects). I believe that a minimal
specification *should* go into the report (hence,
haskell-prime). However, this is a separate issue from this
proposal, so please start a new thread rather than
sidetracking this one :)

The report only mentions that by convention .hs extensions
imply normal haskell and .lhs literate haskell (Section 10.4).
In the absence of guidance from the report GHC's convention of
mapping module Foo.Bar.Baz to Foo/Bar/Baz.hs or
Foo/Bar/Baz.lhs seems the only sort of standard that exists.
In general this standard is nice enough, but the mapping of
literate haskell is a bit inconvenient, it leaves it
completelyl ambiguous what the non-haskell content of said
file is, which is annoying for tool authors.

Pandoc has adopted the policy of checking for further file
extensions for literate haskell source, e.g. Foo.rst.lhs and
Foo.md.lhs. Here .rst.lhs gets interpreted as being
reStructured Text with literate haskell and .md.lhs is
Markdown with literate haskell. Unfortunately GHC currently
maps filenames like this to the module names Foo.rst and
Foo.md, breaking anything that wants to import the module Foo.

I would like to propose allowing an optional extra extension
in the pandoc style for literate haskell files, mapping
Foo.rst.lhs to module name Foo. This is a backwards compatible
change as there is no way for Foo.rst.lhs to be a valid module
in the current GHC convention. Foo.rst.lhs would map to module
name Foo.rst but module name Foo.rst maps to filename
Foo/rst.hs which is not a valid haskell module anyway as the
rst is lowercase and module names have to start with an
uppercase letter.

Pros:
 - Tool authors can more easily determine non-haskell content
of literate haskell files
 - Currently valid module names will not break
 - Report doesn't specify behaviour, so GHC can do whatever it
likes

Cons:
 - Someone has to implement it
 - ??

Discussion: 4 weeks

Cheers,
Merijn


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







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



Re: proposal for trailing comma and semicolon

2013-08-13 Thread Simon Marlow

On 17/05/13 20:01, Ian Lynagh wrote:


I'd be in favour of allowing a trailing or leading comma anywhere that
comma is used as a separator. TupleSections would need to be changed or
removed, though.


The type constructors for tuples look like (,,,), so they would have to 
be a special case.  I'd much rather leave tuples out of it: the precise 
number of commas in a tuple is significant.


Cheers,
Simon


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


Re: Proposal: NoImplicitPreludeImport

2013-06-05 Thread Simon Marlow

On 05/06/13 02:53, Manuel M T Chakravarty wrote:

Ian Lynagh i...@well-typed.com:

On Tue, Jun 04, 2013 at 01:15:58PM +1000, Manuel M T Chakravarty wrote:


If a module contains an import of the form

  import Prelude.XYZ

then it also automatically uses the NoImplicitPrelude language pragma. 
Otherwise, the Prelude remains to be implicitly defined as before.


What about these?:

import Prelude.XYZ as Foo


In that case, I think, we should also have NoImplicitPrelude, but in case of


import qualified Prelude.XYZ as Foo


they might to explicitly want to avoid clashes with the implicit Prelude. This 
would be an argument to not have NoImplicitPrelude in this case. On the other 
hand, simpler is better; so, maybe it shouldn't depend on the way a 
'Prelude.XYZ' module is imported and we should use NoImplicitPrelude regardless.


import Foo as Prelude.XYZ


I would say that doesn't qualify for having NoImplicitPrelude, but I don't feel 
strongly about that.

Summary
~~~

If and only if a module has at least one impdecl of the form

   'import' ['qualified'] Prelude.XYZ ['as' modid] [impspec]

then this implies {-# LANGUAGE NoImplicitPrelude #-}.

That is a simple rule with no surprises.


Furthermore, this is a direct extension of the current behaviour.

Currently:

 - any import declaration that imports 'Prelude' implies
   NoImplicitPrelude.

Proposed:

 - any import declaration that imports 'Prelude' or a module
   beginning 'Prelude.' implies NoImplicitPrelude.

It's a tiny generalisation, but a very useful one I think.

Cheers,
Simon


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


Re: Proposal: NoImplicitPreludeImport

2013-06-04 Thread Simon Marlow

On 28/05/13 17:08, Ian Lynagh wrote:

On Tue, May 28, 2013 at 08:58:29AM -0700, Johan Tibell wrote:


The likely practical result of this is that every module will now read:

module M where

#if MIN_VERSION_base(x,y,z)
import Prelude
#else
import Data.Num
import Control.Monad
...
#endif

for the next 3 years or so.


Not so. First of all, if Prelude is not removed then you can just write
 import Prelude

But even this is not necessary during the transition period: see
 
http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport#Backwardscompatibility
for a way that backwards compatibility can be maintained, with
additional imports not being needed until code migrates to the
split-base packages.


Hardly anybody uses haskell98 or haskell2010, so we would still have a 
backwards compatibility problem. (plus I'm not keen on a magic language 
feature that turns on when you have a particular package enabled, even 
if it is only temporary).


I'm firmly against this change.  The Prelude is an essential baseline 
vocabulary that everyone can use when talking about Haskell and sharing 
snippets of code.  Without that baseline vocabulary, *everything* has to 
be qualified with an import.  The language report itself has a giant 
'import Prelude' around it - many of the code translations used to 
specify the meaning of syntactic sugar use Prelude functions.


Others have raised the backwards compatibility issue, and I completely 
agree on that front too - we're way past the point where we can break 
that much code to make a small improvement in language consistency.


There's plenty of room for making the Prelude have a more sensible and 
modern coverage of library functions, I'd rather see us pursue this instead.


Cheers,
Simon


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


Re: Bang patterns

2013-02-07 Thread Simon Marlow

On 04/02/13 23:42, Ian Lynagh wrote:

On Mon, Feb 04, 2013 at 10:37:44PM +, Simon Peyton-Jones wrote:


I don't have a strong opinion about whether
f ! x y ! z = e
should mean the same; ie whether the space is significant.   I think it's 
probably more confusing if the space is significant (so its presence or absence 
makes a difference).


I also don't feel strongly, although I lean the other way:

I don't think anyone writes f ! x when they mean f with a strict
argument x, and I don't see any particular advantage in allowing it.
In fact, I think writing that is less clear than f !x, so there is an
advantage in disallowing it.

It also means that existing code that defines a (!) operator in infix
style would continue to work, provided it puts whitespace around the !.


FWIW, I really dislike whitespace-significant syntax.  f ! x should mean 
the same as f !x.  Look at the trouble we have with qualified operators: 
how many people have tried to write [Monday..] and been surprised that 
it doesn't work?


So I don't mind at all if BangPatterns makes it harder to write a 
definition of '!', because it's much more common to write bang patterns 
than it is to define '!', and the workaround of writing (!) is not that 
onerous.


Aside from preferring not to change the lexical syntax, I don't have a 
strong opinion. Your original third option, treating ! and ~ the same 
way, looks ok to me, but I also like the idea of only allowing bang 
patterns where they make sense (variables and pattern bindings).


Cheers,
Simon


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


Re: minor errors in Haskell 2010 report

2012-08-24 Thread Simon Marlow

On 23/08/2012 17:09, Ramana Kumar wrote:


M is not the current module, in which case the only way that an
entity could be in scope in the current module is if it was exported
by M and subsequently imported by the current module, so adding
exported by module M is superfluous.


In this case, what you said is not quite correct: an entity could be in
scope in the current module if it was defined in the current module, or
if it was imported from some other module (not M). These are the two
kinds of entity I thought of when I first read the sentence, and was
expecting clarification that only ones imported from M are to be considered.


That wouldn't be a clarification, it would be a change in the 
definition.  Remember that entities that are in scope as M.x might not 
come from module M.  Consider:


import X as M

now saying module M in the export list will export everything from X. 
 Furthermore, we can export many modules at the same time:


import X as M
import Y as M
import M

and then saying module M in the export list will export all of the 
entities from modules X, Y and M.


There was lots of discussion about this in the past, for some tricky 
issues see e.g.


http://www.haskell.org/pipermail/haskell/2001-August/007767.html
http://www.haskell.org/pipermail/cvs-ghc/2002-November/015880.html
http://www.haskell.org/pipermail/haskell/2002-November/010662.html

Cheers,
Simon


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


RE: String != [Char]

2012-03-26 Thread Simon Marlow
 The primary argument is to not break something that works well for most
 purposes, including teaching, at a huge cost of backwards compatibility
 for marginal if any real benefits.

I'm persuaded by this argument.  And I'm glad that teachers are speaking up in 
this debate - it's hard to get a balanced discussion on an obscure mailing list.

So I'm far from convinced that [Char] is a bad default for the String type.  
But it's important that as far as possible Text should not be a second class 
citizen, so I'd support adding OverloadedStrings to the language, and maybe 
looking at overloading some of the String APIs in the standard libraries.

Remember that FilePath is not part of the debate, since neither [Char] nor Text 
are correct representations of FilePath.

If we want to do an evaluation of the pedagogical value of [Char] vs. Text, I 
suggest writing something like a regex matcher in both and comparing the two.
 
One more thing: historically, performance considerations have been given a 
fairly low priority in the language design process for Haskell, and rightly so. 
 That doesn't mean performance has been ignored altogether (for example, seq), 
but it is almost never the case that a concession in other language design 
principles (e.g. consistency, simplicity) is made for performance reasons 
alone.  We should remember, when thinking about changes to Haskell, that 
Haskell is the way it is because of this uncompromising attitude, and we should 
be glad that Haskell is not burdened with (many) legacy warts that were 
invented to work around performance problems that no longer exist.  I'm not 
saying that this means we should ignore Text as a performance hack, just that 
performance should not come at the expense of good language design.

Cheers,
Simon



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


RE: String != [Char]

2012-03-20 Thread Simon Marlow
 On Mon, Mar 19, 2012 at 9:02 AM, Christian Siefkes christ...@siefkes.net
 wrote:
  On 03/19/2012 04:53 PM, Johan Tibell wrote:
  I've been thinking about this question as well. How about
 
  class IsString s where
      unpackCString :: Ptr Word8 - CSize - s
 
  What's the Ptr Word8 supposed to contain? A UTF-8 encoded string?
 
 Yes.
 
 We could make a distinction between byte and Unicode literals and have:
 
 class IsBytes a where
 unpackBytes :: Ptr Word8 - Int - a
 
 class IsText a where
 unpackText :: Ptr Word8 - Int - a
 
 In the latter the caller guarantees that the passed in pointer points to
 wellformed UTF-8 data.

Is there a reason not to put all these methods in the IsString class, with 
appropriate default definitions?  You would need a UTF-8 encoder ( decoder) of 
course, but it would reduce the burden on clients and improve backwards 
compatibility.

Cheers,
Simon



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


RE: What is a punctuation character?

2012-03-19 Thread Simon Marlow
 On Fri, Mar 16, 2012 at 6:49 PM, Ian Lynagh ig...@earth.li wrote:
  Hi Gaby,
 
  On Fri, Mar 16, 2012 at 06:29:24PM -0500, Gabriel Dos Reis wrote:
 
  OK, thanks!  I guess a take away from this discussion is that what is
  a punctuation is far less well defined than it appears...
 
  I'm not really sure what you're asking. Haskell's uniSymbol includes
  all Unicode characters (should that be codepoints? I'm not a Unicode
  expert) in the punctuation category; I'm not sure what the best
  reference is, but e.g. table 12 in
     http://www.unicode.org/reports/tr44/tr44-8.html#Property_Values
  lists a number of Px categories, and a meta-category P Punctuation.
 
 
  Thanks
  Ian
 
 
 Hi Ian,
 
 I guess what I am asking was partly summarized in Iavor's message.
 
 For me, the issue started with bullet number 4 in section 1.1
 
  http://www.haskell.org/onlinereport/intro.html#sect1.1
 
 which states that:
 
The lexical structure captures the concrete representation
of Haskell programs in text files.
 
 That combined with the opening section 2.1 (e.g. example of terminal
 syntax) and the fact that the grammar  routinely described two non-
 terminals ascXXX (for ASCII characters) and uniXXX for (Unicode character)
 suggested that the concrete syntax of Haskell programs in text files is in
 ASCII charset.  Note this does not conflict with the general statement
 that Haskell programs use the Unicode character because the uniXXX could
 use the ASCII charset to introduce Unicode characters -- this is not
 uncommon practice for programming languages using Unicode characters; see
 the link I gave earlier.
 
 However, if I understand Malcolm's message correctly, this is not the
 case.
 Contrary to what I quoted above, Chapter 2 does NOT specify the concrete
 representation of Haskell programs in text files.  What it does is to
 capture the structure of what is obtained from interpreting, *in some
 unspecified encoding or unspecified alphabet*,  the concrete
 representation of Haskell programs in text files.  This conclusion is
 unfortunate, but I believe it is correct.
 Since the encoding or the alphabet is unspecified, it is no longer
 necessarily the case that two Haskell implementations would agree on the
 same lexical interpretation when presented with the same exact text file
 containing  a Haskell program.
 
 In its current form, you are correct that the Report should say
 codepoint
 instead of characters.
 
 I join Iavor's request in clarifying the alphabet used in the grammar.

The report gives meaning to a sequence of codepoints only, it says nothing 
about how that sequence of codepoints is represented as a string of bytes in a 
file, nor does it say anything about what those files are called, or even 
whether there are files at all.

Perhaps some clarification is in order in a future revision, and we should use 
the correct terminology where appropriate.  We should also clarify that 
punctuation means exactly the Punctuation class.

With regards to normalisation and equivalence, my understanding is that Haskell 
does not support either: two identifiers are equal if and only if they are 
represented by the same sequence of codepoints.  Again, we could add a 
clarifying sentence to the report.

Cheers,
Simon



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


Re: Small report fixes

2010-12-23 Thread Simon Marlow

On 20/11/10 01:01, Ian Lynagh wrote:


I've made a couple of tickets for small fixes to the report:

http://hackage.haskell.org/trac/haskell-prime/ticket/140
http://hackage.haskell.org/trac/haskell-prime/ticket/141


I wonder if we ought to have a more lightweight process for these kind 
of changes.  I made many such fixes while editing the Haskell 2010 
report, and I've made a few minor fixes since, all the history is in the 
darcs repo.


Perhaps just 'darcs send' to the current or previous editor, and get the 
patch applied to the repo?


Cheers,
Simon

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


Re: ExplicitForAll complete

2010-12-23 Thread Simon Marlow

On 22/11/10 11:41, Ian Lynagh wrote:


Hi Iavor,

Thanks for your comments.

On Sun, Nov 21, 2010 at 06:25:38PM -0800, Iavor Diatchki wrote:


* Why is forall promoted to a keyword, rather then just being
special in types as is in all implementations?  I like the current
status quo where forall can still be used in value expressions.


You can't use case as a type variable, so I don't see why you should
be able to use forall as an expression variable.

I imagine that the reason implementations currently allow it is to
minimise the chance of an extension breaking existing programs, but I
believe that when making new versions of the standard we should, where
feasible, write them in the way that they would have been written if the
previous versions had never existed.


We tend not to make new global keywords when we can avoid doing so. 
'hiding', 'qualified', 'as', 'safe', 'unsafe', 'dynamic' etc. are all 
examples of identifiers interpreted as keywords only in certain 
contexts.  I don't think it's feasible to allow 'case' as a type 
variable, but it's certainly feasible to allow 'forall' as a term variable.


On the other hand, it makes life difficult for syntax highlighters.

Cheers,
Simon

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


Re: prefix operators

2010-07-13 Thread Simon Marlow

On 10/07/2010 22:02, John Meacham wrote:

On Fri, Jul 09, 2010 at 09:33:52AM +0100, Simon Marlow wrote:

On 08/07/2010 09:45, John Meacham wrote:

On Thu, Jul 08, 2010 at 07:09:29AM +, Simon Peyton-Jones wrote:

(ie as infix operators) and I have to squizzle around to re-interpret them as 
prefix operators.  Not very cool.  Something unified would be a Good Thing.


So, after thinking about it some, I think there may be a somewhat
elegant solution.


I like the sound of it.  I put the code for the Haskell 2010 fixity
resolver together with a little testing framework in the haskell-prime
repo:

   http://darcs.haskell.org/haskell-prime



There is also my one-pass layout algorithm that requires no interaction
with the parser that I believe still has promise. It was able to
properly layout all the wild code I threw at it (all of nofib). With the
addition of that, we may achieve the holy grail of fully independent
lexing,layout,parsing,and fixing of haskell code, and a specification
that has a direct correspondence to an implementable algorithm!

I actually just noticed that my layout code is now implemented in ghc:
http://hackage.haskell.org/trac/haskell-prime/wiki/AlternativeLayoutRule
I am curious what the results will be, I know that adding pattern guards
to it would be complicated, I will have to check out how my algorithm
was modified.


Yes, Ian Lynagh implemented your algorithm in GHC (with several tweaks 
to implement some of the darker corner cases, I believe).  There's also 
-XAlternativeLayoutRuleTransitional but I'm not sure what that does.


There are cases that you can't reasonably handle this way, e.g.

g = (let x, y :: Int; (x,y) = (1,2) in x, 3)
f xs = [ do x | x - xs ]

My feeling is that if we were to do layout this way it would have to be 
a simplified version of the current algorithm, so that it is easy to 
explain both to users and in the report.  Perhaps restricting the tokens 
that can prematurely end a layout context to just the important ones, 
like ) ] } 'in'.


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


Re: fixity resolution

2010-07-08 Thread Simon Marlow

On 07/07/2010 18:03, Christian Maeder wrote:

Simon Marlow schrieb:
[...]

1. - 1 * 1 is accepted as legal pattern, but differently resolved for
expressions! Should one not reject these (rare) patterns, too?


That's the GHC bug, right?


Yes!


Just a meta point, but it would help me a great deal if you could 
clearly separate discussion of what GHC does from discussion of the 
standard, i.e. by using the different mailing lists.



2. I would rather allow 1 * - 1 and 1 + - 1 to be legal as
expressions (with its unambiguous interpretation).


Yes, me too, but that's a matter for a new proposal.


3. Associativity should not matter for the non-binary -!

So the following resolutions are possible:

1 + - 2 + 3 ~~~   (1 + -2) + 3
1 + - 2 * 3 ~~~   1 + -(2 * 3)

infix 6 ##  -- same precedence like + but different associativity

- 1 ## 2 ~~~   (-1) ## 2


Yes, again I agree.  The current fixity resolution is more strict than
it needs to be.  The intention in Haskell 2010 was not to change the way
fixity resolution worked, but rather to avoid the problems caused by
having it as part of the grammar.


The grammar (in particular an ambiguous one) describes a superset of the
language and need not change with a changed fixity resolution (or type
analysis).


Please make a proposal (or proposals), then we can discuss exactly the 
changes you'd like to make.


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


Re: Second draft of the Haskell 2010 report available

2010-07-07 Thread Simon Marlow

On 06/07/2010 13:17, Christian Maeder wrote:


http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch3.html

infixexp →  lexp qop infixexp (infix operator application)
|   - infixexp(prefix negation)
|   lexp

This grammar rule describes a right associative nesting of (any) infix
operators qop and prefix negation as binding weaker than any infix.

Thus a parser would create from - 1 /= 1  a the tree
  - (1 /= (1  a)).


The grammar is non-ambiguous and all you have to do is flatten the 
result to apply fixity resolution.  I don't really see how generalising 
the grammar would help - the tree still has to be flattened to apply 
fixity resolution, and the parser would have to make an arbitrary choice 
from one of the possible parses.  Or perhaps I'm missing something here?


Cheers,
Simon




Would it not be better to give an ambiguous grammar and leave it to the
infix resolution algorithm to allow only the intended trees, rather than
letting the infix resolution algorithm correct a wrong tree?

My suggestion would be to change the rule to:

infixexp →  infixexp qop infixexp (infix operator application)
|   - infixexp(prefix negation)
|   lexp

thus only replacing the first lexp by infixexp.

Cheers Christian

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


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


Re: fixity resolution

2010-07-07 Thread Simon Marlow

On 07/07/2010 15:56, Christian Maeder wrote:

Simon Marlow schrieb:

The string 1 * - 1 is legal as pattern, but rejected as expression!


Well, it's not a pattern (* is a varop, not a conop), and it's an
illegal funlhs (* has greater precedence than prefix -).


it is legal as funlhs (ghc-6.12.3)!

1 * - 1 = 2


Main  1 Main.* (-1)
2


Well, that's a bug in GHC, not the Haskell report :-)


see also:
http://hackage.haskell.org/trac/ghc/ticket/4176


Thanks for reporting it.

Cheers,
Simon




Christian




Furthermore fixity resolution does not distinguish between constructors
and other operators as it should according to the grammar:

pat  → lpat qconop pat  (infix constructor)
 | lpat


funlhs  → var apat { apat }
 | pat varop pat
 | ( funlhs ) apat { apat }


a : b * c : d = undefined is currently rejected with:

cannot mix `:' [infixr 5] and `Main.*' [infixl 9] in the same infix
expression

but should be fine by the given grammar (rule pat varop pat).


The grammar specifies a superset of the language; fixity resolution may
reject something that is legal according to the grammar.  That's the
change we made in Haskell 2010: the grammar no longer attempts to
describe the language precisely with respect to fixity resolution, for
good reasons
(http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution).

See section 4.4.3.1  Function bindings:


Note that fixity resolution applies to the infix variants of the
function binding in the same way as for expressions (Section 10.6).
Applying fixity resolution to the left side of the equals in a function
binding must leave the varop being defined at the top level. For
example, if we are defining a new operator ## with precedence 6, then
this definition would be illegal:
   a ## b : xs = exp

because : has precedence 5, so the left hand side resolves to (a ## x) :
xs, and this cannot be a pattern binding because (a ## x) is not a valid
pattern.



Perhaps this could be clearer, please do suggest improvements.



P.S. like in my proposal for infixexp I would change pat to:

pat  → pat qconop pat  (infix constructor)
 | lpat


is there any need to do that?  The grammar is non-ambiguous right now.

Cheers,
 Simon


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


Re: [Haskell] Second draft of the Haskell 2010 report available

2010-06-30 Thread Simon Marlow

On 29/06/2010 23:31, Henk-Jan van Tuyl wrote:

On Tue, 29 Jun 2010 17:01:54 +0200, Simon Marlow marlo...@gmail.com
wrote:


Comments on the draft report are welcome, before I finalise this and
sign off on Haskell 2010.


Subsection 12.3, Language extensions, mentions the FFI as a language
extension, but FFI is now part of the standerd; the same goes for the
extensions mentioned at the end of the subsection.


Thanks; changed to refer to them as language features rather than 
extensions.


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


Re: Second draft of the Haskell 2010 report available

2010-06-30 Thread Simon Marlow

On 29/06/2010 16:38, malcolm.wallace wrote:

In Foreign.C.Error, the table of values of errno causes an unfortunate
page break, and it overflows the fresh page as well. (As in, some values
are invisible beyond the bottom of the page, rather than flowing onto
the next.)


Well spotted, thanks.  Now fixed.

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


Second draft of the Haskell 2010 report available

2010-06-29 Thread Simon Marlow
The second draft of the Haskell 2010 report is now available in PDF and 
HTML formats (the PDF looks a lot nicer):


http://www.haskell.org/~simonmar/haskell-2010-draft-report-2.pdf
http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskell.html

relative to the first draft, which was only publicised on the 
haskell-prime mailing list, I have now updated the libraries too. 
Rather than update all the library documentation manually, I (perhaps 
rashly) decided to make a LaTeX backend for Haddock instead, and 
generate the report automatically from the library source code.  Getting 
this to work turned out to be a lot more effort than I anticipated, but 
I think the results are quite attractive.  Once the new Haddock backend 
is incorporated upstream, we'll finally have the ability to generate 
decent typeset API documentation.  Furthermore, this should make it much 
easier to incorporate more libraries in future versions of the Haskell 
standard, should we decide to do so.


Right now, the HTML version of the report is generated from the LaTeX 
sources, including the libraries.  We could use the Haddock HTML output 
instead, but that would entail some difficulties with cross-references 
from the language part of the report to the libraries, which is why I've 
left it this way for now.  This is why the libraries part of the report 
is bereft of hyperlinks in HTML; but at least it is well indexed in the 
PDF version.


Summary of the library changes in Haskell 2010 relative to Haskell 98 
and the FFI specification:


 * All libraries have been updated to their hierarchical names

 * The following library modules were dropped from the standard, due to
   being obsolete or superseded.  Replacements are not part of the
   standard yet, but it is expected that they will be replaced in the
   future:

   Directory, System, Time, Locale, CPUTime, Random

   In the case of System, some functions have moved to
   the new modules System.Environment and System.Exit.

 * Foreign.Marshal.Error: functions on IOError moved to System.Error
   (this is where they've been in base for ever).

 * Data.List: added intercalate, subsequences, permutations, foldl',
   foldl1', stripPrefix (H2010 Data.List matches the current base
   version).

 * Data.Char: various additions of Unicode predicates (e.g. isLetter,
   isMark, isNumber), the GeneralCategory type and generalCategory.
   (matches the base version)

 * Control.Monad: added forM, forM_, (=), (=), forever, foldM_,
   replicateM, replicateM_ (matches the base version).

 * System.IO: added fixIO, hSetFileSize, hTell, hIsTerminalDevice,
   hSetEcho, hGetEcho, hShow.  The base version has various additions:
   hGetBuf/hPutBuf, binary Handles, encodings, and newline support,
   but I erred on the side of being conservative here: these APIs
   need discussion, and in some cases are probably not suitable
   for the standard in their current state at all.

 * System.IO.Error: new module, providing functionality that was
   in Foreign.Marshal.Error in the FFI spec.

 * System.IO.Exit: new module, functionality moved from H98 System
 * System.Environment: new module, functionality moved from H98 System


We expect to provide exactly these libraries in GHC 6.14, although the 
exact mechanism has yet to be decided; for discussion see


http://www.haskell.org/pipermail/haskell-prime/2010-April/003158.html


Comments on the draft report are welcome, before I finalise this and 
sign off on Haskell 2010.


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


Re: Haskell 2010 draft report

2010-05-04 Thread Simon Marlow

On 30/04/2010 17:58, Sean Leather wrote:

I'd appreciate a few more eyes over this, in particular look out for
messed up typesetting as there could still be a few bugs lurking.


In the HTML version, there are a few cases where section numbers are
missing from the subsection headers in the TOC. I see at least 11 and 22.


I wish I knew why this happened.  It always seems to be chapters 11 and 22.


In the PDF, is there any possibility of formatting the entries in the
TOC as links to the text?


Good idea - done.

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


Re: Haskell 2010 draft report

2010-05-04 Thread Simon Marlow

On 01/05/2010 13:18, Ian Lynagh wrote:

On Fri, Apr 30, 2010 at 05:05:17PM +0100, Simon Marlow wrote:

I've completed most of the edits to the Haskell 98 report for Haskell
2010, modulo the changes to the libraries that we still have to resolve.

I cleaned up various other things I discovered along the way, and tidied
up the typesetting.  I've also made a much nicer HTML rendering of the
report using TeX4ht, which means we can ditch the old 1500 lines of
hacked up Haskell code which used to do the HTML conversion before.

You can see the draft report here, in PDF and online HTML respectively:

http://www.haskell.org/~simonmar/haskell-2010-draft-report.pdf
http://www.haskell.org/~simonmar/haskell-2010-draft-report/haskell.html

In the PDF you'll notice that the bits that changed in Haskell 2010
relative to Haskell 98 are purple (except for the FFI chapter).
Unfortunately I haven't yet managed to make this work in the HTML
version, but it ought to be possible.

I'd appreciate a few more eyes over this, in particular look out for
messed up typesetting as there could still be a few bugs lurking.


In the PDF:

p37: guard  --   pat- infixexp
  Is that really meant to be infixexp, not exp? GHC accepts:
  foo
   | True- True :: Bool
   = 'a'

p37: Hmm, likewise guard  --   infixexp. GHC accepts
  foo
   | True :: Bool
   = 'a'
  but hugs doesn't (unexpected `::'). So I guess these are both
  just GHC bugs, although I wonder why the report isn't more liberal.


See the bottom of 3.13:


A note about parsing. The expression
  case x of { (a,_) | let b = not a in b :: Bool - a }

is tricky to parse correctly. It has a single unambiguous parse, namely
  case x of { (a,_) | (let b = not a in b :: Bool) - a }

However, the phrase Bool - a is syntactically valid as a type, and 
parsers with limited lookahead may incorrectly commit to this choice, 
and hence reject the program. Programmers are advised, therefore, to 
avoid guards that end with a type signature — indeed that is why a guard 
contains an infixexp not an exp.




In Haskell 98 we had

  gd - | exp^0

where exp^0 is now called infixexp, so I kept things as they were.

Arguably using infixexp here is only a partial fix for the parsing 
problem described above, and so it might be better not to try to fix the 
problem at all.  Either way though, GHC will be wrong.



p42: The negative literal alternative in pat is redundant


well spotted, thanks.


p47: I'm not sure I see the reason for this change. It seems to just
  make it more complicated. If the change is made, should say y is a
  new variable.
  I don't know if the colouring is important, but there's a black y
  that should be purple, and two purple _ - that should be black,


Agreed, I've reverted that.


p47: Case (h) is alone in ending in a full stop

p48: Case s, again I don't see the point of the y binding


Fixed.  Thanks!

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


Re: Haskell 2010 draft report

2010-05-04 Thread Simon Marlow

On 02/05/2010 13:57, Ian Lynagh wrote:

On Fri, Apr 30, 2010 at 05:05:17PM +0100, Simon Marlow wrote:


I'd appreciate a few more eyes over this, in particular look out for
messed up typesetting as there could still be a few bugs lurking.


In the PDF:

p129-137: A program can only contain a modid as part of a
   qvarid, ..., qconsym, but e.g. a module needs a
   bare modid. May be best to defer fixing this, and
   tidy up the syntax definition in H2011.

p152: There's a huge amount of whitespace between dclass and inst

p153: Same guard  --   pat- infixexp comment as on p37 (GHC bug?).
p153: Same guard  --   infixexp comment as on p37 (GHC bug?).

p153: RHS of gdrhs production should be purple (as on p66)

p154: As on p42, the negative literal alternative in pat is redundant

p156: The argument to resolve doesn't have to strictly alternate, e.g.
   id $ - three.

p156: The program needs an import Control.Monad
p156: The program should derive Show for everything

p157: In one case (in the penultimate paragraph) - is quoted and short,
   while earlier uses are bare and long.


All fixed, thanks.


p159: Is this legal?:
   {-# LANGUAGE EmptyDataDecls #-}
   data Foo
   deriving ()
   GHC accepts it, but hugs says (unexpected keyword deriving)


Yes, it's legal according to the grammar.

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


Re: Haskell 2010 libraries

2010-05-02 Thread Simon Marlow

On 01/05/10 20:17, Ian Lynagh wrote:

On Sat, May 01, 2010 at 08:05:58PM +0100, Simon Marlow wrote:

On 01/05/10 17:16, Ian Lynagh wrote:


So it seems this is closer to option (2) in my message, because
portablebase and haskell2010 overlap, and are therefore mutually
exclusive, whereas in (4) haskell2010 and base2010 are non-overlapping -
that's the crucial difference.


If they are non-overlapping, how would a new Data.List function be
added? Or an existing Data.List function be altered?


In this scenario there would be base as it is now, and base2010 (or
whatever you want to call it) that is base minus the modules in
haskell2010.  So you can add things to base:Data.List, but
haskell2010:Data.List must export exactly the API as specified in the
report.


So someone using haskell2010+base2010 wouldn't be able to use this new
function?


Correct.  If you opt to use the Haskell 2010 API, you don't get to see 
new additions made to those modules, but that's entirely reasonable.


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


Re: Haskell 2010 libraries

2010-05-01 Thread Simon Marlow

On 01/05/10 17:16, Ian Lynagh wrote:


So it seems this is closer to option (2) in my message, because
portablebase and haskell2010 overlap, and are therefore mutually
exclusive, whereas in (4) haskell2010 and base2010 are non-overlapping -
that's the crucial difference.


If they are non-overlapping, how would a new Data.List function be
added? Or an existing Data.List function be altered?


In this scenario there would be base as it is now, and base2010 (or 
whatever you want to call it) that is base minus the modules in 
haskell2010.  So you can add things to base:Data.List, but 
haskell2010:Data.List must export exactly the API as specified in the 
report.



No matter what solution is chosen, changes to datatypes or classes seem
likely to be troublesome.


Yes, that's true. Adding methods to classes is possible, but adding 
constructors to datatypes, or new instances, is not.



I think the library change plans are underdeveloped, the libraries
should be unchanged in H2010, and we should resolve this issue before
changing them in a future language revision. That would keep other
options open, such as the report standardising Haskell2011.Data.List
rather than Data.List, etc.


FWIW, I omitted mentioning that option because I think it's the worst of 
the bunch :-)  I think that putting version numbers into module names is 
a very dangerous thing to start doing.  When you want to upgrade your 
code to Haskell 2011, you have to change not just the .cabal file but 
all the imports too.  Keeping version dependencies collected together in 
one place and not scattered through source code is one of the better 
design decisions we made, I believe.


Doing nothing as you suggest is an option, but it would mean using the 
non-hierarchical names for the FFI libraries.  There's nothing 
technically wrong with it, but I find it a bit odd to be standardising 
modules with names that in practice almost no code has ever used.  I 
suppose those are the names in the FFI addendum though.



I described this as a non-option because I thought trying to use the
packages together might be a common problem that leads to obscure error
messages about ambiguous modules, but perhaps it's not that bad, or at
least not worse than the other solutions.


Direct imports of base* and haskell* could be (dis)allowed by the
implementation depending on whether it is in Haskell 2010 mode or not.


Not sure what you mean here - modules are imported, not packages.  Type 
error!


It's the modules that overlap between the two packages that are the 
problem.  If someone imports Data.List, do they mean the haskell2010 or 
the base one?  If you're suggesting that we choose based on whether the 
flag -fhaskell2010 is set, then that really amounts to the haskell2010 
package shadowing base when -fhaskell2010 is on.  It might be the right 
thing, but it's a slightly ugly special case.



We hope in the future that the set of libraries standardised in the
report grows beyond what we have in base currently


Oh, I thought the plan was for library standardisation in the report to
be reduced, with perhaps the Haskell Platform becoming the new library
standardisation effort.


I thought the *eventual* plan was to properly standardise lots of 
libraries, with the Haskell Platform being an intermediate step on the 
way to standardisation. Though I don't think we ever actually decided 
anything, really.


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


Re: Haskell 2010 libraries

2010-05-01 Thread Simon Marlow

On 30/04/10 23:52, Felipe Lessa wrote:

On Fri, Apr 30, 2010 at 09:37:39PM +0100, Simon Marlow wrote:

I like the picture where we have a small base, lots of independent
packages, and one or more haskell20xx packages that re-exports all
the standardised stuff from the other packages.  This arrangement
extends smoothly, the only problem is that haskell20xx overlaps with
the other packages.


I wonder how much pain will there be when Haskell 2011 comes out.
Some packages will depend on haskell2010, and others on
haskell2011.  Will they integrate and compile fine?

If haskell2010 is a metapackage that says

   Depends: base == X.Y.*

and haskell2011 is another metapackage that says

   Depends: base == Z.W.*

then I think we're going to have big problems.  Sorry if this is
a resolved issue. :)


That won't be a problem, for the same reasons that we can happily mix 
packages that depend on base-3 with packages that depend on base-4 right 
now.


That is, unless Haskell 2011 decides to make some incompatible changes 
to datatypes or classes, as Ian pointed out.


Cheers,
Simon

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


Haskell 2010 libraries

2010-04-30 Thread Simon Marlow

Hi Folks,

I'm editing the Haskell 2010 report right now, and trying to decide what 
to do about the libraries.  During the Haskell 2010 process the 
committee agreed that the libraries in the report should be updated, 
using the current hierarchical names, adding new functionality from the 
current base package, and dropping some of the H'98 library modules that 
now have better alternatives.


In Haskell 2010 we're also adding the FFI modules.  The FFI addendum 
used non-hierarchical names (CForeign, MarshalAlloc etc.) but these are 
usually known by their hierarchical names nowadays: e.g. Foreign.C, 
Foreign.Marshal.Alloc.  It would seem strange to add the 
non-hierarchical names to the Haskell language report.


So this is all fine from the point of view of the Haskell report - I can 
certainly update the report to use the hierarchical module names, but 
that presents us with one or two problems in the implementation.


The obvious thing to do would be to make a haskell2010 package that 
re-exports the appropriate modules from base, providing a fixed API that 
people can depend on when they write Haskell 2010 code.  However, what 
happens when someone wants to write some code that uses Haskell 2010 
libraries, but also uses something else from base, say 
Control.Concurrent?  The modules from haskell2010 overlap with those 
from base, so all the imports of Haskell 2010 modules will be ambiguous. 
 The Prelude is a bit of a thorny issue too: currently it is in base, 
but we would have to move it to haskell2010.


Bear in mind these goals: we want to

  a. support writing code that is Haskell 2010 only: it only uses
 Haskell 2010 language features and modules.

  b. not break existing code as far as possible

  c. whatever we do should extend smoothly when H'2011 makes
 further changes, and so on.

Here are some non-options:

  1. Not have a haskell2010 package.  We lose (a) above, and we
 lose the ability to add or change the API for these modules,
 in base, since they have to conform to the H'2010 spec.  If
 H'2011 makes any changes to these modules, we're really stuck.

  2. As described above: you can either use haskell2010, or base,
 but not both.  It would be painful to use haskell2010 in
 GHCi, none of the base modules would be available.

Here are some options:

  3. allow packages to shadow each other, so haskell2010 shadows
 base.  This is a tantalising possibility, but I don't have
 any idea what it would look like, e.g. should the client or
 the package provider specify shadowing?

  4. Provide a haskell2010 package and a base2010 package that
 re-exports all of base except the modules that overlap with
 haskell2010.  You can either use haskell2010,
 haskell2010+base2010, or base.  This is a bit like (1), but
 avoids the need for shadowing by using package re-exports,
 on the other hand confusion could well arise due to the
 strange base2010 package, and some people would surely try
 to use haskell2010 + base and run into difficulties.

  5. Not have a haskell2010 package, but have the report say that
 implementations are allowed to add things to the standard
 libraries.

Thoughts?  Better ideas?

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


Re: Haskell 2010 libraries

2010-04-30 Thread Simon Marlow

On 30/04/10 13:19, Malcolm Wallace wrote:

4. Provide a haskell2010 package and a base2010 package that
re-exports all of base except the modules that overlap with
haskell2010. You can either use haskell2010,
haskell2010+base2010, or base. This is a bit like (1), but
avoids the need for shadowing by using package re-exports,
on the other hand confusion could well arise due to the
strange base2010 package, and some people would surely try
to use haskell2010 + base and run into difficulties.


In many ways this corresponds to my preferred solution, although I would
rephrase it thus:

* Deprecate use of the base package, (I do not mean to remove base,
just to freeze it, and discourage its general use.)
* Create a new haskell2010 package (for ghc this will be built on topcommon
of base, but other compilers might make a different choice).
* Create a new portablebase package which contains (or re-exports)
all of the remaining useful and portable parts of the current base
_and_ haskell2010.
* Create a new ghcextras package which re-exports (or defines afresh)
all of the useful but non-portable parts of the current base.


So it seems this is closer to option (2) in my message, because 
portablebase and haskell2010 overlap, and are therefore mutually 
exclusive, whereas in (4) haskell2010 and base2010 are non-overlapping - 
that's the crucial difference.


I described this as a non-option because I thought trying to use the 
packages together might be a common problem that leads to obscure error 
messages about ambiguous modules, but perhaps it's not that bad, or at 
least not worse than the other solutions.


I think we can leave the question of whether to abstract the existing 
base into separate portablebase and ghcextras packages as a separate 
issue - there are merits to doing something like this for sure, but I'd 
like to focus specifically on Haskell 2010, and I think 
portablebase/ghcextras are orthogonal.



Because I suggest that portablebase re-export the haskell2010 API in
its entirety, it would be impossible to use both packages explicitly at
the same time from a single module - users would need to choose one or
the other. Also, packages which currently depend on base should be
encouraged to upgrade to a dependency on haskell2010 rather than on
portablebase, if possible, because it provides greater stability of
interface.


We hope in the future that the set of libraries standardised in the 
report grows beyond what we have in base currently, so I'm not sure how 
much sense it makes for portablebase to re-export the haskell20xx 
modules.  Generally speaking we've been tyring to make base smaller 
rather than larger.  Indeed right now there are some modules in the 
report that aren't in base, although those are the ones we're 
considering removing in this iteration.


I like the picture where we have a small base, lots of independent 
packages, and one or more haskell20xx packages that re-exports all the 
standardised stuff from the other packages.  This arrangement extends 
smoothly, the only problem is that haskell20xx overlaps with the other 
packages.



5. Not have a haskell2010 package, but have the report say that
implementations are allowed to add things to the standard
libraries.


This seems superficially attractive, but I think it would be impossible
in practice to guarantee anything. For instance, the semantics of take
and drop changed between Haskell 1.4 and Haskell'98 iirc, with no
corresponding change in the API. With separate packages it is possible
to retain and choose between both sets of semantics.


Yes, I agree - that's a non starter.

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


Re: Deprecating haskell98 module aliases

2010-03-17 Thread Simon Marlow

On 09/03/2010 12:11, Malcolm Wallace wrote:

And regarding guest's comments, doesn't the Haskell 2010 standard[1]
count as an actual language standard? If not, then what is it and
why isn't it one?


Haskell 2010 has been decided, but the Language Report itself has not
yet been published. So yes, it is a standard, but not one you can refer
to (yet).

IIRC, H'2010 makes no changes to the Libraries section of the Report.
There was a proposal for 2010 to update the names of the libraries, to
their new hierarchical forms. It was not accepted. Thus, the Haskell'98
names are still part of the official 2010 language standard, if I am not
mistaken.


The discussion didn't result in a concrete proposal, but there was 
general agreement that we should remove


 Directory
 System
 Time
 Locale
 CPUTime
 Random

and update the others to use hierarchical names:

1. Ratio keep as Data.Ratio
2. Complex   keep as Data.Complex
3. Numeric   keep as Numeric (?)
4. Ixkeep as Data.Ix
5. Array keep as Data.Array
6. List  keep as Data.List
7. Maybe keep as Data.Maybe
8. Char  keep as Data.Char
9. Monad keep as Control.Monad
   10. IOkeep as System.IO

and the FFI libraries would be added as

   CError   - Foreign.C.Error
   CForeign - Foreign.C
   CString  - Foreign.C.C.String
   CTypes   - Foreign.C.Types
   ForeignPtr   - Foreign.ForeignPtr
   Int  - Data.Int
   MarshalAlloc - Foreign.Marshal.Alloc
   MarshalArray - Foreign.Marshal.Array
   MarshalError - Foreign.Marshal.Error
   MarshalUtils - Foreign.Marshal.Utils
   StablePtr- Foreign.StablePtr
   Storable - Foreign.Storable
   Word - Data.Word

(this proposal wasn't discussed publicly, unfortunately.  I think that 
was an oversight.)


I was actually planning to look at doing this during the H2010 report 
update. However, updating the libraries in the report to use the 
hierarchical names actually gives us a slight problem, in that we then 
have to provide those modules with exactly those interfaces for ever, 
presumably via some well-known package.  The module names overlap with 
base, so we'd have to do some package reorganisation.  Things could get 
painful really fast.  I'm tempted to not do this in H2010, but defer it 
until we've really thought about how to manage the transition and future 
updates.


I would like to remove the old superseded modules though: Directory, 
Time, System, Random, Locale, CPUTime.  That would be an easy change, 
and we can provide a haskell2010 package exporting just the remaining 
modules.


Cheers,
Simon

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


Re: PROPOSAL: Include record puns in Haskell 2011

2010-02-24 Thread Simon Marlow

On 24/02/10 18:23, Ian Lynagh wrote:

On Tue, Feb 23, 2010 at 07:07:30PM -0800, Iavor Diatchki wrote:


I'd like to propose that we add record punning to Haskell 2011.

Thoughts, objections, suggestions?


I have a feeling I'm in the minority, but I find record punning an ugly
feature.

Given
 data T = C { f :: Int }
we implicitly get
 f :: T -  Int
which punning shadows with
 f :: Int
whereas I generally avoid shadowing completely.


While I agree with these points, I was converted to record punning 
(actually record wildcards) when I rewrote the GHC IO library.  Handle 
is a record with 12 or so fields, and there are literally dozens of 
functions that start like this:


  flushWriteBuffer :: Handle - IO ()
  flushWriteBuffer Handle{..} = do

if I had to write out the field names I use each time, and even worse, 
think up names to bind to each of them, it would be hideous.


There are reasons to find this distasteful, yes, but I think the 
alternative is much worse.


I'm not proposing record wildcards (yet) *cough* labelled-field 
wildcards, but punning is a step in the right direction.


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


Re: Negation

2010-02-14 Thread Simon Marlow

On 14/02/10 02:21, Lennart Augustsson wrote:

I agree, I don't think this is a bug.  If the grammar actually says
that this is legal, then I think the grammar is wrong.


As far as I can tell Doitse is correct in that GHC does not implement 
the grammar, so it's either a bug in GHC or the grammar.  To fix it in 
the grammar would no doubt involve quite a bit of refactoring, I can't 
immediately see how to do it easily.


Cheers,
Simon



On Sun, Feb 14, 2010 at 1:48 AM, John Launchburyj...@galois.com  wrote:

I don't think this is a bug. I do not expect to be able to unfold a definition 
without some syntactic issues. For example,

two = 1+1
four = 2 * two

but unfolding fails (four = 2 * 1 + 1). In general, we expect to have to 
parenthesize things when unfolding them.

John


On Feb 13, 2010, at 11:56 AM, Simon Marlow wrote:


On 09/02/10 21:43, S. Doaitse Swierstra wrote:

One we start discussing syntax again it might be a good occasion to
reformulate/make more precise a few points.

The following program is accepted by the Utrecht Haskell Compiler (here
we took great effort to follow the report closely ;-} instead of
spending our time on n+k patterns), but not by the GHC and Hugs.

module Main where

-- this is a (rather elaborate) definition of the number 1
one = let x=1 in x

-- this is a definition of the successor function using section notation
increment = ( one + )

-- but if we now unfold the definition of one we get a parser error in GHC
increment' = ( let x=1 in x + )


Now that *is* an interesting example.  I had no idea we had a bug in that area. 
Seems to me that it ought to be possible to fix it by refactoring the grammar, 
but I haven't tried yet.

Are there any more of these that you know about?

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


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



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


Re: Negation

2010-02-13 Thread Simon Marlow

On 10/02/10 07:53, Atze Dijkstra wrote:


On 10 Feb, 2010, at 00:53 , Lennart Augustsson wrote:


Do you deal with this correctly as well:
case () of _ - 1==1==True


No, that is, in the same way as GHC  Hugs, by reporting an error.


Note that Haskell 2010 now specifies that expression to be a precedence 
parsing error, assuming that == is nonfix.


http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution

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


Re: Negation

2010-02-13 Thread Simon Marlow

On 09/02/10 21:43, S. Doaitse Swierstra wrote:

One we start discussing syntax again it might be a good occasion to
reformulate/make more precise a few points.

The following program is accepted by the Utrecht Haskell Compiler (here
we took great effort to follow the report closely ;-} instead of
spending our time on n+k patterns), but not by the GHC and Hugs.

module Main where

-- this is a (rather elaborate) definition of the number 1
one = let x=1 in x

-- this is a definition of the successor function using section notation
increment = ( one + )

-- but if we now unfold the definition of one we get a parser error in GHC
increment' = ( let x=1 in x + )


Now that *is* an interesting example.  I had no idea we had a bug in 
that area. Seems to me that it ought to be possible to fix it by 
refactoring the grammar, but I haven't tried yet.


Are there any more of these that you know about?

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


Re: Nominations for the Haskell 2011 committee

2009-12-30 Thread Simon Marlow
I also put myself forward for next year's committee, although I'm 
equally happy to stand down and make way for new members.


In any case I plan to continue working on proposals for Haskell 2011, 
perhaps we should be thinking about Concurrency for 2011?  There's 
already a draft of the report text that I wrote for Haskell Prime here:


http://hackage.haskell.org/trac/haskell-prime/wiki/Concurrency/DraftReportText

Cheers,
Simon

On 14/12/09 12:34, Simon Marlow wrote:

So that the Haskell 2011 cycle can get underway, we are soliciting
nominations for new committee members. Since this is the first time
we've done this, the procedure is still somewhat unsettled and things
may yet change, but the current guidelines are written down here:

http://hackage.haskell.org/trac/haskell-prime/wiki/Committee

In particular, on the makeup of the commitee:

The committee should represent each class of stakeholders with
roughly equal weight. These classes are

* Implementers (compiler/tool writers)
* Commercial users
* Non-commercial users (e.g. open source)
* Academic users (using Haskell in research)
* Teachers
* Authors

In addition, members of the committee should be long-standing users
with a deep knowledge of Haskell, and preferably with experience of
language design. The committee should contain at least some members
with a comprehensive knowledge of the dark corners of the Haskell
language design, who can offer perspective and rationale for existing
choices and comment on the ramifications of making different choices.


To nominate someone (which may be yourself), send a message to
haskell-pr...@haskell.org. Please give reasons for your nomination.

The current committee will appoint new commitee members and editors
starting in the new year, so the deadline for nominations is 31 December
2009.

During discussion amongst the current commitee, we realised that the
choice of committee should be informed not just by the criteria above,
but also by the particular proposals that are expected to be under
consideration during this cycle. With that in mind, we plan that
following the nominations the current committee will choose a core
commitee of up to 10 members, and further members may be appointed
during the year based on expertise needed to consider particular
proposals. Accordingly, now would be a good time to start discussing
which proposals should be considered in the Haskell 2011 timeframe, as
that may affect the choice of commitee members.

More details on the current Haskell Prime process are here:

http://hackage.haskell.org/trac/haskell-prime/wiki/Process


Cheers,
Simon


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


Nominations for the Haskell 2011 committee

2009-12-14 Thread Simon Marlow
So that the Haskell 2011 cycle can get underway, we are soliciting 
nominations for new committee members.  Since this is the first time 
we've done this, the procedure is still somewhat unsettled and things 
may yet change, but the current guidelines are written down here:


http://hackage.haskell.org/trac/haskell-prime/wiki/Committee

In particular, on the makeup of the commitee:

  The committee should represent each class of stakeholders with
  roughly equal weight. These classes are

* Implementers (compiler/tool writers)
* Commercial users
* Non-commercial users (e.g. open source)
* Academic users (using Haskell in research)
* Teachers
* Authors

  In addition, members of the committee should be long-standing users
  with a deep knowledge of Haskell, and preferably with experience of
  language design. The committee should contain at least some members
  with a comprehensive knowledge of the dark corners of the Haskell
  language design, who can offer perspective and rationale for existing
  choices and comment on the ramifications of making different choices.


To nominate someone (which may be yourself), send a message to 
haskell-pr...@haskell.org.  Please give reasons for your nomination.


The current committee will appoint new commitee members and editors 
starting in the new year, so the deadline for nominations is 31 December 
2009.


During discussion amongst the current commitee, we realised that the 
choice of committee should be informed not just by the criteria above, 
but also by the particular proposals that are expected to be under 
consideration during this cycle.  With that in mind, we plan that 
following the nominations the current committee will choose a core 
commitee of up to 10 members, and further members may be appointed 
during the year based on expertise needed to consider particular 
proposals.  Accordingly, now would be a good time to start discussing 
which proposals should be considered in the Haskell 2011 timeframe, as 
that may affect the choice of commitee members.


More details on the current Haskell Prime process are here:

http://hackage.haskell.org/trac/haskell-prime/wiki/Process


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


Re: On the Meaning of Haskell 6

2009-11-30 Thread Simon Marlow
This kind of discussion would be more appropriate on the haskell-cafe 
mailing list.  haskell-prime@haskell.org is specifically for discussing 
proposals for changes in future revisions of the Haskell language.


Thanks.

Simon

On 30/11/2009 08:46, John D. Earle wrote:

I have used the expression Forefathers of Haskell before. Someone
earlier wrote Haskell will die with the two Simons. Cruel words that
perhaps were not meant to be cruel per se, just a perceived fact. Making
the ancient sign with my hand that signifies my authority as a teacher
my response is as follows: One must master logic, but not be its slave.
In so many ways it is true, from dust to dust; but any earnest entreaty
upon this hallowed ground would involve a token of respect such as this.
We are fortunate that we have him. Let us not be neglectful for what we
have while we still have it!
In retrospect poor Simon may have said to himself, What! I'm not dead
and buried yet! What is this man saying! I'm not that old! Perhaps I
have caused him to chuckle privately. I would prefer the later.



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


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


Re: Unsafe hGetContents

2009-10-20 Thread Simon Marlow

On 10/10/2009 18:59, Iavor Diatchki wrote:

Hello,

well, I think that the fact that we seem to have a program context
that can distinguish f1 from f2 is worth discussing because I
would have thought that in a pure language they are interchangable.
The question is, does the context in Oleg's example really distinguish
between f1 and f2?  You seem to be saying that this is not the
case:  in both cases you end up with the same non-deterministic
program that reads two numbers from the standard input and subtracts
them but you can't assume anything about the order in which the
numbers are extracted from the input---it is merely an artifact of the
GHC implementation that with f1 the subtraction always happens the
one way, and with f2 it happens the other way.

I can (sort of) buy this argument, after all, it is quite similar to
what happens with asynchronous exceptions (f1 (error 1) (error 2)
vs f2 (error 1) (error 2)).  Still, the whole thing does not
smell right:  there is some impurity going on here, and trying to
offload the problem onto the IO monad only makes reasoning about IO
computations even harder (and it is petty hard to start with).  So,
discussion and alternative solutions should be strongly encouraged, I
think.


Duncan has found a definition of hGetContents that explains why it has 
surprising behaviour, and that's very nice because it lets us write the 
compilers that we want to write, and we get to tell the users to stop 
moaning because the strange behaviour they're experiencing is allowed 
according to the spec.  :-)


Of course, the problem is that users don't want the hGetContents that 
has non-deterministic semantics, they want a deterministic one.  And for 
that, they want to fix the evaluation order (or something).  The obvious 
drawback with fixing the evaluation order is that it ties the hands of 
the compiler developers, and makes a fundamental change to the language 
definition.


Things will get a lot worse in the future as we experiment with more 
elaborate compiler optimisations and evaluation strategies.  I predict 
that eventually we'll have to ditch hGetContents, at least in its 
current generality.


Cheers,
Simon


-Iavor







On Sat, Oct 10, 2009 at 7:38 AM, Duncan Coutts
duncan.cou...@googlemail.com  wrote:

On Sat, 2009-10-10 at 02:51 -0700, o...@okmij.org wrote:


The reason it's hard is that to demonstrate a difference you have to get
the lazy I/O to commute with some other I/O, and GHC will never do that.


The keyword here is GHC. I may well believe that GHC is able to divine
programmer's true intent and so it always does the right thing. But
writing in the language standard ``do what the version x.y.z of GHC
does'' does not seem very appropriate, or helpful to other
implementors.


With access to unsafeInterleaveIO it's fairly straightforward to show
that it is non-deterministic. These programs that bypass the safety
mechanisms on hGetContents just get us back to having access to the
non-deterministic semantics of unsafeInterleaveIO.


Haskell's IO library is carefully designed to not run into this
problem on its own.  It's normally not possible to get two Handles
with the same FD...



Is this behavior is specified somewhere, or is this just an artifact
of a particular GHC implementation?


It is in the Haskell 98 report, in the design of the IO library. It does
not not mention FDs of course. The IO/Handle functions it provides give
no (portable) way to obtain two read handles on the same OS file
descriptor. The hGetContents behaviour of semi-closing is to stop you
from getting two lazy lists of the same read Handle.

There's nothing semantically wrong with you bypassing those restrictions
(eg openFile /dev/fd/0) it just means you end up with a
non-deterministic IO program, which is something we typically try to
avoid.

I am a bit perplexed by this whole discussion. It seems to come down to
saying that unsafeInterleaveIO is non-deterministic and that things
implemented on top are also non-deterministic. The standard IO library
puts up some barriers to restrict the non-determinism, but if you walk
around the barrier then you can still find it. It's not clear to me what
is supposed to be surprising or alarming here.

Duncan

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



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


Re: Unsafe hGetContents

2009-10-12 Thread Simon Marlow

On 11/10/2009 09:26, Florian Weimer wrote:

* Simon Marlow:


Oleg's example is quite close, don't you think?

URL: http://www.haskell.org/pipermail/haskell/2009-March/021064.html


Ah yes, if you have two lazy input streams both referring to the same
underlying stream, that is enough to demonstrate a problem.  As for
whether Oleg's example is within the rules, it depends whether you
consider fdToHandle as unsafe:


Is relying on seq to show the difference allowed, according to your
rules on an insecurity proof?


Absolutely.


What about handles from System.Process?  Do they count as well?


Sure - we hopefully don't consider System.Process to be unsafe.

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


Re: Unsafe hGetContents

2009-10-06 Thread Simon Marlow

On 03/10/2009 19:59, Florian Weimer wrote:

* Nicolas Pouillard:


Excerpts from Florian Weimer's message of Wed Sep 16 22:17:08 +0200 2009:

Are there any plans to get rid of hGetContents and the semi-closed
handle state for Haskell Prime?

(I call hGetContents unsafe because it adds side effects to pattern
matching, stricly speaking invalidating most of the transformations
which are expected to be valid in a pure language.)


Would you consider something like [1] as an acceptable replacement?

[1]: http://hackage.haskell.org/package/safe-lazy-io


It only addresses two known issues with lazy I/O, doesn't it?  It
still injects input operations into pure code not in the IO monad.


While what you say is true, and I've complained about the same thing 
myself in the past, it turns out to be quite difficult to demonstrate 
the unsafety.


Try it!  Here's the rules.

  - write a program that gives different results when compiled with
different optimisation flags only. (one exception: you're not
allowed to take advantage of -fno-state-hack).

  - Using exceptions is not allowed (they're non-determinstic).

  - A difference caused by resources (e.g. stack overflow) doesn't
count.

  - The only unsafe operation you're allowed to use is hGetContents.

  - You're allowed to use any other I/O operations, including from
libraries, as long as they're not unsafe, and as long as the I/O
itself is deterministic.

The reason it's hard is that to demonstrate a difference you have to get 
the lazy I/O to commute with some other I/O, and GHC will never do that. 
 If you find a way to do it, then we'll probably consider it a bug in GHC.


You can get lazy I/O to commute with other lazy I/O, and perhaps with 
some cunning arrangement of pipes (or something) that might be a way to 
solve the puzzle.  Good luck!


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


Re: Unsafe hGetContents

2009-10-06 Thread Simon Marlow

On 06/10/2009 14:18, Nicolas Pouillard wrote:

Excerpts from Simon Marlow's message of Tue Oct 06 14:59:06 +0200 2009:

On 03/10/2009 19:59, Florian Weimer wrote:

* Nicolas Pouillard:


Excerpts from Florian Weimer's message of Wed Sep 16 22:17:08 +0200 2009:

Are there any plans to get rid of hGetContents and the semi-closed
handle state for Haskell Prime?

(I call hGetContents unsafe because it adds side effects to pattern
matching, stricly speaking invalidating most of the transformations
which are expected to be valid in a pure language.)


Would you consider something like [1] as an acceptable replacement?

[1]: http://hackage.haskell.org/package/safe-lazy-io


It only addresses two known issues with lazy I/O, doesn't it?  It
still injects input operations into pure code not in the IO monad.


While what you say is true, and I've complained about the same thing
myself in the past, it turns out to be quite difficult to demonstrate
the unsafety.

Try it!  Here's the rules.

- write a program that gives different results when compiled with
  different optimisation flags only. (one exception: you're not
  allowed to take advantage of -fno-state-hack).

- Using exceptions is not allowed (they're non-determinstic).

- A difference caused by resources (e.g. stack overflow) doesn't
  count.

- The only unsafe operation you're allowed to use is hGetContents.

- You're allowed to use any other I/O operations, including from
  libraries, as long as they're not unsafe, and as long as the I/O
  itself is deterministic.

The reason it's hard is that to demonstrate a difference you have to get
the lazy I/O to commute with some other I/O, and GHC will never do that.
   If you find a way to do it, then we'll probably consider it a bug in GHC.

You can get lazy I/O to commute with other lazy I/O, and perhaps with
some cunning arrangement of pipes (or something) that might be a way to
solve the puzzle.  Good luck!


Oleg's example is quite close, don't you think?

URL: http://www.haskell.org/pipermail/haskell/2009-March/021064.html


Ah yes, if you have two lazy input streams both referring to the same 
underlying stream, that is enough to demonstrate a problem.  As for 
whether Oleg's example is within the rules, it depends whether you 
consider fdToHandle as unsafe: Haskell's IO library is carefully 
designed to not run into this problem on its own.  It's normally not 
possible to get two Handles with the same FD, however 
GHC.IO.Handle.hDuplicate also lets you do this.


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


Re: Unsafe hGetContents

2009-09-21 Thread Simon Marlow

On 16/09/2009 21:17, Florian Weimer wrote:

Are there any plans to get rid of hGetContents and the semi-closed
handle state for Haskell Prime?

(I call hGetContents unsafe because it adds side effects to pattern
matching, stricly speaking invalidating most of the transformations
which are expected to be valid in a pure language.)


There is no current proposal for this, no.  Feel free to start one; 
information about the process for Haskell Prime proposals is here


http://hackage.haskell.org/trac/haskell-prime/wiki/Process

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


Re: Unsafe hGetContents

2009-09-21 Thread Simon Marlow

On 17/09/2009 13:58, Nicolas Pouillard wrote:

Excerpts from Florian Weimer's message of Wed Sep 16 22:17:08 +0200 2009:

Are there any plans to get rid of hGetContents and the semi-closed
handle state for Haskell Prime?

(I call hGetContents unsafe because it adds side effects to pattern
matching, stricly speaking invalidating most of the transformations
which are expected to be valid in a pure language.)


Would you consider something like [1] as an acceptable replacement?

[1]: http://hackage.haskell.org/package/safe-lazy-io


I rater like this as a workaround for the most common practical problems 
with lazy I/O, those of resource control.  It doesn't address the deeper 
concern that lazy I/O requires a particular evaluation order and is 
therefore a bit warty as a language feature - implementing lazy I/O 
properly in GHC's parallel mutator was somewhat tricky.  I'm not of the 
opinion that we should throw out lazy I/O, but it's still a problematic 
area in Haskell.


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


Re: bug in language definition (strictness)

2009-08-07 Thread Simon Marlow

On 06/08/2009 17:42, Malcolm Wallace wrote:



What semantics would you like Haskell to have, in which (x `seq` y
`seq` e) and (y `seq` x `seq` e) are not equal?


I can easily imagine that (x `seq` y `seq` e) might have *two* semantic
denotations: bottom (Exception: stack overflow), and e. And I would like
to be able to choose which one I get (please). This is the declared
purpose of seq, namely to improve performance by avoiding unneeded
laziness.


I'm afraid I don't really comprehend what you're getting at. What do
you mean by an expression having two semantic denotations, and how
would you like to choose which one you get? And I'm baffled by the
mention of stack overflow, where does that come in?


Whether it is a stack overflow, or some other kind of resource-related
exception like out-of-memory, or too-many-open-file-handles, does not
really matter. As you were saying, semantically they are all just bottom.

My real point is that seq looks for all the world like it is intended to
affect the operational behaviour of a program, yet some people insist
that it is a purely denotational device, and that operational questions
are not relevant.


The fact remains that seq *is* defined denotationally, and any 
implementation that respects its semantics is legal.  If you want to 
change that, you need to make a Haskell Prime proposal.


I think it might be difficult to do that.  The Haskell report has no 
framework for talking about operational semantics at all.  The pure 
subset of Haskell is timeless, there's no specified evaluation order. 
Before we think about changing that, let's remember why it's that way: 
one reason is that evaluation order doesn't affect the denotational 
semantics, so it's unnecessary.  Another reason is that it lets Haskell 
admit many different implementations, including things like automatic 
speculative parallelism.  If you start nailing down evaluation orders, 
you rule out interesting implementations.  (this is why I've complained 
about lazy I/O in the past - it starts to creep in this direction).


There's nothing stopping you from making a compiler in which seq has the 
behaviour you want.  Indeed, Control.Parallel.pseq is the kind of seq 
you want (I think - we haven't put any thought into precisely specifying 
what it means).  pseq is a valid implementation of seq, it's just not 
the one we normally want to use, because it restricts the compiler's 
ability to optimise.  And pseq isn't something we want to mandate in the 
language, because it only makes sense in certain kinds of 
implementations.  I'm completely happy with asking users to use pseq 
when they really want an evaluation order guarantee.



Yet I think it would be
valid to say that seq can turn a non-terminating (exceptioning) program
into a terminating one.


Do you have an example of that?

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


Re: bug in language definition (strictness)

2009-08-07 Thread Simon Marlow

On 06/08/2009 23:56, Peter Gammie wrote:

On 07/08/2009, at 12:00 AM, Simon Marlow wrote:


On 06/08/2009 14:20, Peter Gammie wrote:

On 06/08/2009, at 10:59 PM, Simon Marlow wrote:

On 06/08/2009 13:49, Thomas Davie wrote:

On 6 Aug 2009, at 14:37, Nils Anders Danielsson wrote:


On 2009-08-06 11:08, Malcolm Wallace wrote:

yet, because of the definition of $!, this applies the
constructor to
its arguments right-to-left instead of the intuitive left-to-right.


I do not think that there is a bug: x `seq` y `seq` e has the same
denotation as y `seq` x `seq` e.


Not if one considers the kind of bottom one receives:

undefined `seq` error it exploded `seq` e will print
Prelude.undefined
while
error it exploded `seq` undefined `seq` e will print Error: it
exploded


There's only one kind of bottom in Haskell 98. And even with the
imprecise exceptions extension, both expressions still have the same
denotation - they denote the same set of exceptions, one of which is
non-deterministically picked when the program is run.


If the FFI Addendum is considered part of Haskell 98, then we have
unsafePerformIO, and so an appeal to denotational equivalence is not
sufficient. When grafting a pure interface onto a notionally-pure
library (specifically a BDD library), I often used seq to get these
effects buried in pure values under control.


That sounds like a very dangerous use of seq and unsafePerformIO to me!


How so? Take this code:

newtype BDD = BDD (ForeignPtr Int)

exists :: Group BDD - BDD - BDD
exists group bdd = bdd `seq` unsafePerformIO $
withGroup group $ \ gid -
do bdd_assoc bdd_manager gid
withBDD bdd ({#call unsafe bdd_exists#} bdd_manager) = addBDDfinalizer

Without the seq, a recursive use of a quantifier will screw up the
effect of bdd_assoc. How is this unsafe?
IMHO I'm using seq in the standard way, to shuffle the data dependencies
to get better (correct) operational behaviour.

I grant that it is dodgy in a concurrent setting, but the library itself
is not thread safe.


If, as I understand it, you are relying on the fact that seq's first 
argument is evaluted before its second, then you really want pseq rather 
than seq.


This is the sense in which I mean it's a dangerous use of seq and 
unsafePerformIO - because the compiler is within its rights to evaluate 
the second argument to seq first.


In GHC we provide a way to do what you want (pseq), I'm just not 
convinced it should be the required behaviour of seq.


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


Re: bug in language definition (strictness)

2009-08-07 Thread Simon Marlow

Dan Weston wrote:


   foldl (+) 0 [1..1000] :: Integer
   *** Exception: stack overflow
   foldl' (+) 0 [1..1000] :: Integer
   500500

I thought both of these were perfectly well defined in denotational 
semantics (and equal to 500500). The first is merely a failure 
of one person's computer to implement the (perfectly well-defined) 
denotational semantics of the program.


Quite.  It's slightly confusing that a stack overflow manifests in the 
same way as an exception that indicates _|_, such as error or divide by 
zero.


It's exactly the same as if you'd pressed Control-C during the first 
evaluation.  That doesn't cause the expression to have value _|_, but it 
does raise an exception.  The type of the exception is some help: 
StackOverflow is a constructor in the AsyncException datatype, 
indicating that it was an asynchronous exception.  Evaluating the 
expression again might yield a result.


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


Re: bug in language definition (strictness)

2009-08-06 Thread Simon Marlow

On 06/08/2009 14:20, Peter Gammie wrote:

On 06/08/2009, at 10:59 PM, Simon Marlow wrote:

On 06/08/2009 13:49, Thomas Davie wrote:

On 6 Aug 2009, at 14:37, Nils Anders Danielsson wrote:


On 2009-08-06 11:08, Malcolm Wallace wrote:

yet, because of the definition of $!, this applies the constructor to
its arguments right-to-left instead of the intuitive left-to-right.


I do not think that there is a bug: x `seq` y `seq` e has the same
denotation as y `seq` x `seq` e.


Not if one considers the kind of bottom one receives:

undefined `seq` error it exploded `seq` e will print
Prelude.undefined
while
error it exploded `seq` undefined `seq` e will print Error: it
exploded


There's only one kind of bottom in Haskell 98. And even with the
imprecise exceptions extension, both expressions still have the same
denotation - they denote the same set of exceptions, one of which is
non-deterministically picked when the program is run.


If the FFI Addendum is considered part of Haskell 98, then we have
unsafePerformIO, and so an appeal to denotational equivalence is not
sufficient. When grafting a pure interface onto a notionally-pure
library (specifically a BDD library), I often used seq to get these
effects buried in pure values under control.


That sounds like a very dangerous use of seq and unsafePerformIO to me!

The presence of unsafePerformIO doesn't change the meaning of the rest 
of Haskell.  You can use it to write programs that don't behave 
according to the denotational semantics if you want, but if you do that 
it's considered an unsafe use of unsafePerformIO.


What semantics would you like Haskell to have, in which (x `seq` y `seq` 
e) and (y `seq` x `seq` e) are not equal?



I also think the principle of least surprise is clearly violated here.


I do have some sympathy with that.  The fact that we're having this 
discussion is evidence that something is wrong - and indeed it took 
quite a while before we noticed that seq doesn't actually enforce a 
sequential evaluation order.  And seq was originally introduced to fix 
space leaks, but sometimes it can't be used for this because it doesn't 
provide enough operational guarantees (I haven't seen such cases myself, 
but Malcolm W tells me it really happens).


I'm against the change originally proposed in this thread, because on 
its own it doesn't make any difference.  But by all means let's think 
about ways to restore the lack of surprise, but which hopefully don't 
curtail the compiler's ability to optimise, or run programs in parallel.


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


Re: bug in language definition (strictness)

2009-08-06 Thread Simon Marlow

On 06/08/2009 15:33, Malcolm Wallace wrote:

What semantics would you like Haskell to have, in which (x `seq` y
`seq` e) and (y `seq` x `seq` e) are not equal?


I can easily imagine that (x `seq` y `seq` e) might have *two* semantic
denotations: bottom (Exception: stack overflow), and e. And I would like
to be able to choose which one I get (please). This is the declared
purpose of seq, namely to improve performance by avoiding unneeded
laziness.


I'm afraid I don't really comprehend what you're getting at.  What do 
you mean by an expression having two semantic denotations, and how would 
you like to choose which one you get?  And I'm baffled by the mention of 
stack overflow, where does that come in?


Cheers,
Simon

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


Re: Proposals and owners

2009-08-03 Thread Simon Marlow

On 02/08/2009 22:38, Niklas Broberg wrote:

I updated the code on the wiki page: the previous version didn't handle
prefix negation - did you implement that yourself in HLint?


No, I didn't implement prefix negation in HLint - it never came up as
an issue. Perhaps the underlying HSE library dealt with it for me -
Niklas would know.


In haskell-src-exts (and haskell-src, since that's inherited), unary
minus binds tighter than any infix operator:


exp0b :: { PExp }
   : exp0b qop exp10b  { InfixApp $1 $2 $3 }
   | dvarexp   { $1 }
   | exp10b{ $1 }



exp10b :: { PExp }
   : 'case' exp 'of' altslist  { Case $2 $4 }
   | '-' fexp  { NegApp $2 }
   | 'do' stmtlist { Do $2 }
   | 'mdo' stmtlist{ MDo $2 }
   | fexp  { $1 }


It has never come up as a problem. Guess that's a point in case for
getting rid of unary minus as an operator. :-)


I think someone should propose this change for next year's Haskell 
revision.  We have evidence that (a) the current precedence of prefix 
negation is confusing, and (b) it is rarely relied upon.


Changing the syntax as above is better IMO than the suggestion in

http://hackage.haskell.org/trac/haskell-prime/wiki/NegativeSyntax

to move prefix negation into the lexical syntax of numbers.

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


Re: StricterLabelledFieldSyntax

2009-08-03 Thread Simon Marlow

On 01/08/2009 12:58, Simon Peyton-Jones wrote:

Personally I hate the fact that
f Z {x=3}
parses as
f (Z {a=3})
because even though (as Iavor says) there is only one function application 
involved, it *looks* as if there are two.

Equally personally, I think that the presence or absence of white space is a powerful 
signal to programmers, and it's a shame to deny ourselves use of it.  So I'd be quite 
happy with *requiring* there to be no space, thus Z{ x=3 }.  If that's tricky to lex, so 
be it.  (Though a token BRACE_WITH_NO_PRECEDING_WHITESPACE might do the job.) 
 But this would be a very non-backward-compatible change.


On this point - I agree that whitespace-sensitive syntax presents no 
problem to programmers, and is often quite natural.  However, I think it 
presents enough other problems that it should be avoided where possible.


I'm thinking of

 - being friendly to automatic program generation
 - being friendly to parsers, and tools that grok Haskell
 - making code robust to modification that changes whitespace
 - making the grammar (in the report) simpler

all of these things are hurt by whitespace-sensitive syntax.  IMO, we 
should think very carefully before introducing any.


Cheers,
Simon


Simon

| -Original Message-
| From: haskell-prime-boun...@haskell.org [mailto:haskell-prime-
| boun...@haskell.org] On Behalf Of Ian Lynagh
| Sent: 26 July 2009 21:53
| To: haskell-prime@haskell.org
| Subject: Re: StricterLabelledFieldSyntax
|
| On Sun, Jul 26, 2009 at 10:16:28PM +0300, Iavor Diatchki wrote:
|
|  On Sun, Jul 26, 2009 at 10:01 PM, Isaac
|  Dupreem...@isaac.cedarswampstudios.org  wrote:
|Iavor Diatchki wrote:
|  
|I am strongly against this change.  The record notation works just
|fine and has been doing so for a long time.  The notation is really
|not that confusing and, given how records work in Haskell, makes
|perfect sense (and the notation has nothing to do with the precedence
|of application because there are no applications involved).  In short,
|I am not sure what problem is addressed by this change, while a very
|real problem (backwards incompatibility) would be introduced.
|-Iavor
|  
|a different approach to things that look funny, has been to implement a
|warning message in GHC.  Would that be a good alternative?
|
|  Not for me. I use the notation as is, and so my code would start
|  generating warnings without any valid reason, I think.  What would
|  such a warning warn against, anyway?
|
| For context, I looked at the alsa package. All of the (roughly 10)
| would-be-rejected cases looked like one of the two examples below. I
| don't really have anything new to say: Some people think these are
| clear, others find them confusing. Hopefully we'll find a consensus and
| make a decision.
|
|
| throwAlsa :: String -  Errno -  IO a
| throwAlsa fun err = do d- strerror err
|throwDyn AlsaException
|  { exception_location = fun
|  , exception_description = d
|  , exception_code = err
|  }
|
|   peek p  = do cl- #{peek snd_seq_addr_t, client} p
|po- #{peek snd_seq_addr_t, port} p
|return Addr { addr_client = cl, addr_port = po }
|
|
| Thanks
| Ian
|
| ___
| Haskell-prime mailing list
| Haskell-prime@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-prime

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


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


Re: Proposals and owners

2009-07-31 Thread Simon Marlow

I have fleshed out the report delta for


  remove FixityResolution from the context-free grammar


http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution

Please take a look and comment.  This fixes a nasty bug in the Haskell 
syntax - albeit one that doesn't cause problems in practice, but still. 
 I think the changes make the grammar look nicer, and help compiler 
implementers by providing a sample implementation of fixity resolution.


We better be sure the sample implementation is correct!  I've tested it 
fairly well, but I wouldn't rule out corner cases being wrong, 
especially with prefix negation.


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


Re: Proposals and owners

2009-07-31 Thread Simon Marlow

On 31/07/2009 14:51, Neil Mitchell wrote:

Hi


remove FixityResolution from the context-free grammar


http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution

Please take a look and comment.  This fixes a nasty bug in the Haskell
syntax - albeit one that doesn't cause problems in practice, but still.  I
think the changes make the grammar look nicer, and help compiler
implementers by providing a sample implementation of fixity resolution.

We better be sure the sample implementation is correct!  I've tested it
fairly well, but I wouldn't rule out corner cases being wrong, especially
with prefix negation.


The code in Resolve.hs has been used by HLint for months, and is the
basis of the resolution used in haskell-src-exts 1.0.0. In that time I
haven't seen any bugs with the fixity resolution.


I updated the code on the wiki page: the previous version didn't handle 
prefix negation - did you implement that yourself in HLint?


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


Re: [Haskell'-private] NoMonomorphismRestriction

2009-07-27 Thread Simon Marlow

On 25/07/2009 16:28, Ian Lynagh wrote:


I've made a ticket and proposal page for removing the monomorphism
restriction:
   http://hackage.haskell.org/trac/haskell-prime/ticket/131
   http://hackage.haskell.org/trac/haskell-prime/wiki/NoMonomorphismRestriction


I think if we do this we really have to do

http://hackage.haskell.org/trac/haskell-prime/wiki/SpecifyPatternBindingSemantics

Which is not strictly speaking a change, but is a necessary 
clarification if the MR is removed.  I believe the conclusion we came to 
in March/April 2008 was to do this.


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


Re: [Haskell'-private] NoNPlusKPatterns

2009-07-27 Thread Simon Marlow

On 25/07/2009 02:02, Ian Lynagh wrote:


Hi all,

I've made a ticket and proposal page for removing n+k patterns:
 http://hackage.haskell.org/trac/haskell-prime/ticket/130
 http://hackage.haskell.org/trac/haskell-prime/wiki/NoNPlusKPatterns

Should I have also added it to some index page somewhere?

Please let me know if there's anything else I should do.


No, that's all you need to do.  This link shows the proposals grouped by 
status, which shows the ones that are actively being worked on:


http://hackage.haskell.org/trac/haskell-prime/query?status=newstatus=assignedstatus=reopenedgroup=state

(that link is available from the home page as All Proposal Tickets)


By the way, I find all the old tickets and wiki pages make it very hard
to understand what is current on the haskell-prime trac.


We could easily make the query ignore the old tickets.  Would that help?

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


Re: Haskell 2010: libraries

2009-07-15 Thread Simon Marlow

On 14/07/2009 15:04, Ian Lynagh wrote:

On Tue, Jul 14, 2009 at 07:48:36AM +0100, Sittampalam, Ganesh wrote:

I don't have any strong opinion about whether there should be a library
standard or not, but if there is a standard, how about putting the
entire thing (perhaps including the Prelude) under the prefix
Haskell2010. or similar? Most of it could be implemented by just
re-exporting things from the real libraries.


That would be OK with me, although I still think it would be easier for
us to disentangle the library standardisation effort from the language
standardisation effort.

I'd suggest

 Haskell.V2010.Data.List (just re-exports from V2011 where possible)
 Haskell.V2010.Prelude   (just re-exports from V2011 where possible)
 Haskell.V2011.Data.List
 Haskell.V2011.Prelude

with the implicit Prelude import being changed to
 Haskell.Vversion.Prelude
whereversion  is that latest the compiler supports, unless you say
e.g. -XHaskell2010.


I find this rather jarring, because it moves versioning from where it 
should be (in the package metadata) to where it shouldn't be (in the 
module names).


So why can't we use package versioning to do this?  Suppose we have a 
'haskell-std' package, with versions starting at 2010, providing modules 
like Data.List.  The problem is that haskell-std:Data.List overlaps with 
base:Data.List.


But there's a solution: we could remove the standard modules from 
base, and have them only provided by haskell-std (since base will just 
be a re-exporting layer on top of base-internals, this will be easy to 
do).  Most packages will then have dependencies that look like


  build-depends: base-4.*, haskell-std-2010

(or does it have to be haskell-std-2010.0?)

In some ways this is nice, because we will be able to keep old versions 
of haskell-std much longer than we can keep old versions of base.  And 
in due course, we can move more modules into haskell-std.  That makes an 
incremental approach to library standardisation possible, in the same 
way as we have modularised the language standardisation process.


So, if we have standard Haskell library modules, then I believe they 
should be separate at the package level (as they are now).


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


Re: Haskell 2010: libraries

2009-07-15 Thread Simon Marlow

On 15/07/2009 15:47, Sittampalam, Ganesh wrote:


But there's a solution: we could remove the standard modules from
base, and have them only provided by haskell-std (since base will
just be a re-exporting layer on top of base-internals, this will be
easy to do).  Most packages will then have dependencies that look
like


But this precludes the kind of changes to those modules that Ian
described as having happened in the last few years.


I don't follow.  If we have versioned haskell-std packages, surely they 
can export different APIs?


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


Re: Haskell 2010: libraries

2009-07-15 Thread Simon Marlow

On 15/07/2009 15:54, Ian Lynagh wrote:

On Wed, Jul 15, 2009 at 03:39:55PM +0100, Simon Marlow wrote:

But there's a solution: we could remove the standard modules from
base, and have them only provided by haskell-std (since base will just
be a re-exporting layer on top of base-internals, this will be easy to
do).  Most packages will then have dependencies that look like

   build-depends: base-4.*, haskell-std-2010


We'll probably end up with situations where one dependency of a package
needs haskell-std-2010, and another needs haskell-std-2011. I don't know
which impls support that at the moment.


That's the case with base-3/base-4 at the moment.  Is it a problem?

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


Re: Proposal: change to qualified operator syntax

2009-07-14 Thread Simon Marlow

On 14/07/2009 08:58, Malcolm Wallace wrote:

 left section  right section  prefix
unqualified (+ 1) (1 +) (+)
Haskell 98 (M.+ 1) (1 M.+) (M.+)
proposed (`M.(+)` 1) (1 `M.(+)`) M.(+)
or(*) (M.(+) 1) (flip M.(+) 1)


The last line is not correct. (M.(+) 1) captures the first argument of
the function, not the second like all the other entries in that column.
Likewise the flip variant captures the second arg, where all the others
capture the first.


oops, I got those the wrong way around.  Well spotted.

Fixed on the wiki page:

http://hackage.haskell.org/trac/haskell-prime/wiki/QualifiedOperators

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


Re: Proposal: change to qualified operator syntax

2009-07-13 Thread Simon Marlow

On 12/07/2009 22:32, hask...@henning-thielemann.de wrote:


On Tue, 7 Jul 2009, hask...@henning-thielemann.de wrote:


I like to note that I'm against this proposal. The example given in
http://hackage.haskell.org/trac/haskell-prime/wiki/QualifiedOperators
namely [Red..] can be easily resolved by adding a space, thus [Red
..]. I use qualified operators occasionally, since I use
NumericPrelude and thus have to import some things from Prelude in a
qualified way. As there will appear more and more infix operators in
libraries along with more name clashes (e.g. recently discussed
List.++ and Monoid.++), qualified operator names will become not so
uncommon. Of course, to keep the spirit of infix operators, you will
better define custom operators locally, but this is only reasonable if
you use an infix operator more than once.
The current syntax is also in a way consistent, since e.g. (+)
coincides with a two side operator section, which is no longer true
with the new proposal.


Should the consistency with operator section also be added as 'cons' to
http://hackage.haskell.org/trac/haskell-prime/wiki/QualifiedOperators
?


So correct me if I'm wrong; the point you're making is:

 left section  right section   prefix
unqualified  (+ 1) (1 +)   (+)
Haskell 98   (M.+ 1)   (1 M.+) (M.+)
proposed (`M.(+)` 1)   (1 `M.(+)`) M.(+)
   or(*) (M.(+) 1) (flip M.(+) 1)

(*) only if precedence isn't important, e.g. not in cases like (`M.(+)` 
x `M.(*)` y).


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


Re: Haskell 2010: libraries

2009-07-10 Thread Simon Marlow

On 08/07/2009 22:45, Ian Lynagh wrote:

On Wed, Jul 08, 2009 at 03:09:29PM +0100, Simon Marlow wrote:

  1. Just drop the whole libraries section from the report.  The
 Report will still define the Prelude, however.

I'm tending towards (1), mainly because it provides a clean break and is
likely to be the least confusing for users: they have one place to go
looking for library documentation.


Sounds good to me.

See also http://hackage.haskell.org/trac/haskell-prime/ticket/118


Ian, would you like to take ownership for this proposal, and start 
fleshing out the details in a wiki page?


There seems to be support for removing all the libraries in the report. 
 Whether the report also blesses either the Haskell Platform or a set 
of packages is a separate matter; either way, we still have to extract 
the existing libraries from the report, and there will be a set of 
changes to the report necessary to make that happen.  The Report should 
explicitly list all the library entities that it refers to.


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


Re: Proposals and owners

2009-07-09 Thread Simon Marlow

We still need owners for:

On 08/07/2009 10:07, Simon Marlow wrote:


  Remove n+k patterns
  NonDecreasingIndentation


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


Re: Proposal: change to qualified operator syntax

2009-07-09 Thread Simon Marlow

On 08/07/2009 23:06, k...@cas.mcmaster.ca wrote:

Simon Marlow replied to Henning Thielemann:

Prelude.= just doesn't look like an infix operator.  The point of
infix operators is that they are a lightweight notation, but they lose
that advantage when qualified.  The qualified operator proposal gives
you a nice rule of thumb to rely on when parsing code in your head: if
it begins with a letter, it is not infix.  The advantages of this
shouldn't be underestimated, IMO.

Actually, I am another supporter of qualified infix operators.

Is see on

http://hackage.haskell.org/trac/haskell-prime/wiki/QualifiedOperators

that with the new proposal, I would have to write

   `Prelude.(=)`


You don't *have* to write that, you can use the prefix form.  The 
argument that this proposal makes is that when you have to qualify an 
operator, it has lost most of the advantages of being infix.



. I frequently run into situations where that would be extremely useful.


 the M.. M... M debacle

I don't think that problems arising from a single character
should outlaw a whole lexical category.
Better outlaw that character! ;-)


Dot is a particularly troublesome character, owing to the decision to 
use it for qualified operators back in Haskell 1.3.  It's really too 
late to change that now, sadly.



Back to the original argument:

Prelude.= just doesn't look like an infix operator.

I think that

   `Prelude.(=)`

doesn't really look like an infix operator either.


It does begin with a `, just like `Data.List.map`, or `fmap`.  So in 
that sense it is more like an infix operator than Prelude.=.


Anyway, thanks for all the comments in this thread.  I've tried to 
summarise the pros/cons on


http://hackage.haskell.org/trac/haskell-prime/wiki/QualifiedOperators

Please let me know if I've missed anything.  The committee will review 
the arguments when we make final decisions.


I realise this change is not a clear-cut win.  So few things are.  It's 
a question of balancing the advantages against the disadvantages, and 
reasonable people are very likely to differ.


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


Re: Haskell 2010: libraries

2009-07-09 Thread Simon Marlow

On 09/07/2009 13:26, Bulat Ziganshin wrote:

Hello Simon,

Thursday, July 9, 2009, 3:46:31 PM, you wrote:


This would be a bold step, in that we would be effectively standardising
a lot more libraries than the current language standard.  The base
package is a fairly random bag of library modules, for instance.  It


The base library is under the question, but remaining libs of ghc/HP
are in rather good shape

of course, without base we can't do even i/o, so questions still
remains. in particular, you plan to do something with base in 6.12
although it was not yet decided what exactly

so these two discussions (what to do with libs in 6.12 and what to do
with libs in Report) may go together

ideally, we would split base into smaller and versionable packages. at
least in form of interfaces, while implementations will just import
everything from base


I feel this discussion is widening a bit too far.

The question at hand is how to make the Haskell 2010 Report 
self-consistent, avoid confusing users, and avoid perpetuating obsolete 
libraries.  The Haskell Report doesn't have to specify libraries, it is 
not supposed to be a complete specification of the Haskell universe, it 
is a specification of the language.


Remember that we're talking here about a *standard*.  The Haskell 
Platform libraries, while being a hugely useful resource, are not 
specified to the level of precision we would expect for a Haskell 
standard.  Neither have they undergone the level of scrutiny that we 
would ideally subject libraries to.  So we can't just throw all this 
stuff in the standard and say done!.


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


Re: Announcing the new Haskell Prime process, and Haskell 2010

2009-07-08 Thread Simon Marlow

On 07/07/2009 16:40, Claus Reinke wrote:

At last year's Haskell Symposium, it was announced that we would
change the Haskell Prime process to make it less monolithic. ..
In the coming weeks we'll be refining proposals in preparation for
Haskell 2010.


Given the incremental nature of the new standards, would it be
useful to switch back to version numbers, eg Haskell 2.0.0 (2010)
instead of Haskell 2010? Otherwise, we'll end up with half a
dozen more or less current Haskells related by no obvious means.
Haskell'98 was chosen because it projected more permanence
than the Haskell 1.x line of Haskell revisions that came before it.


The relationship between the versions will be quite clear: each revision 
will be specified by a set of deltas to the previous one.  I think the 
year-based naming scheme is fine, especially since we're planning to 
produce annual revisions.


An important question though is what we should call the major versions. 
 There it will probably make sense to use Haskell 2, Haskell 3, and 
so on.  I imagine the first major version won't be for a few years, though.



Having API instead of date encoded in the name would support
deprecations, breaking changes, or additions as well as make it clear
whether a new year's version does break anything or not.

Btw, once upon a time, there was a discussion about an even
more modular approach, standardising language extensions
without saying which extensions made up a standard language.
That would give support to the status quo, where people want
to use, say, Haskell'98+FFI+Hierarchical Modules+MPTC+..

In other words, existing language extensions (LANGUAGE
pragmas) ought to be standardized (currently, they mean different
things in different implementations), independent of whether
or not the committee decides to group them into a Haskell X.


What you're suggesting is not incompatible with Haskell'.  In Haskell', 
each change to the language will be independently specified, as an 
addendum, before being accepted as part of the language.


So a side-effect of the standardisation process is a set of addenda, 
that you could mix and match.  GHC will still support one flag per 
extension, where it makes sense (there's not much point making a flag 
for fixes and trivial changes).  So in GHC, {-# LANGUAGE Haskell2010 #-} 
could be expanded to the set of extensions in Haskell 2010, and will 
probably be implemented that way.


Cheers,
Simon

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


Re: Proposal: change to qualified operator syntax

2009-07-08 Thread Simon Marlow

On 07/07/2009 16:58, hask...@henning-thielemann.de wrote:


Adding to an old thread:
http://www.haskell.org/pipermail/haskell-prime/2008-April/002441.html

I like to note that I'm against this proposal. The example given in
http://hackage.haskell.org/trac/haskell-prime/wiki/QualifiedOperators
namely [Red..] can be easily resolved by adding a space, thus [Red ..].
I use qualified operators occasionally, since I use NumericPrelude and
thus have to import some things from Prelude in a qualified way. As
there will appear more and more infix operators in libraries along with
more name clashes (e.g. recently discussed List.++ and Monoid.++),
qualified operator names will become not so uncommon. Of course, to keep
the spirit of infix operators, you will better define custom operators
locally, but this is only reasonable if you use an infix operator more
than once.
The current syntax is also in a way consistent, since e.g. (+) coincides
with a two side operator section, which is no longer true with the new
proposal. Also (...) and `...` are dual, which is a nice property.



This proposal cleans up some nastiness in the lexical syntax.  For 
example the M.. M... M debacle.  How many lexemes in each of those? 
in Haskell 98 it's 1, 2, and 3 respectively, whereas with the qualified 
operator proposal they are all 2 lexemes.


Yes, you can add spaces to make [Red ..] work.  But why should you have 
to, when [1..] works without a space?


Prelude.= just doesn't look like an infix operator.  The point of 
infix operators is that they are a lightweight notation, but they lose 
that advantage when qualified.  The qualified operator proposal gives 
you a nice rule of thumb to rely on when parsing code in your head: if 
it begins with a letter, it is not infix.  The advantages of this 
shouldn't be underestimated, IMO.


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


Re: [Haskell] Announcing the new Haskell Prime process, and Haskell 2010

2009-07-08 Thread Simon Marlow

On 07/07/2009 20:17, Simon Peyton-Jones wrote:

| There are a couple sensible removals here.  Do we also want to get rid
| of the useless class contexts on data-declarations? (that look like
| data Ord a =  Set a = Set ...)

Yes! Yes! Kill them.

(In GHC's source code these contexts are consistently called stupid_theta.)


This is listed as Remove class context on data definitions in the list 
of proposals.  It doesn't have an owner or a wiki page yet.  Any volunteers?


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


Haskell 2010: libraries

2009-07-08 Thread Simon Marlow
This is more of a consistency issue than anything else.  We have to 
decide what to do with the libraries in the Report.


Right now, the Haskell Report specifies 15 library modules.  Things like 
Maybe, Char, IO, Time, and Random.  The situation is not ideal, for many 
reasons:


 - There are a lot more than 15 library modules available to Haskell
   programmers!  The libraries section of the report was a good
   idea when there were no libraries at all, nowadays it makes
   a lot less sense.

 - These modules are using the old non-hierarchical names.  Best
   practice these days is to use the hierarchical versions.

 - some of these libraries have well-known problems, and some have
   been superseded by better libraries: Time is a good example.

On the other hand, some people like having these modules around, and 
deliberately use them because they aren't allowed to change.


I'm mainly concerned with projecting a consistent picture in the Report, 
so as not to mislead or confuse people.  Here are the options I can see:


 1. Just drop the whole libraries section from the report.  The
Report will still define the Prelude, however.

There will be some loose ends where the rest of the report
refers to entities from these libraries, e.g. the Prelude
refers to Rational from the Ratio library.  We just have to
fix up these references, moving the appropriate definitions
into the Report as necessary.

 2. Just drop the obvious candidates (Time, Random, CPUTime,
Locale, Complex?), leaving the others.

 3. Update the libraries to match what we have at the moment.
e.g. rename List to Data.List, and add the handful of
functions that have since been added to Data.List.  One
problem with this is that these modules are then tied to
the language definition, and can't be changed through
the usual library proposal process.  Also it would seem
slightly strange to have a seemingly random set
of library modules in the report.

 4. Combine 2 and 3: drop some, rename the rest.

 5. Don't do anything.


Note that we have to take into account the FFI libraries too: the FFI 
addendum includes modules such as Foreign, CForeign, Storable, 
MarshalError, and so on.  The same issues apply: the report needs to 
mention some of the types and entities exported by these modules.


I'm tending towards (1), mainly because it provides a clean break and is 
likely to be the least confusing for users: they have one place to go 
looking for library documentation.


Please keep discussion focussed: this is about how libraries are 
presented in the Haskell report, not about library standardisation in 
general.  I'm aware there are much wider issues, but we have some 
immediate problems to address.


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


Announcing the new Haskell Prime process, and Haskell 2010

2009-07-07 Thread Simon Marlow
At last year's Haskell Symposium, it was announced that we would change 
the Haskell Prime process to make it less monolithic.  Since then, 
everyone has been busy using Haskell (or implementing it), and we 
haven't made much progress on the standardisation side of things.  Well, 
with ICFP and the Haskell Symposium approaching we felt it was time to 
get the new process moving and hopefully produce a language revision 
this year.


I've updated the Haskell' wiki with the new information; in particular 
the process is documented here:


  http://hackage.haskell.org/trac/haskell-prime/wiki/Process

We're aiming to announce the list of accepted proposals at the Haskell 
Symposium this year.  However, owing to the short timescale, the list is 
going to be correspondingly short, and limited to extensions which are 
either already fully specified (i.e. the FFI) or are small and 
well-understood.  The following list is very provisional; we'll be 
making the final decisions next month.


ForeignFunctionInterface
LineCommentSyntax
PatternGuards
DoAndIfThenElse
Remove n+k patterns
RelaxedDependencyAnalysis
EmptyDataDeclarations
HierarchicalModules
NonDecreasingIndentation
remove FixityResolution from the context-free grammar
change the syntax of QualifiedOperators

In the coming weeks we'll be refining proposals in preparation for 
Haskell 2010.  By all means suggest more possibilities; however note 
that as per the new process, a proposal must be complete (i.e. in the 
form of an addendum) in order to be a candidate for acceptance.


I have updated the status page

  http://hackage.haskell.org/trac/haskell-prime/wiki/Status

marking everything except the proposals that have been already 
implemented in the draft Report as old.  The new process requires a 
proposal to have an owner or owners in order to make progress; once a 
proposal has an owner it will move into the under discussion state. To 
take up ownership of an existing proposal, or to start a new proposal, 
ask on the mailing list.  There are other ways you can get involved; 
some suggestions are on the Haskell' main page:


  http://hackage.haskell.org/trac/haskell-prime/wiki

(hmm, I suppose we should fix that logo too...)

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


Re: Repair to floating point enumerations?

2008-10-22 Thread Simon Marlow

Malcolm Wallace wrote:


Phil proposes that, although retaining the instances of Enum for Float
and Double, we simplify the definitions of the numericEnumFrom family:

  numericEnumFromThenTo   :: (Fractional a, Ord a) = a - a - a - [a]
  numericEnumFrom =  iterate (+1)
  numericEnumFromThen n m =  iterate (+(m-n)) n
  numericEnumFromTo n m   =  takeWhile (= m) (numericEnumFrom n)
  numericEnumFromThenTo n m p = takeWhile (= p) (numericEnumFromThen n m)


I'll leave it to the floating-point experts to decide exactly what to do 
here for Haskell' (but I note that David Roundy's version looks better than 
the iterate version above, because the errors won't accumulate).



But as maintainer and bug-fixer of the Haskell'98 Report, I have also
been asked whether we should make this change retrospectively to the
Haskell'98 language (as a typo).  Since it involves not merely an
ordinary library function, but a Prelude function, and moreover a
function that is used in the desugaring of syntax, it is less clear to
me whether to alter Haskell'98.


We definitely can't make breaking changes to Haskell 98; this would be much 
more than a typo.


However, this does give us a problem if we decide to make a change here for 
H', as Neil points out, because there would be two mutually-incompatible 
instances for Enum Float.  We'd need to have a clear distinction between 
programs that are Haskell 98 and those that are not, with only the former 
allowed to use the haskell98 package.


Cheers,
Simon

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


patch applied (haskell-prime-status): reject CompositionAsDot

2008-05-14 Thread Simon Marlow
Wed Apr 30 09:49:57 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * reject CompositionAsDot

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080430164957-8214f-0b8497293fb762b3eca2f467db49f3fb13bf42d4.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): accept QualifiedOperators

2008-05-14 Thread Simon Marlow
Wed Apr 30 09:50:38 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * accept QualifiedOperators

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080430165038-8214f-81a70a53e326d741ecdd46e63c895397763f7d11.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): Accepted: specify the static semantics of pattern bindings

2008-05-14 Thread Simon Marlow
Wed May 14 07:57:26 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * Accepted: specify the static semantics of pattern bindings

M ./status.hs +5

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080514145726-12142-c9043f9e22b6eee2d15bdc00ae6a71c60aa5ac0c.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): Accepted: remove the monomorphism restriction

2008-05-14 Thread Simon Marlow
Wed May 14 08:12:34 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * Accepted: remove the monomorphism restriction

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080514151234-12142-8883dd9b436af3208701e5dcd9b926e38391765c.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): separate the various monomorphism restriction proposals

2008-05-14 Thread Simon Marlow
Wed May 14 08:12:12 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * separate the various monomorphism restriction proposals

M ./status.hs -1 +17

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080514151212-12142-28aa86fa87208d58913b72b0fdb6be38e61e9a62.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): Reject: make variable and pattern bindings monomorphic by default

2008-05-14 Thread Simon Marlow
Wed May 14 08:13:16 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * Reject: make variable and pattern bindings monomorphic by default

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080514151316-12142-96877503c976760e847641936a8b93f5e6e7f3ef.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-28 Thread Simon Marlow

Manuel M T Chakravarty wrote:

Lennart Augustsson:
So I still think changing $ is insane.  Why change?  If you want a new 
operator, make a new one.  Don't make a gratuitous change that will 
waste countless man hours.  For me it's a simple decision, if $ 
changes I cannot use Haskell'.  :(


Given that people can't even agree whether it makes sense to change $ at 
all, this is IMHO far away from a change that justifies breaking any code.


So I suggest we reject the proposal, and move any further discussion to 
 haskell-cafe.  Ok?


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


Re: RFC: qualified vs unqualified names in defining instance methods

2008-04-25 Thread Simon Marlow

Claus Reinke wrote:


i originally filed this as a bug, until Simon PJ kindly pointed
me to the Haskell 98 report, which forces GHC to behave
this way.. i guess i'll remember this oddity for a while, so
i can live with it, but if it is irksome that the report allows
me to refer to a name that is not in scope, it is far from obvious why 
it needs to prevent me from referring to a

name that *is* in scope (Malcolm mentioned parsing
ambiguities as the reason for this, but in my case, GHC
recognizes the qualified name and *complains* about it).


Is it too hard to remember that in an instance declaration you can give 
bindings for methods of the class being instantiated only?  To me, the 
oddity is that the method name must be in scope at all - this is a 
definition, not a reference, with a fixed set of things that can be defined.


However, there is a consistency issue with record construction.  The 
fields of a record construction are very much like the methods in an 
instance declaration: they are bindings for already-defined identifiers, 
and the set of available identifiers is known statically.  In Haskell 98:


aexp-  qcon { fbind1 , ... , fbindn }
fbind   -  qvar = exp

so record fields can be referred to by qualified names, and in fact you 
are required to use the name by which the field is in scope - but GHC's 
DisambiguateRecordFields extension relaxes this so you're allowed to use 
the unqualified name.


So, in summary:

 - Haskell 98 is completely inconsistent here.

 - GHC + DisambiguateRecordFields is a bit more consistent
   in that unqualified names are allowed in both settings, but
   still allows qualified names in one setting but not the other.

So whatever we do we should be consistent.

It would be slightly strange if record construction required the 
unqualified name, but record update required the qualified name, when 
the field name is only in scope qualified.  So that indicates that we 
should allow either form in record construction (and instance 
declaration), i.e. Claus's suggestion + DisambiguateRecordFields.


Cheers,
Simon

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


Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-24 Thread Simon Marlow

Iavor Diatchki wrote:


I should also point out that if we were to adopt the MBP rule, we
would have to adjust the definition of what pattern bindings mean.
For example, I think that this is how things are desugared at the
moment:
(x,y)  = e
becomes
new_var = e
x = case new_var of (v,_) - v
y = case new_var of (_,v) - v


The report doesn't actually mention this translation although it is 
widely used to implement pattern bindings, and in some compilers (not 
GHC) the translation is done before type checking.


What's interesting to me is that perhaps this gives us a way to 
understand what the static semantics of pattern bindings should be, 
absent MPB. e.g.


(x,y) = (negate,show)

(Simon's example) translates to

z = (negate,show)
x = fst z
y = snd z

and we can see why both x and y end up generalised over both 
constraints, because


z :: (Num a, Show b) = (a - a, b - String)

and this also explains why the pattern-bound variables don't have to be 
generalised over all the type variables.  e.g. in


z = (id,id)
x = fst z
y = snd z

we'd get

 z :: forall a b . (a-a, b-b)
 x :: forall a . a - a

not

 x :: forall a b . a - a

because the generalisation step for x only generalises over the type 
variables in the type arising from its right-hand side.


Cheers,
Simon


It seems that under MBP the second program is not equivalent to the
first because it is more polymorphic.

-Iavor



On Wed, Apr 23, 2008 at 10:32 AM, Simon Marlow [EMAIL PROTECTED] wrote:

Folks,

 The current proposal on the table for what to do about the monomorphism
restriction (henceforth MR) is

  * remove the MR entirely
  * adopt Monomorphic Pattern Bindings (MPB)

 Right now, the committee is almost uniformly in favour of dropping the MR,
and most of us are coming round to the idea of MPB.  Since this area has
historically been difficult to achieve a concensus on, I'm excited that we
appear to be close to making a decision, and a good one at that!

 The arguments for removing the MR are pretty well summarised on the wiki:

 http://hackage.haskell.org/trac/haskell-prime/wiki/MonomorphismRestriction

 You can read about MPB here:


http://hackage.haskell.org/trac/haskell-prime/wiki/MonomorphicPatternBindings

 GHC has implemented MPB by default (i.e. we deviate slightly from Haskell
98) since 6.8.1.

 The nice thing about the combination of removing MR and adopting MPB is
that we retain a way to explicitly declare monomorphic bindings.  These are
monomorphic bindings:

  ~x = e
  [EMAIL PROTECTED] = e

 or if you don't mind a strict binding: !x = e.  The wiki points out that

  (x) = e

 would also be monomorphic, but arguably this is in poor taste since we
expect (x) to mean the same as x everywhere.

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



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


patch applied (haskell-prime-status): wiki link for the $ issue

2008-04-23 Thread Simon Marlow
Wed Apr 23 09:47:02 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * wiki link for the $ issue

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080423164702-8214f-f38f4a62db63708da38c8cabdb65bc8af8aea58c.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-23 Thread Simon Marlow

Dan Doel wrote:

On Tuesday 22 April 2008, Simon Marlow wrote:

I'm hoping someone will supply some.  There seemed to be strong opinion
on #haskell that this change should be made, but it might just have been
a very vocal minority.


These are the arguments off the top of my head:


Thanks, I've put these points, and Josef's point, on the wiki:

http://hackage.haskell.org/trac/haskell-prime/wiki/ChangeDollarAssociativity

(I should point out that I'm personally *not* in favour of this change, 
just making sure the arguments are documented)


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


Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-23 Thread Simon Marlow

Duncan Coutts wrote:

On Tue, 2008-04-22 at 21:02 -0400, Dan Doel wrote:

3) Left associative ($) is consistent with left associative ($!). The right 
associative version of the latter is inconvenient, because it only allows 
things to be (easily) strictly applied to the last argument of a function.


What about having ! as a left associative strict apply operator?

f !x !y !z

Isn't there already a proposal along these lines? There is certainly a
proposal to stop using ! for array indexing.


The problem with this is that

  f !x y

would associate differently in an expression than it does on the left 
hand side of an equation, where ! is the prefix bang-pattern operator. 
To make this consistent we'd have to make ! a prefix operator in 
expressions, or give it the same precedence as function application; 
both mean a new extension.


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


Re: Meta-point: backward compatibility

2008-04-23 Thread Simon Marlow

Johan Tibell wrote:

An interesting question. What is the goal of Haskell'? Is it to, like
Python 3000, fix warts in the language in an (somewhat) incompatible
way or is it to just standardize current practice? I think we need
both, I just don't know which of the two Haskell' is.


The stated goal is still for Haskell' to be a language that is stable 
and relevant for large-scale development for several years to come.


It is mainly a consolidation effort: that is, we aim to standardise 
existing practice in the form of language extensions that are currently 
implemented and widely used.  Having said that, the standardisation 
process gives us the opportunity to critically assess the design of 
these extensions, and the design of the system as a whole, and as a 
result we may wish to make changes in order that the resulting language 
does not have inconsistencies, design flaws, or critical omissions.


The language design process is also an opportunity to re-assess existing 
language features in the light of the wealth of experience gained over 
recent years.  A perfect example is the monomorphism restriction: we now 
know that this aspect of the language really does surprise people in 
practice, whereas this wasn't known, or at least wasn't as clear, at the 
time that Haskell 98 was being designed.


As for the particular question of backwards-incompatible changes, here 
are some criteria that Henrik Nilsson proposed early on, and I think are 
still relevant (i'm sure he won't mind my reposting these from the 
committee mailing list):


* If a proposed change breaks backwards compatibility, then it is
   acceptable only if either

   - very little existing code is likely going to be broken in
 practice, or
   - + it is widely agreed that not addressing the issue really
   would harm the long-term relevance of Haskell', and
 + it is widely agreed that attempting to maintain backwards
   compatibility would lead to an unwieldy language design, and
 + the proposed design and its implications are well understood,
   i.e. it has been implemented in at least one system and it has
   been used extensively, or a strong argument can be made on
   the grounds of, say, an underlying well-understood theory.

Libraries are another matter.  We have in place mechanisms for 
versioning libraries and specifying precise dependencies, so changes to 
libraries are in a sense less fundamental than changes to the language 
itself.  We've already stated that libraries are to be standardised 
separately, and I think it would also make sense for library standards 
to be issued more regularly than standards for the language.


Cheers,
Simon



-- Johan

On Wed, Apr 23, 2008 at 2:16 PM, Chris Smith [EMAIL PROTECTED] wrote:

There appears to be some question as to the backward compatibility goals
 of Haskell'.  Perhaps it's worth bringing out into the open.

 From conversations I've had and things I've read, I've always gathered
 that the main goal of Haskell' is to address the slightly embarrassing
 fact that practically no one actually writes code in Haskell, if by
 Haskell we mean the most recent completed language specification.  This
 obviously argues strongly for a high degree of backward compatibility.

 On the other hand, I am assuming everyone agrees that we don't want to
 replicate Java, which (in my view, anyway) is rapidly becoming obsolete
 because of an eagerness to make the language complex, inconsistent, and
 generally outright flawed in order to avoid even the most unlikely of
 broken code.

 --
 Chris

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


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


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


patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-22 Thread Simon Marlow
Tue Apr 22 15:53:31 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * add Make $ left associative, like application

M ./status.hs +5

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/2008045331-8214f-8c2b7ec4a7666bfaa70b2514290172981bdebb50.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-22 Thread Simon Marlow

Chris Smith wrote:

On Tue, 22 Apr 2008 15:53:39 -0700, Simon Marlow wrote:

Tue Apr 22 15:53:31 PDT 2008  Simon Marlow
[EMAIL PROTECTED]
  * add Make $ left associative, like application


Is there a justification for this somewhere?


I'm hoping someone will supply some.  There seemed to be strong opinion 
on #haskell that this change should be made, but it might just have been 
a very vocal minority.


I know it would break 
nearly every single piece of Haskell code I've ever written.  As such, 
I'm biased toward thinking it's an extremely bad idea.


Absolutely.  Given that, we'd need a *very* good reason to make the change.

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


DRAFT: Haskell' status update

2008-04-21 Thread Simon Marlow

Those on the Haskell' mailing list may have seen recent signs of
activity on the Haskell' front.  I thought I should clarify the current
status, and update the community on our plans for Haskell'.

The main sticking point in the design of Haskell' has been the type
system: namely whether Haskell' should have Functional Dependencies or
Type Families.  This issue is still undecided, although the experts are
hard at work on developing a stronger understanding of Type Families in
particular.

Nevertheless, the committee feels that we cannot have a Haskell' without
some way to resolve ambiguities when using multi-parameter type
classes, be it Functional Dependencies (FDs) or Type Families (TFs).
For one thing, a great deal of existing code uses FDs or depends on code
that does, so unless we adopt one of these extensions all this code will
still exist outside of Haskell', and that is far from ideal.  So we
decided to proceed in two stages:

  - Haskell' alpha will be a complete language specification,
including all the modifications and additions we want to make
to the language *except* for FDs or TFs.

  - Haskell' will follow afterward, adding either FDs or TFs.

The motivation for this two-stage approach is that we can make progress
on all the other parts of the language without being blocked on the type
system, we can start work on implementing Haskell' alpha in our
compilers, users can start using the new standard, and we can gain some
experience with using it in practice.

On the process side of things, we're now tracking the status of all
language design proposals on this page:

  http://hackage.haskell.org/trac/haskell-prime/wiki/Status

and as usual all the Haskell' resources are on the wiki:

  http://hackage.haskell.org/trac/haskell-prime/wiki

The committee have been discussing various proposals amongst ourselves
over the past few weeks, with the goal of making as many concrete 
decisions as possible.  However, the general policy is still for 
technical discussions to take place in public, as far as possible.


Changes to the status page are sent to the public mailing list, and we
welcome comments on any of the issues, regardless of status.

Thanks for your patience :-)  And rest assured that progress is being made!

Cheers,

Simon (and the Haskell' committee)
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Haskell' status update

2008-04-21 Thread Simon Marlow

Simon Marlow wrote:
Subject: DRAFT: Haskell' status update

of course, that shouldn't have said DRAFT.

Cheers,
Simon


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


patch applied (haskell-prime-status): add wiki link for ArrayIndexing

2008-04-21 Thread Simon Marlow
Mon Apr 21 11:30:40 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * add wiki link for ArrayIndexing

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080421183040-8214f-02ff20c870f45e474bf91dc581b45e3a20e6bea7.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): BangPatterns: probably accept == undecided

2008-04-21 Thread Simon Marlow

John Meacham wrote:

On Fri, Apr 18, 2008 at 08:36:42AM +0100, Simon Peyton-Jones wrote:

Not allowing infix functions on the LHS would be a notable
simplification.  Constructors in patterns should still be infix of
course: f (a :=: b) = ...


I don't know, I think this will confuse things, especially for newbies,
people tend to say things like:

a + b = foo

as a plus b is foo, and so would probably naturally write it in infix
form, it would be a source of confusion if the compiler didn't accept
it.

I don't think saying ~ and ! are operators unless they 


1. immediately followed  by a '(', a letter, or an underscore
2. are preceded by whitespace or BOL

is that onerous. 


I don't like the idea of solving this in the lexical syntax, e.g. by the 
rules you gave above, it's just too ad-hoc.  I think a better way to fix 
it is just to disallow infix declarations of !, ~ (and @ ?).  Currently 
the grammar has:


funlhs   -   var apat {apat}
|   pati+1 varop(a,i) pati+1
|   lpati varop(l,i) pati+1
|   pati+1 varop(r,i) rpati
|   ( funlhs ) apat {apat}

so we can use a restricted variant of varop that doesn't include !, ~ or 
@ (well, varop doesn't currently include ~ or @, but I assume we want it 
to - it would be similar to the way hiding is handled now).


Incedentally I think we should use a different operator for array 
indexing, because ! is almost universally used to mean strict now: in 
bang patterns, strict datatype fields, and $!.  See


http://hackage.haskell.org/trac/haskell-prime/wiki/ArrayIndexing

Cheers,
Simon

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


Re: patch applied (haskell-prime-status): BangPatterns: probably accept == undecided

2008-04-21 Thread Simon Marlow

Sittampalam, Ganesh wrote:
 

Incedentally I think we should use a different operator for array
indexing, because ! is almost universally used to mean strict
now: in bang patterns, strict datatype fields, and $!.  See



http://hackage.haskell.org/trac/haskell-prime/wiki/ArrayIndexing


A lot of the discussion on that page pre-supposes that CompositionAsDot
will be accepted. Does it really stand a chance? It would be enormously
disruptive and uglify the language massively. Making it necessary to
use non-ASCII characters would be a big practical problem, I think.


Here are the possibilities for composition:

0. do nothing
1. use a Unicode operator for composition
2. require spaces around . as an operator
3. require spaces around all operators
4. use another ASCII operator for composition, e.g. 

Nothing has been decided yet, but most of the committee tends to favour 
(2), with some expressing a slight preference for (0).  We've pretty 
much ruled out (1) and (3) as too radical, and as you say using Unicode 
is still too impractical.


There is some uncertainty about the precise details of (2), and thinking 
about that is what lead to my proposal about changing the syntax of 
qualified operators.


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


Re: Haskell' - class aliases

2008-04-21 Thread Simon Marlow

Jacques Carette wrote:
I tried to see the discussion that led to class aliases being rejected 
as a proposal, but could not find links on the Wiki.  In fact, in Trac 
(#101) that proposal is still a 'maybe', but with no updates.  Is there 
a competing proposal that got accepted?


[Without a mechanism like class aliases, breaking up Num into a 
hierarchy of proper mathematical concepts becomes too unwieldly to be 
realistic.  This is a real stumbling block for anyone trying to use the 
class system to encode fine-grained mathematical concepts.]


We want to get Haskell' done, and unfortunately that may mean rejecting 
some good proposals - in this case, class aliases is a fairly large 
feature that we don't have enough experience with yet, so it was dropped 
(I proposed dropping it recently to the committee, and no-one argued 
against).


That's not to say it isn't worthwhile, and this certainly doesn't 
prevent it from being adopted in a future version of the standard.  We'd 
 like to see it implemented in GHC, too.


BTW, by the end of this process I do want to make sure we've documented 
the rationale for all the decisions, so that future committees have a 
useful knowledge base to work from.


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


Re: Proposal: change to qualified operator syntax

2008-04-21 Thread Simon Marlow

Dan Weston wrote:
Would it not be cleaner just to disallow infix notation of qualified 
operators altogether? It is clear enough to use import qualified or 
let or where clauses containing prefix notation to identify a qualified 
operator with an unqualified one:


UGLY:

m `Prelude.(=)` a
  `Prelude.(=)` b
  `Prelude.(=)` c


CLEAR:

m = a = b = c
  where (=) = Prelude.(=)

[Personally, I prefer where to let for such purely syntactic details].


I did consider doing that, and it is certainly an option.  The reasons I 
chose to allow the infix forms are:


 - if you add an import and introduce a name clash, then you want
   to resolve clashes by just modifying the names, not by
   refactoring code.  The trick from your example above works,
   but it requires that all instances of (=) are
   in scope qualified, otherwise you get a shadowing warning.

 - it's cheap in terms of grammar and implementation.

Cheers,
Simon



Dan

Simon Marlow wrote:

Folks,

Please comment on the following proposed change to qualified operator 
syntax:


  http://hackage.haskell.org/trac/haskell-prime/wiki/QualifiedOperators

Cheers,
Simon

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






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


patch applied (haskell-prime-status): add QualifiedOperators proposal

2008-04-16 Thread Simon Marlow
Wed Apr 16 10:25:08 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * add QualifiedOperators proposal

M ./status.hs +5

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080416172508-8214f-1d31cbfdec2e09db90231720fa5d207f4efa1126.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): typo

2008-04-16 Thread Simon Marlow
Wed Apr 16 10:26:16 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * typo

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080416172616-8214f-9e6f613425fd3199fbd2ff9acbb67be188734af7.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): add DerivingInstances

2008-04-15 Thread Simon Marlow
Tue Apr 15 10:50:54 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * add DerivingInstances

M ./status.hs +2

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080415175054-8214f-b951f87924270aa36c2af9110f025a6caebe0d62.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): reject caseless Underscore

2008-04-15 Thread Simon Marlow
Tue Apr 15 10:55:30 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * reject caseless Underscore

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080415175530-8214f-7a0e97f3952cddee8178c5929ae2869abb22c060.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): TypeSynonymInstances: probably accept == undecided

2008-04-15 Thread Simon Marlow
Tue Apr 15 11:10:10 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * TypeSynonymInstances: probably accept == undecided

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080415181010-8214f-eb96ed362e394a7ec5ca2d0b2849bc331d7a3b8c.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): NondecreasingIndentation: probably accept == accept

2008-04-15 Thread Simon Marlow
Tue Apr 15 11:10:51 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * NondecreasingIndentation: probably accept == accept

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080415181051-8214f-b71764fa8771790d94565efcac663d7c17356ade.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): QualifiedIdentifiers: probably accept == undecided

2008-04-15 Thread Simon Marlow
Tue Apr 15 11:11:16 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * QualifiedIdentifiers: probably accept == undecided

M ./status.hs -2 +3

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080415181116-8214f-61de042c56edab3210e49e968d9e88a24961ef1f.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): BangPatterns: probably accept == undecided

2008-04-15 Thread Simon Marlow
Tue Apr 15 11:12:08 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * BangPatterns: probably accept == undecided

M ./status.hs -2 +3

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080415181208-8214f-5e1ae9e40a9feb2afbd077b0e2f623dc0bdbd02f.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): NewtypeDeriving: probably accept == undecided

2008-04-15 Thread Simon Marlow
Tue Apr 15 11:12:27 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * NewtypeDeriving: probably accept == undecided

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080415181227-8214f-d75f6774183661274c106aded5c7a4a2d9b96cd8.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): improve [wiki:Defaulting] rules: probably accept == undecided

2008-04-15 Thread Simon Marlow
Tue Apr 15 11:12:42 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * improve [wiki:Defaulting] rules: probably accept == undecided

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080415181242-8214f-9565b50d490a06fd126df3ec64a5a4984c4fcb6c.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): KindAnnotations: probably accept == accept

2008-04-15 Thread Simon Marlow
Tue Apr 15 11:12:55 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * KindAnnotations: probably accept == accept

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080415181255-8214f-823a0b473064b7ce419f9c7418f8e9fceafa38cd.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-status): MonomorphicPatternBindings: probably accept == undecided

2008-04-15 Thread Simon Marlow
Tue Apr 15 11:13:11 PDT 2008  Simon Marlow [EMAIL PROTECTED]
  * MonomorphicPatternBindings: probably accept == undecided

M ./status.hs -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080415181311-8214f-618ae9b32fb53764506ae5552248468ba24907cf.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


  1   2   3   >