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

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

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.

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

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

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

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

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

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

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

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

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

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

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

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

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

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.

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

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

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

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

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

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

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

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

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

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,

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

Re: Negation

2010-02-14 Thread Simon Marlow
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

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

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

Re: Nominations for the Haskell 2011 committee

2009-12-30 Thread Simon Marlow
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

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:

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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)

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

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

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

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

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

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

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

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

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

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

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

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

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)

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

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

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

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

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

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

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'. :(

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

Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-24 Thread Simon Marlow
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

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

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

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

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

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

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

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'

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

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,

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

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

Re: Proposal: change to qualified operator syntax

2008-04-21 Thread Simon Marlow
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

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

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

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

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

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

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

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

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

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

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

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

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

  1   2   3   >