Re: proposal for trailing comma and semicolon

2013-08-19 Thread Ian Lynagh
On Tue, Aug 13, 2013 at 09:47:49PM +0100, Simon Marlow wrote:
> 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.

Ugh, true.

> I'd much rather leave tuples out of it: the
> precise number of commas in a tuple is significant.

It would be rather unpleasant to have

[1,2,3,] ::[Int]
(1,2,3,) :: Int -> (Int, Int, Int, Int)


Thanks
Ian


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


Re: Proposal: NoImplicitPreludeImport

2013-06-04 Thread Ian Lynagh
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

import Foo as Prelude.XYZ


Thanks
Ian
-- 
Ian Lynagh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/

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


Re: Proposal: NoImplicitPreludeImport

2013-06-04 Thread Ian Lynagh
On Tue, Jun 04, 2013 at 01:06:25PM +0100, Simon Marlow wrote:
> 
> Hardly anybody uses haskell98 or haskell2010, so we would still have
> a backwards compatibility problem.

I meant 'base' to be included in 'these packages'; I've clarified the
wiki page.


Thanks
Ian
-- 
Ian Lynagh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/

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


Re: Proposal: NoImplicitPreludeImport

2013-05-28 Thread Ian Lynagh
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.


Thanks
Ian
-- 
Ian Lynagh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/

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


Re: Proposal: NoImplicitPreludeImport

2013-05-28 Thread Ian Lynagh
On Tue, May 28, 2013 at 11:41:44AM -0400, Edward Kmett wrote:
> I'm definitely in favor of having the *option* to shut off the import of
> the Prelude without entangling the notion of overriding all of the
> desugarings.
> 
> I do, however, feel that removing the Prelude from base is a rather strong
> step, which hasn't seen much support.

Just to clarify: This proposal is to stop importing the module
implicitly, not to actually remove the module.


Thanks
Ian
-- 
Ian Lynagh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/

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


Proposal: NoImplicitPreludeImport

2013-05-28 Thread Ian Lynagh

Dear Haskellers,

I have made a wiki page describing a new proposal,
NoImplicitPreludeImport, which I intend to propose for Haskell 2014:
http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport

What do you think?


Thanks to the folks on #ghc who gave some comments on an earlier draft.


Thanks
Ian
-- 
Ian Lynagh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/


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


Re: proposal for trailing comma and semicolon

2013-05-17 Thread Ian Lynagh
On Fri, May 17, 2013 at 02:04:44PM -0400, Edward Kmett wrote:
> My main concern is its a really weird corner case for the grammar to
> remember for tuple sections and it does have very weird grammar
> specification issues.

Tuple sections could look like
(True, _)
rather than
(True,)

Does anyone know how common tuple sections are, incidentally? They've
been around since GHC 6.12, so it would be interesting to know if people
are actually using them.

> I really have no objection to it for the other cases. It'd make export
> lists cleaner,

Actually, you are already allowed an extra trailing comma in import and
export lists.

> maybe a few other cases, but how often can you really say
> you can meaningfully comment out one field of a tuple have have the
> surrounding code make any sense?

It happens occasionally, especially when simplifying code while
debugging.

Commenting out list items is much more common, though.

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.


Thanks
Ian
-- 
Ian Lynagh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/


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


Haskell 2014

2013-05-01 Thread Ian Lynagh

Dear Haskellers,

We are pleased to announce that the Haskell 2014 committee has now
formed, and we would be delighted to receive your proposals for changes
to the language. Please see
http://hackage.haskell.org/trac/haskell-prime/wiki/Process
for details on the proposal process.

The committee will meet 4 times a year, to consider proposals completed
before:
* 1st August
* 1st November
* 1st February
* 1st May
so if you have been meaning to put the finishing touches to a proposal,
then we would encourage you to do so by the end of July!

The source for the Haskell report will be updated as proposals are
accepted, but new versions of the standard will only be released once a
year, during January.

The Haskell 2014 committee is comprised of:

* Carlos Camarão
* Iavor Diatchki
* Ian Lynagh (chair)
* John Meacham
* Neil Mitchell
* Ganesh Sittampalam
* David Terei
* Bas van Dijk
* Henk-Jan van Tuyl


Thanks
Ian (Haskell 2014 committee chair)
-- 
Ian Lynagh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/


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


Re: Is it time to start deprecating FunDeps?

2013-05-01 Thread Ian Lynagh
On Tue, Apr 30, 2013 at 11:35:10PM -0400, Edward Kmett wrote:
> 
> I have dozens of classes of forms like
> 
> class Wrapped s t a b | a -> s, b -> t, a t -> s, b s -> t

Isn't this equivalent to just

class Wrapped s t a b | a -> s, b -> t

?


Thanks
Ian


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


Re: Bang patterns

2013-02-05 Thread Ian Lynagh
On Mon, Feb 04, 2013 at 07:26:16PM -0500, Edward Kmett wrote:
> If space sensitivity or () disambiguation is being used on !, could one of
> these also be permitted on ~ to permit it as a valid infix term-level
> operator?

I don't think there's any reason ~ couldn't be an operator, defined with
the
(~) x y = ...
syntax.

Allowing it to be defined with infix syntax would be a little trickier.


Hmm, I've just realised that if we decide to make !_ and !foo lexemes,
then we'd also want !(+) to be a lexeme, which presumably means we'd
want (+) to be a single lexeme too (and also `foo`, for consistency).
But I don't think making that change would be problematic.


Thanks
Ian


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


Re: Bang patterns

2013-02-04 Thread Ian Lynagh
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 !. 


Thanks
Ian


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


Re: Bang patterns

2013-02-03 Thread Ian Lynagh
On Mon, Feb 04, 2013 at 12:44:53AM +, Ben Millwood wrote:
> 
> I have two proposals, I suppose:
> - make bang patterns operate only on variables and wildcards
> - make bang patterns in let altogether invalid

Looking at this again made me realise that, as well as !_ and !varid
lexemes, we could also alter the decl production so that we get
decl -> ...
  | pat rhs -- existing lazy binding production
  | '!' pat rhs -- new strict binding production

That means that
let !(x, y) = e in ...
would still be valid, with the ! not actually being parsed as part of
the pattern, but would parse instead as a strict binding. It would be
a little ugly under the hood, as
let !x = e in ...
would parse as a lazy binding, although we'd want to treat it as a
strict binding anyway.


Thanks
Ian


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


Re: Bang patterns

2013-02-03 Thread Ian Lynagh
On Sun, Feb 03, 2013 at 10:34:04PM +, Ben Millwood wrote:
> On Fri, Feb 01, 2013 at 05:10:42PM +0000, Ian Lynagh wrote:
> >
> >The first is suggested by "A bang only really has an effect if it
> >precedes a variable or wild-card pattern" on
> >http://hackage.haskell.org/trac/haskell-prime/wiki/BangPatterns
> >
> >We could therefore alter the lexical syntax to make strict things into
> >lexems, for example
> >   reservedid -> ...
> >   | _
> >   | !_
> >   strictvarid -> ! varid
> >etc. This would mean that "f !x" is 2 lexemes, and "f ! x" 3 lexemes,
> >with the former defining the function 'f' and the latter defining the
> >operator '!'.
> >
> >This has 3 downsides:
> >
> >* It would require also accepting the more radical proposal of making
> > let strict, as it would no longer be possible to write
> >   let ![x,y] = undefined in ()
> 
> We really can't make let strict, in my view: its laziness is sort of
> fundamental. I don't see why the given example necessitates it
> though: just use case-of in that scenario.

Well, true, that's another option. It's rather unpleasant when you have
multiple bindings, as when converted to 'case's, each 'case' requires
you to indent deeper (or to use more braces).

> >The third is to parse '!' in patterns in the same way that '~' is parsed
> >in patterns, except that (!) would be accepted as binding the operator
> >'!'. This means that "f ! x" defines f.
> 
> This is roughly how it's done at present, right?

I think it's roughly what GHC does now, yes.

> You missed the option of going the way of ~ and making ! an illegal
> name for an operator. Obvious drawbacks, probably not a good idea,
> but it would be the most consistent solution, so I wouldn't dismiss
> it immediately.

Yes, OK. That's basically option 3 as far as patterns are concerned, but
also disallows ! as an operator.

> (If we do come up with a way that doesn't involve making ! illegal,
> maybe we should consider allowing ~ as an operator as well!)

Right, if we went for option 3 then making ~ an operator in the same way
as ! would be possible. I think we should be cautious about doing so,
though, as it's a semi-one-way change, i.e. once it's an operator and
people start using it it becomes a lot trickier to revert the decision.

> Anyway, in light of my above comments, I think I like the first
> option the best (so bang patterns only apply to variables, let
> doesn't become strict).

So just to clarify what you're proposing, this wouldn't be valid:
let ![x] = e in ...
and I guess these wouldn't either?:
let !x = e in ...
let [!x] = e in ...
let (x, ~(y, !z)) = e in ...
but these would?:
let f !x = e in ...
case x of ~(y, !z) -> ()

i.e. you wouldn't be able to use ! in the 'pat' in the
decl -> pat rhs
production.

You'd also no longer support:
do ![x]  <- e; ...
and so again for consistency I guess these wouldn't work?:
do !x<- e; ...
do [!x]  <- e; ...
do (x, ~(y, !z)) <- e; ...

i.e. you also wouldn't be able to use ! in the 'pat' in the
stmt -> pat <- exp ;
production.


Thanks
Ian


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


Re: Status of Haskell'?

2013-02-01 Thread Ian Lynagh
On Fri, Feb 01, 2013 at 05:31:53PM +, Malcolm Wallace wrote:
> The committee has received no nominations.

At least one was sent. Does haskell-2011-commit...@haskell.org accept
mails from non-members?


Thanks
Ian


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


Re: Status of Haskell'?

2013-02-01 Thread Ian Lynagh

Hi Malcolm,

On Wed, Dec 12, 2012 at 10:40:53AM +, Malcolm Wallace wrote:
> 
> Please send nominations to haskell-2011-commit...@haskell.org, summarising 
> your interest and experience.  The existing committee will (I hope) make some 
> decision on how to proceed, in early January 2013.

Any progress on this?


Thanks
Ian


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


Bang patterns

2013-02-01 Thread Ian Lynagh

Hi all,

I would like to get a full specification of the bang patterns syntax,
partly so it can be proposed for H', and partly so we can resolve
tickets like http://hackage.haskell.org/trac/ghc/ticket/1087 correctly.


I think there are 3 possibilities:



The first is suggested by "A bang only really has an effect if it
precedes a variable or wild-card pattern" on
http://hackage.haskell.org/trac/haskell-prime/wiki/BangPatterns

We could therefore alter the lexical syntax to make strict things into
lexems, for example
reservedid -> ...
| _
| !_
strictvarid -> ! varid
etc. This would mean that "f !x" is 2 lexemes, and "f ! x" 3 lexemes,
with the former defining the function 'f' and the latter defining the
operator '!'.

This has 3 downsides:

* It would require also accepting the more radical proposal of making
  let strict, as it would no longer be possible to write
let ![x,y] = undefined in ()

* It would mean that "f !x" and "f !(x)" are different. Probably not a
  big issue in practice.

* It may interact badly with other future extensions. For example,
{-# LANGUAGE ViewPatterns #-}
f !(view -> x) = ()
  should arguably be strict in x.
  (you might also argue that it should define the operator '!'.
  Currently, in ghc, it defines an 'f' that is lazy in x, which IMO is a
  bug).



The second is to parse '!' differently depending on whether or not it is
followed by a space. In the absence of a decision to require infix
operators to be surrounded by spaces, I think this is a bad idea: Tricky
to specify, and to understand.



The third is to parse '!' in patterns in the same way that '~' is parsed
in patterns, except that (!) would be accepted as binding the operator
'!'. This means that "f ! x" defines f.



So my proposal would be to go with option 3. What do you think? And did
I miss any better options?


Thanks
Ian


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


Re: Status of Haskell'?

2012-11-27 Thread Ian Lynagh
On Tue, Nov 27, 2012 at 11:44:51AM -0500, Brandon Allbery wrote:
> On Tue, Nov 27, 2012 at 10:50 AM, Nate Soares  wrote:
> 
> > I second this question. At what point do we cut Haskell' with what we
> > have, release it, and push the big undecideds back to Haskell"?
> 
> Maybe the question is whether we have anything.  We already skipped 2011
> because there wasn't anything worth the effort of a new standard.

FWIW, I stopped working on writing things up as proposals after (TTBOMK)
http://www.haskell.org/pipermail/haskell-prime/2011-February/003362.html
didn't happen.

The big things (GADTs, FD vs AT, etc) are probably still some way off,
but there are plenty of incremental changes that we could make now to
improve the language. For example, adding negative literals should be
simple and would be nice to have, and adding DeriveDataTypeable
hopefully wouldn't be too controversial and would help us reach a point
where people don't feel the need to use CPP and/or hand-write instances.


Thanks
Ian


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


Re: String != [Char]

2012-03-26 Thread Ian Lynagh
On Mon, Mar 26, 2012 at 08:20:45AM -0700, Johan Tibell wrote:
> On Mon, Mar 26, 2012 at 7:48 AM, Malcolm Wallace  
> wrote:
> >> In the region of this side of the Atlantic Ocean where I teach, the
> >> student population is very diverse
> >
> > Prelude> putStrLn (take 5 "Fröhßen")
> > Fröhß
> 
> ghci> putStrLn "Fro\x0308hßen"
> Fröhßen
> ghci> putStrLn (take 5 "Fro\x0308hßen")
> Fröh
> 
> Your example works because your input happens to be in a normal form.

I am very unicode-ignorant, so apologies if I have misunderstood
something, but doesn't Text do the same thing?

Prelude T> import Data.Text.IO as T
Prelude T T> T.putStrLn (T.take 5 (T.pack "Fro\x0308hßen"))
Fröh

Maybe your point is that neither "take" function should be used with
unicode strings, but I don't see how advocating the Text type is going
to help with that.


Thanks
Ian


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


Re: String != [Char]

2012-03-24 Thread Ian Lynagh
On Sat, Mar 24, 2012 at 05:31:48PM -0400, Brandon Allbery wrote:
> On Sat, Mar 24, 2012 at 16:16, Ian Lynagh  wrote:
> 
> > On Sat, Mar 24, 2012 at 11:50:10AM -0700, Johan Tibell wrote:
> > > Using list-based operations on Strings are almost always wrong
> >
> > Data.Text seems to think that many of them are worth reimplementing for
> > Text. It looks like someone's systematically gone through Data.List.
> > And in fact, very few functions there /don't/ look like they are
> > directly equivalent to list functions.
> >
> 
> I was under the impression they have been very carefully designed to do the
> right thing with characters represented by multiple codepoints, which is
> something the String version *cannot* do.  It would help if Bryan were
> involved with this discussion, though.  (I'm cc:ing him on this.)  Since
> the whole point of Data.Text is to handle stuff like this properly I would
> be surprised if your assertion that
> 
> > upcase :: String -> String
> > > upcase = map toUpper
> >
> > This is no more incorrect than
> >upcase = Data.Text.map toUpper
> 
> is correct.

I don't see how it could do any better, given both use
toUpper :: Char -> Char
to do the hard work. That's why there is also a
Data.Text.toUpper :: Text -> Text

Based on a very quick skim I think that there are only 3 such functions
in Data.Text (toCaseFold, toLower, toUpper), although the 3
justification functions may handle double-width characters properly.


Anyway, my main point is that I don't think that either text or String
should make it any easier for people to get things right. It's true that
currently only text makes correct case-conversions easy, but only
because no-one's written Data.String.to* yet.


Thanks
Ian


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


Re: String != [Char]

2012-03-24 Thread Ian Lynagh
On Sat, Mar 24, 2012 at 08:38:23PM +, Thomas Schilling wrote:
> On 24 March 2012 20:16, Ian Lynagh  wrote:
> >
> >> Correctness
> >> ==
> >>
> >> Using list-based operations on Strings are almost always wrong
> >
> > Data.Text seems to think that many of them are worth reimplementing for
> > Text. It looks like someone's systematically gone through Data.List.
> 
> That's exactly what happened as part of the platform inclusion
> process.  In fact, there was quite a bit of bike shedding whether the
> Text API should be compatible with the list API or not.  In the end
> the decision was made to add all the list functions even if that
> encouraged running into unicode issues.  I'm pretty sure you
> participated in that discussion.

As far as I remember, a few functions were added to text and bytestring
during that, but mostly the discussion was about naming.

Even in the first 0.1 release of bytestring:
  http://hackage.haskell.org/packages/archive/text/0.1/doc/html/Data-Text.html
there is a large amount of Data.List covered, e.g. map, transpose,
foldl1', minimum, mapAccumR, groupBy.


Thanks
Ian


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


Re: String != [Char]

2012-03-24 Thread Ian Lynagh

Hi Johan,

On Sat, Mar 24, 2012 at 11:50:10AM -0700, Johan Tibell wrote:
> 
> On Sat, Mar 24, 2012 at 12:39 AM, Heinrich Apfelmus
>  wrote:
> > Which brings me to the fundamental question behind this proposal: Why do we
> > need Text at all? What are its virtues and how do they compare? What is the
> > trade-off? (I'm not familiar enough with the Text library to answer these.)
> >
> > To put it very pointedly: is a %20 performance increase on the current
> > generation of computers worth the cost in terms of ease-of-use, when the
> > performance can equally be gained by buying a faster computer or more RAM?
> > I'm not sure whether I even agree with this statement, but this is the
> > trade-off we are deciding on.
> 
> Correctness
> ==
> 
> Using list-based operations on Strings are almost always wrong

Data.Text seems to think that many of them are worth reimplementing for
Text. It looks like someone's systematically gone through Data.List.
And in fact, very few functions there /don't/ look like they are
directly equivalent to list functions.

> , as
> soon as you move away from English text. You almost always have to
> deal with Unicode strings as blobs, considering several code points at
> once. For example,
> 
> upcase :: String -> String
> upcase = map toUpper

This is no more incorrect than
upcase = Data.Text.map toUpper

There's no reason that there couldn't be a Data.String.toUpper
corresponding to Data.Text.toUpper.

> Performance
> ===
> 
> Depending on the benchmark, the difference can be much bigger than
> 20%. For example, here's a comparison of decoding UTF-8 byte data into
> a String vs a Text value:

I think Heinrich meant 20% performance in a useful program, not a
micro-benchmark.


Thanks
Ian


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


Re: What is a punctuation character?

2012-03-16 Thread Ian Lynagh

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


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


Re: FW: 7.4.1-pre: Show & Integral

2011-12-24 Thread Ian Lynagh
On Fri, Dec 23, 2011 at 05:41:23PM +, Simon Peyton-Jones wrote:
> I'm confused too.  I'd welcome clarification from the Haskell Prime folk.

We use the library process to agree changes to the libraries, and
Haskell' should then incorporate the changes into the next version of
the standard.


Thanks
Ian


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


Re: Proposal: Make gcd total

2011-05-25 Thread Ian Lynagh
On Wed, May 25, 2011 at 08:24:52PM +0200, Daniel Fischer wrote:
> 
> If it's considered to be a small enough change so a libraries proposal 
> would be sufficient, all the better, but if not, I'd like to pursue the 
> haskell-prime process further.

My understanding is that for changes to libraries mentioned in the
language report, we use the libraries@ process, not the H' process.


Thanks
Ian


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


Re: Announce: ~Haskell 2011

2011-02-06 Thread Ian Lynagh
On Fri, Jan 07, 2011 at 06:39:11PM +, Malcolm Wallace wrote:
>
>  (b) this delta will be applied to the 2010 Report to form a new  
> baseline;

Did this happen? If so, where is it?

I only found:
http://darcs.haskell.org/haskell-prime-report/
which hasn't had a patch since Jul 21 2009, and:
http://darcs.haskell.org/haskell98-report/
http://darcs.haskell.org/haskell2010-report/
which are for older versions of the standard.

>  (a) we wish to accept the NoDatatypeContexts proposal
>  http://hackage.haskell.org/trac/haskell-prime/wiki/NoDatatypeContexts

Shouldn't
http://hackage.haskell.org/trac/haskell-prime/ticket/139
be state "accepted" and closed now, then?


Thanks
Ian


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


Re: Reform of the Monad, and Disruptive Change

2011-02-04 Thread Ian Lynagh
On Fri, Feb 04, 2011 at 12:49:09PM +0200, Dark Lord wrote:
> On 04/02/2011 12:08, Malcolm Wallace wrote:
> > I suggested, and several people +1'd, that if we are making disruptive 
> > changes to the standard libraries defined in the
> > Language Report (especially the Prelude), then we should aim to make a 
> > thorough job of cleaning up all the cruft and
> > redesigning in a single strike. This means not just rearranging the Monad 
> > hierarchy, but looking at I/O types,
> > exceptions, the default strictness of foldl, and much much more. I would 
> > expect the language committee to get involved
> > in reviewing the decisions of the base library strike force.
> >
> > Then (for instance) ghc could make a major release with the refreshed 
> > libraries, and after a little experience in the
> > field (and perhaps a few patches), the libraries would then proceed to be 
> > blessed as part of the subsequent language
> > standard.
>
> I thoroughly agree with this. However, in the event that this does not 
> happen, piecemeal fixes are better than none.
>
> (Seeing as the inertia in Haskell is such that Haskell 2011 was 
> cancelled, and Haskell Platform 2011 contains no new packages, such a 
> task force doesn't seem very likely.)

Also note that the H' process is the way it is because "fix everything
at once" in the language turned out to be infeasible. The same may or
may not be true for the libraries.

I don't object to a "fix everything at once" libraries change, but in
the absence of it happening, fixing things individually is also good
with me.

(where "individually" would still mean, for example, all Monad class
reshuffling should happen at once, but the strictness of foldl' would be
a separate change).


Thanks
Ian


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


Re: Announce: ~Haskell 2011

2011-01-07 Thread Ian Lynagh
On Fri, Jan 07, 2011 at 06:39:11PM +, Malcolm Wallace wrote:
>
>  (a) we wish to accept the NoDatatypeContexts proposal

Hurrah!

>  (b) this delta will be applied to the 2010 Report to form a new  
> baseline;
>  (c) we will _not_ issue a new language standard called 2011;
>  (d) we intend to issue a new language standard in 2012;

Have you considered deciding about individual proposals as and when they
are completed, rather than making a decision about all proposals each
September? This could also avoid merge-conflicts between the report
deltas for proposals that touch the same bit of the report.


Thanks
Ian


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


Haskell 2011?

2011-01-05 Thread Ian Lynagh

Hi all,

I haven't heard anything about Haskell 2011 since
http://www.haskell.org/pipermail/haskell-prime/2010-August/003263.html

Can someone let me know what's happening please? Will there be a Haskell
2011?


Thanks
Ian


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


Re: ExplicitForAll complete

2011-01-05 Thread Ian Lynagh
On Fri, Dec 24, 2010 at 11:31:17PM +0100, Lennart Augustsson wrote:
> I think they are equally feasible, but as Simon says, we have avoided
> introducing new global keywords.
> And I think we should avoid it this time too.  Why break programs when we
> don't have to.

I've added an alternative delta to the page, where forall is only a
keyword in types. The committee can choose which they prefer.


Thanks
Ian


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


Re: ExplicitForAll complete

2010-12-24 Thread Ian Lynagh
On Thu, Dec 23, 2010 at 09:46:29AM +, Simon Marlow wrote:
>
> 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.

Why is 'case'-only-in-expression harder than 'forall'-only-in-type?

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

Yup.


Thanks
Ian


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


Re: ExplicitForAll complete

2010-11-22 Thread Ian Lynagh
On Mon, Nov 22, 2010 at 02:36:51PM -0500, Isaac Dupree wrote:
>
> P.S. IMHO capitalization, ExplicitForAll vs ExplicitForall, let's stick  
> to one.  The extension is written ExplicitForall.

GHC only knows about ExplicitForAll. I think this was a mistake, but I
don't think it's worth changing now (assuming the proposal is accepted),
as shortly after it is part of H' it won't be necessary to refer to it
by name in new code anyway.


Thanks
Ian

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


Re: ExplicitForAll complete

2010-11-22 Thread Ian Lynagh

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.

> * It seems that allowing "superflous" values in "foralls" could be
> useful for some future extensions.  For example, if we had scoped type
> variables and explicit type application, then it may make sense to
> have quantified variables that do not appear
> in the rest of the type (but do appear in the definition of the
> function).  I guess, we could revise things again if that was to ever
> happen but still, it seems to me that this might be more appropriate
> as an "unused variable" warning, rather then an error?

"Eq a => Int" isn't a valid type, so I don't think "forall a . Int"
should be either. As you say, it's possible that future extensions will
generalise this.

> *  Is there any case where an empty "forall" is useful, and if not,
> why allow it?  I guess it is a way to make it explicit that a value is
> monomorphic but i think that types like "forall. Int" look odd.

I don't mind either way.


Thanks
Ian

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


Re: [Haskell] typo in Haskell definition

2010-11-20 Thread Ian Lynagh
On Sat, Nov 20, 2010 at 08:56:52PM +0200, Yitzchak Gale wrote:
> 
> I don't seem to be able to log in to the trac, so
> perhaps someone else will submit the ticket.

Done: http://hackage.haskell.org/trac/haskell-prime/ticket/142


Thanks
Ian

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


ExplicitForAll complete

2010-11-19 Thread Ian Lynagh

Hi all,

I've completed the ExplicitForAll proposal, started by Niklas Broberg
(but any errors are doubtless mine!):

http://hackage.haskell.org/trac/haskell-prime/wiki/ExplicitForall
http://hackage.haskell.org/trac/haskell-prime/ticket/133

I imagine this is too late for H2011 (if that will actually be
happening?), but there wasn't an H2012 milestone, so I put it in H2011
anyway. Please feel free to remilestone.


Thanks
Ian

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


Small report fixes

2010-11-19 Thread Ian Lynagh

Hi all,

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


Thanks
Ian

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


Re: new keyword: infixlr?

2010-09-12 Thread Ian Lynagh
On Fri, Sep 10, 2010 at 11:14:53PM +0200, S. Doaitse Swierstra wrote:
> 
> On 10 sep 2010, at 20:13, Ian Lynagh wrote:
> 
> > On Fri, Sep 10, 2010 at 07:51:10PM +0200, S. Doaitse Swierstra wrote:
> >> 
> >> Currently Haskell has infix, infixl and infixr operators. I see a use for 
> >> infixlr as well. This indicates that the implemtation may assume the 
> >> operator to be associative, and thus has the freedom to "balance" an 
> >> expression containing several operator occurrences.
> > 
> > Would it be restricted to use with operators with types that are (a -> a
> > -> a) (or more specific)?
> 
> This is what I would normally expect from an infix operator. 

I assume you mean "an associative operator", but even then it's not true
for (.).

And just because it is what you would expect, does not mean that people
will only use it in that way if the type system does not enforce it!

A detail is whether
x ^^^ y = x ^ y
infixlr ^^^
is rejected, or gives
(^^^) :: (Num a, Integral a) => a -> a -> a

Although I guess if you require the compiler to give you the balanced
parse, there's no technical need to restrict the type of the operator as
it's deterministic.

Overall, my feeling is that this syntax feels very specialised and
fiddly, and would be better handled by a more general machanism similar
to GHC's RULE pragma, or by quasi-quotes or TH, or even by a domain
specific optimiser plugin which can see the result of inlining etc.


Thanks
Ian

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


Re: new keyword: infixlr?

2010-09-10 Thread Ian Lynagh
On Fri, Sep 10, 2010 at 07:51:10PM +0200, S. Doaitse Swierstra wrote:
> 
> Currently Haskell has infix, infixl and infixr operators. I see a use for 
> infixlr as well. This indicates that the implemtation may assume the operator 
> to be associative, and thus has the freedom to "balance" an expression 
> containing several operator occurrences.

Would it be restricted to use with operators with types that are (a -> a
-> a) (or more specific)?

Otherwise e.g.
let (+:) = (:)
infixlr :+
in [] +: [] +: []
could have type [[a]] or [[[a]]].

> The reason that I bring up this is that in a new combinator I have added to 
> my parser library (the <||> in Text.ParserCombinators.UU.Derived) internally 
> uses cartesian products, which are being constructed and updated. If the 
> compiler had the right to interpret  the expressions a <||> b <||>c <||> d  
> as e.g. (a <||> b) <||> (c <||> d) then the updating time for would go down 
> from O(n) to O(log n). 

How would the compiler work out which parsing to prefer? Or would it
assume that infixlr expressions are best balanced?

When first reading the proposal, I thought the idea was to allow the
compiler to more easily perform optimisations like
a+b+c+2+3+d => a+b+c+5+d
but I guess that wasn't something you were thinking about?


Thanks
Ian

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


Re: preparing for Haskell 2011

2010-08-11 Thread Ian Lynagh
On Mon, Aug 09, 2010 at 04:25:18PM +0100, Malcolm Wallace wrote:
>
> Can I therefore encourage any people who have made proposals, either  
> informally on mailing lists, or formally in the Haskell-prime ticket  
> system, to consider what they need to do to bring those proposals to a  
> state where the committee can vote on them.

I believe
http://hackage.haskell.org/trac/haskell-prime/wiki/NoDatatypeContexts
is ready; please let me know if there's something else I need to do.


Thanks
Ian

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


Re: prefix operators

2010-07-20 Thread Ian Lynagh
On Tue, Jul 13, 2010 at 01:52:36PM +0100, Simon Marlow wrote:
>
> 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.

It adds a couple of rules to accept (but whine about) the two most
common problems with the alternative layout rule:
`where' clause at the same depth as implicit layout block
`|' at the same depth as implicit layout block

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

I think I agree that a simpler rule, but more breakage of existing code,
would be better. I don't expect I'll have time to do the necessary
experimentation etc in the H2011 timeframe.


Thanks
Ian

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


Propsal: NoDatatypeContexts

2010-07-18 Thread Ian Lynagh

Hi all,

H98 and H2010 allow a context to be given for datatypes, e.g. the
"Eq a" in

data Eq a => Foo a = Constr a

I have made a proposal to remove support for that context (ticket #139).
More details are on the proposal wiki page:

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


Thanks
Ian

___
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 Ian Lynagh
On Tue, Jun 29, 2010 at 04:01:54PM +0100, Simon Marlow wrote:
> 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

Great work! I noticed a few things as I skimmed through it:

p12(x) "It too is intended to be a" ->
   "It too was intended to be a"

p40(24) In "local bindings are of the form let decls." there is a lot
more white space between "let" and "decls" than there is in the
BNF on the previous page

p60(44) There are some odd-looking spaces before closing parentheses in
the first paragraph.

p62(46) "Ix" -> "Data.Ix" (3 times)

p79(63) "Maybe" -> "Data.Maybe"

p82(66) "List" -> "Data.List"

p121(105) "Char, Monad, IO, and Numeric" ->
  "Data.Char, Control.Monad, System.IO and Numeric"

p121(105) "List" -> "Data.List"

p122(106) "Ratio" -> "Data.Ratio"

p133(117) "Char" -> "Data.Char"

p139(123) "Char" -> "Data.Char"

p171(155) "module provide the" ->
  "module provides the"

p171(155) This is a bit klunky, talking about Control.Monad providing
  things that are actually defined in the Prelude. The
  "The instances of Functor [...] defined in the Prelude" is odd
  if you don't realise that.

p172(156) Do you mean to have these instances?:
  instance Functor ReadP
  instance Monad P
  instance Monad ReadP

p173(157) I don't think the report should refer to the mtl package.

p173(157) Do you mean to have these instances?:
  instance MonadPlus P
  instance MonadPlus ReadP

p175(159) Odd space after "xm" in "[x1, x2, ..., xm ]"

p177(161) The "module Data.Ix" looks confusing; I assume it's being
  listed as an export? The paragraph above it doesn't look
  associated with it.

p178(162) Talks about the difference between H98 and GHC

p178(162) "nonstrict" -> "non-strict"

p179(163) Is strictness of the accumulating function actually relevant?

p179(163) Talks about the difference between H98 and GHC

p180(164) "module  Array" -> "module Data.Array"
  "module Ix" -> "module Data.Ix"
  "import Ix" -> "import Data.Ix"
  "import List" -> "import Data.List"
  Something has gone wrong with 2 of the error calls.

p186(170) Do you mean to have these instances?:
  instance Bits WordPtr
  instance Bits IntPtr

p193(177) Do you mean to have these instances?:
  instance Typeable1 Complex
  instance (Data a, RealFloat a) => Data (Complex a)

p194(178) "module Complex" -> "module Data.Complex"

p195(179) Bad indentation in the Fractional instance

p197(181) "see the section of the Haskell report dealing with arithmetic
  sequences)" should be a link

p201(185) three bullet points are indented more than the other one

C20: There are a number of references to "Data.List.foo" rather than
 just "foo", presumably from when the docs were in the Prelude
 rather than Data.List

C20: In example, sometimes "==" is used but in other cases "->" is used

p222(206) "module Maybe" -> "module Data.Maybe"

p226(210) "module  Ratio" -> "module Data.Ratio"

p227(211) Bad indentation in Show instance

p229(213) I don't understand "One non-obvious consequence of this is
  that negate should not raise an error on negative arguments."

p229(213) "see the section of the Haskell report dealing with arithmetic
  sequences" should be a link

p235(219) Do you mean to have these instances?:
  instance Typeable ExitCode
  instance Exception ExitCode

p236(220) "sucessfully" ->
  "successfully"

p244(228) "Construct a Haskell 98 I/O error"

p245(229) "additionlly" ->
  "additionally"

p252(236) onwards: Lots of Typeable instances, and Typeable is also
   given in the list of classes in the 30.1.1, 30.1.2
   and 30.1.3 opening paragraphs.

p258(242) Talks about Data.Time

p262(246) "A Finalizer" ->
  "A finalizer"

p262(246) "like addForeignPtrFinalizerEnv" ->
  "Like addForeignPtrFinalizerEnv"

p263(247) Mentions MVars

p263(247) I don't think there should be GHC notes in the report

p270(254) Delete "This version traverses the array backwards using an
  accumulating parameter, which uses constant stack space. The
  previous version using mapM needed linear stack space."

p276(260) "marshall" ->
  "marshal"

p278(262) Why is e.g. "Char" unqualified but "Prelude.Double" qualified?

p285(269) Do you mean to have these instances?:
  instance Storable WordPtr
  instance Storable IntPtr

p289(273) "System.IO.openFile" ->
  "openFile"

p291(275) "System.IO.hFlush" ->
  "hFlush"
  (twice)

p291(275) "System.IO.hlookAhead" ->
  "hlookAhead"


Thanks
Ian

__

Re: Haskell 2010 draft report

2010-05-02 Thread Ian Lynagh
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:

p166: Does anything support these?:
  DoAndIfThenElse, HierarchicalModules, FixityResolution,
  LineCommentSyntax, LanguagePragma
  Should "RelaxedDependencyAnalysis" be "RelaxedPolyRec"?
  "EmptyDataDeclarations" should be "EmptyDataDecls".


Thanks
Ian

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


Re: Haskell 2010 draft report

2010-05-02 Thread Ian Lynagh
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.

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


Thanks
Ian

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


Re: Haskell 2010 libraries

2010-05-01 Thread Ian Lynagh
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?

>>> 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!

Heh, true. I meant that e.g.
ghc --language haskell2010 -package base ...
would give an error.


Thanks
Ian

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


Re: Haskell 2010 libraries

2010-05-01 Thread Ian Lynagh
On Fri, Apr 30, 2010 at 09:37:39PM +0100, Simon Marlow wrote:
> 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.

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

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

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.

> 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.

> 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.


Thanks
Ian

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


Re: Haskell 2010 draft report

2010-05-01 Thread Ian Lynagh
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.

p42: The negative literal alternative in pat is redundant

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,

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


Thanks
Ian

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


Re: Haskell 2010 draft report

2010-04-30 Thread Ian Lynagh
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:

p10: Typo "Februrary"
p10: The new (purple) bullet points do not end in full stops, while the
 old (black) ones do

p11: "Audrey Tang" is not alphabetically placed
p11: Missing linebreak after "John Goerzen"
p11: Missing vowel in "Andres Lh"
p11: Alphabetical order breaks down for surnames beginning 'M'/'N'

p12: Aerts/Aberg out of order
p12: Blott/Blenko out of order
p12: Wolfram Kahl is listed twice
p12: Ralf Hinze is in both the "committee" and the "other" list
p12: Simon Thompson is in both the "committee" and the "other" list


Thanks
Ian

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


Re: showing Ratios

2010-02-25 Thread Ian Lynagh
On Thu, Feb 25, 2010 at 09:54:04AM -0500, Doug McIlroy wrote:
> Very minor library change to promote readability of output:
> eliminate spaces in the string representation of Ratios.
> 
> Currently, a Ratio appears as a pair separated by " % ".
> The spaces that flank "%" make for confusing output.
> Example:
> 
>   [1 % 2,1 % 3,1 % 4,1 % 5,1 % 6]
> 
> The spaces suggest that "," binds more tightly than "%".
> I claim that
> 
>   [1%2,1%3,1%4,1%5,1%6]

See also:

http://www.mail-archive.com/glasgow-haskell-b...@haskell.org/msg14853.html
http://hackage.haskell.org/trac/ghc/ticket/1920

A comment in the code says:
-- H98 report has spaces round the %
-- but we removed them [May 04]
-- and added them again for consistency with
-- Haskell 98 [Sep 08, #1920]


Thanks
Ian

___
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 Ian Lynagh
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.


Thanks
Ian

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


Re: Negation

2010-02-13 Thread Ian Lynagh
On Sun, Feb 14, 2010 at 03:21:54AM +0100, 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.

Then what do you think the grammar should say instead?

That sections should be
( fexp qop )
?

I've never been keen on
(1 * 2 +)
actually; and I've just discovered that hugs doesn't accept it.


Thanks
Ian

> On Sun, Feb 14, 2010 at 1:48 AM, John Launchbury  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?
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Negation

2010-02-08 Thread Ian Lynagh
On Mon, Feb 08, 2010 at 04:59:59PM +, Ross Paterson wrote:
> 
> But I agree they should all be legal, i.e. that unary minus should bind
> more tightly than any infix operator (as in C).

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


Thanks
Ian

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


Re: DoAndIfThenElse

2009-11-26 Thread Ian Lynagh
On Thu, Nov 26, 2009 at 03:14:13PM +0100, Christian Maeder wrote:
> David Virebayre schrieb:
> > 
> > On Thu, Nov 26, 2009 at 10:29 AM, Christian Maeder
> > mailto:christian.mae...@dfki.de>> wrote:
> > 
> > I wonder why I still get a "parse error (possibly incorrect
> > indentation)" for:
> > 
> > \begin{code}
> > main = do
> >  if True then putStrLn "1"
> >  else putStrLn "2"
> > \end{code}
> 
> This works with hugs!
> 
> >  
> > Isn't the proposal about :
> > 
> > \begin{code}
> > main = do
> >  if True then putStrLn "1"
> >  ;else putStrLn "2"
> > \end{code}
> 
> This does not work with hugs. ";" must be indented further.
> 
> \begin{code}
> main = do
>   if True then putStrLn "1";
>   else putStrLn "2"
> \end{code}
> 
> This does also not work with hugs (";" at the end)

In both cases you have 2 semi-colons before the else (after the layout
rule has been applied).


Thanks
Ian

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


Re: DoAndIfThenElse

2009-11-26 Thread Ian Lynagh

Hi Christian,

On Thu, Nov 26, 2009 at 10:29:10AM +0100, Christian Maeder wrote:
> 
> seeing Haskell 2010 and
> http://hackage.haskell.org/trac/haskell-prime/wiki/DoAndIfThenElse
> 
> saying:
> Compiler support ¶
> GHC   full (no flag)
> 
> I wonder why I still get a "parse error (possibly incorrect
> indentation)" for:
> 
> \begin{code}
> main = do
>   if True then putStrLn "1"
>   else putStrLn "2"
> \end{code}
> 
> Can I try out this feature somehow?

I can't see any support for it in GHC, even in the HEAD. The page claims
"full (no flag)" for every implementation, so I'd guess it's just a
boilerplate table that hasn't been properly filled in.


Thanks
Ian

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


Re: [Haskell'-private] StricterLabelledFieldSyntax

2009-08-13 Thread Ian Lynagh
On Wed, Aug 12, 2009 at 11:45:04PM -0700, John Meacham wrote:
> 
> Also, what about data declarations? Would we need something like below?
> It seems odd to apply such a rule sometimes but not others.
> 
> > data Foo = (Foo { .. }) | ...

You would not need these parentheses; nor would you need parentheses in

foo = Foo { ... }


Thanks
Ian

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


Re: Haskell 2010: libraries

2009-07-27 Thread Ian Lynagh
On Tue, Jul 14, 2009 at 01:57:34PM +0100, Ian Lynagh wrote:
> On Tue, Jul 14, 2009 at 12:23:51PM +0100, Duncan Coutts wrote:
> > On Tue, 2009-07-14 at 00:20 +0100, Ian Lynagh wrote:
> > > On Mon, Jul 13, 2009 at 09:56:50PM +0100, Duncan Coutts wrote:
> > > > 
> > > To take one example, since List was immortalised in the H98 report with
> > > 104 exports, Data.List has gained an additional 7 exports:
> > >
> > > The last change (making the behaviour of the generic* functions
> > > consistent with their non-generic counterparts) was less than a year
> > > ago, and the last additions were less than 2.
> > 
> > Though also note that we have not changed any of the existing ones.
> 
> Yes we have, less than a year ago:

Also, we've just had a proposal to change some others:
Generalize the type of Data.List.{deleteBy, deleteFirstsBy}
http://hackage.haskell.org/trac/ghc/ticket/3399

Both functions are spec in List in haskell98:
http://haskell.org/onlinereport/list.html


Thanks
Ian

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


Re: StricterLabelledFieldSyntax

2009-07-26 Thread Ian Lynagh
On Sun, Jul 26, 2009 at 10:16:28PM +0300, Iavor Diatchki wrote:
> 
> On Sun, Jul 26, 2009 at 10:01 PM, Isaac
> Dupree 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


Re: StricterLabelledFieldSyntax

2009-07-26 Thread Ian Lynagh
On Sun, Jul 26, 2009 at 03:24:03PM +0100, Neil Mitchell wrote:
> 
> I haven't seen anyone else claim to use the current more liberal
> syntax for fields, but I know that I do rather extensively. I would
> consider:
> 
> Just A {a = 1}
> 
> To be confusing, but if you simply omit the space:
> 
> Just A{a = 1}
> 
> I now find that perfectly clear and unambiguous.

I did consider allowing that, perhaps by making "Foo{" a single token,
but I couldn't see a clean way to do it.

Personally, I prefer rejecting it anyway.


Thanks
Ian

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


Re: StricterLabelledFieldSyntax

2009-07-26 Thread Ian Lynagh
On Sun, Jul 26, 2009 at 03:46:41PM +0200, Sean Leather wrote:
> On Sun, Jul 26, 2009 at 13:41, Ian Lynagh wrote:
> 
> > Would it be useful to add an example with the appropriate parentheses?
> >
> > I'm not sure I understand what sort of an example you want. Isn't
> >Just (A {x = 5})
> > one?
> >
> 
> I think an example should be added to the report itself with a mention of
> the change from the previous edition. (Any reasonable example will do.)
> Looking through the proposal's "Report Delta," I didn't see such a change,
> though perhaps it escaped me.

Ah, I see what you mean.

In my opinion the report should just define the language that it
defines. One should be able to take the report and implement the
language, without being distracted by all the differences between it and
other language definitions.

I'm assuming that the polished addenda will be kept and linked from the
language reports page, for people who want to see what's changed, or who
want to add support for the changes to an older implementation.


I think that even an example of where parentheses are needed would be
noise in the report. I don't think the report generally gives examples
for this sort of thing, e.g. I don't think there's an example to
demonstrate that this is invalid without parentheses:
id if True then 'a' else 'b'


If there is a consensus that examples like this should be added then I
will add them, though.


Thanks
Ian

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


Re: StricterLabelledFieldSyntax

2009-07-26 Thread Ian Lynagh
On Sun, Jul 26, 2009 at 09:21:06AM +0100, Jon Fairbairn wrote:
> Ian Lynagh  writes:
> > http://hackage.haskell.org/trac/haskell-prime/wiki/StricterLabelledFieldSyntax
> 
> I approve of the principle -- the binding level is confusing, but I
> would far rather make a bigger change, so that rather than being
> confusable with the binding level of function application, it /has/ the
> binding level of function application. ie, instead of a{x=42} one would
> have to write {x=42}a
>
> This would allow a future change [...]
> 
> Would it be proper to create a counterproposal for this syntax?
> ReversedLabelledFieldSyntax?

I would claim that, of the existing Haskell code,
StricterLabelledFieldSyntax only rejects unclear ("bad") code, and
requiring it be changed (to be made clearer) is a good thing.

Your proposal would reject /all/ labelled field code, "good" and "bad"
alike. That's a much harder sell, especially without the "future change"
being fleshed out or agreed upon.


All just my opinion, of course! The only way to find out for sure is to
make the proposal and see what happens.


Thanks
Ian

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


Re: StricterLabelledFieldSyntax

2009-07-26 Thread Ian Lynagh
On Sun, Jul 26, 2009 at 09:40:40AM +0200, Sean Leather wrote:
> > I've made a ticket and proposal page for making the labelled field
> > syntax stricter
> >
> 
> I'm definitely in favor of this change. I only have an issue with calling it
> "stricter." Maybe it's just me, but strictness doesn't provoke the expected
> image in this case. More like lower precedence.

I'm happy with it being given a different name.

> Would it be useful to add an example with the appropriate parentheses?

I'm not sure I understand what sort of an example you want. Isn't
Just (A {x = 5})
one?


Thanks
Ian

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


Re: StricterLabelledFieldSyntax

2009-07-26 Thread Ian Lynagh
On Sat, Jul 25, 2009 at 09:45:18PM -0400, Isaac Dupree wrote:
> Ian Lynagh wrote:
>> Hi all,
>>
>> I've made a ticket and proposal page for making the labelled field
>> syntax stricter, e.g. making this illegal:
>>
>> data A = A {x :: Int}
>>
>> y :: Maybe A
>> y = Just A {x = 5}
>>
>> and requiring this instead:
>>
>> data A = A {x :: Int}
>>
>> y :: Maybe A
>> y = Just (A {x = 5})
>
> and, as currently, "(f some expression) {x=5}" still requires those  
> parentheses also?  Although depending on the surroundings, after this  
> proposal, it might need to become "((f some expression) {x=5})"

Yes, exactly. I've added this to the wiki page:

No additional programs are accepted by this change, and no programs
have their behaviour changed. This change only rejects some programs
that were previously accepted.


Thanks
Ian

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


StricterLabelledFieldSyntax

2009-07-25 Thread Ian Lynagh

Hi all,

I've made a ticket and proposal page for making the labelled field
syntax stricter, e.g. making this illegal:

data A = A {x :: Int}

y :: Maybe A
y = Just A {x = 5}

and requiring this instead:

data A = A {x :: Int}

y :: Maybe A
y = Just (A {x = 5})

http://hackage.haskell.org/trac/haskell-prime/ticket/132
http://hackage.haskell.org/trac/haskell-prime/wiki/StricterLabelledFieldSyntax


Thanks
Ian

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


NoMonomorphismRestriction

2009-07-25 Thread Ian Lynagh

Hi all,

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


Thanks
Ian

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


NoNPlusKPatterns

2009-07-24 Thread Ian Lynagh

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.


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.


Thanks
Ian

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


patch applied (haskell-prime-report): Tweak rule so make knows how to create haskell.idx

2009-07-24 Thread Ian Lynagh
Tue Jul 21 04:06:30 PDT 2009  Ian Lynagh 
  * Tweak rule so make knows how to create haskell.idx

M ./report/Makefile -1 +1

View patch online:
http://darcs.haskell.org/haskell-prime-report/_darcs/patches/20090721110630-3fd76-830582c20b8ab7ea571049b4de25b042db91f04f.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-report): Refactor away old-fashioned make syntax

2009-07-24 Thread Ian Lynagh
Tue Jul 21 04:03:50 PDT 2009  Ian Lynagh 
  * Refactor away old-fashioned make syntax

M ./report/Makefile -7 +5

View patch online:
http://darcs.haskell.org/haskell-prime-report/_darcs/patches/20090721110350-3fd76-a6176df5dc492d5b34cb2dfed4a31f84870272e2.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-report): Remove duplicate haskell.dvi dependencies

2009-07-24 Thread Ian Lynagh
Tue Jul 21 03:47:49 PDT 2009  Ian Lynagh 
  * Remove duplicate haskell.dvi dependencies

M ./report/Makefile -2

View patch online:
http://darcs.haskell.org/haskell-prime-report/_darcs/patches/20090721104749-3fd76-56eaacd95457f668692292862b7b07915af7635f.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-report): Everyone has perl, clean Prelude*.tex too

2009-07-24 Thread Ian Lynagh
Tue Jul 21 03:39:57 PDT 2009  Ian Lynagh 
  * Everyone has perl, clean Prelude*.tex too

M ./report/Makefile -3 +1

View patch online:
http://darcs.haskell.org/haskell-prime-report/_darcs/patches/20090721103957-3fd76-ccdb28273cabb4495bdf0d4c65495cae6156b03b.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-report): Remove a command from "make clean" that breaks in a fresh repo

2009-07-24 Thread Ian Lynagh
Tue Jul 21 03:38:44 PDT 2009  Ian Lynagh 
  * Remove a command from "make clean" that breaks in a fresh repo

M ./report/Makefile -1

View patch online:
http://darcs.haskell.org/haskell-prime-report/_darcs/patches/20090721103844-3fd76-0511779ead8500ad74a68e4f83f196b0c664013b.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


patch applied (haskell-prime-report): Fix indentation in an example

2009-07-24 Thread Ian Lynagh
Mon Jul 20 17:31:43 PDT 2009  Ian Lynagh 
  * Fix indentation in an example
  Using tabs doesn't give the correct indentation in the HTML output

M ./report/modules.verb -2 +2

View patch online:
http://darcs.haskell.org/haskell-prime-report/_darcs/patches/20090721003143-3fd76-7bde64bacdb9c7a544e888c80f171313b0829658.gz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Haskell 2010: libraries

2009-07-19 Thread Ian Lynagh
On Tue, Jul 14, 2009 at 12:23:51PM +0100, Duncan Coutts wrote:
> On Tue, 2009-07-14 at 00:20 +0100, Ian Lynagh wrote:
> > On Mon, Jul 13, 2009 at 09:56:50PM +0100, Duncan Coutts wrote:
> > > 
> > > Specifically, I suggest:
> > > 
> > >  4. Ixkeep as Data.Ix
> > >  5. Array keep as Data.Array
> 
> Though also note that we have not changed any of the existing ones. Is
> there a problem with specifying in the libraries section of the report
> that the exports are a minimum and not a maximum?

Here's another example I've just been looking at:

Prelude> Array.listArray (1,4) [1..4] Array.! 5
*** Exception: Ix{Integer}.index: Index (5) out of range ((1,4))

Prelude> Array.listArray ((0,0), (3,3)) (repeat 0) Array.! (0,5)
*** Exception: Error in array index

Because the "Ix Integer" instance is for a type that we have a "Show"
instance for, it can give a nice out-of-bounds error message.

But the "Ix (a, b)" instance doesn't know if "(Show a, Show b)"
instances exist, so it has to fall back to an unhelpful error message.

So one could certainly argue that we should make Show a superclass of
Ix, leaving us with a class that is incompatible with the older class
definition.


Thanks
Ian

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


Re: Haskell 2010: libraries

2009-07-15 Thread Ian Lynagh
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.


Thanks
Ian

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


Re: Haskell 2010: libraries

2009-07-14 Thread Ian Lynagh
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.V.Prelude
where  is that latest the compiler supports, unless you say
e.g. -XHaskell2010.


Thanks
Ian

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


Re: Haskell 2010: libraries

2009-07-14 Thread Ian Lynagh
On Tue, Jul 14, 2009 at 11:57:11AM +0400, Bulat Ziganshin wrote:
> Tuesday, July 14, 2009, 3:20:42 AM, you wrote:
> 
> > We've been fortunate recently that, because the hierarchical modules
> > haven't been in the standard, we've been able to extend and improve them
> > without breaking compatibility with the language definition.
> 
> but breaking compatibility with existing programs. i hate situation
> when we need to reupload entire hackage every year

Standardising the number of modules we're talking about isn't going to
affect whether or not this happens.

Also, just because the libraries are standardised separately doesn't
mean that we /need/ to change them every year, it just makes it
/possible/ to change them.


Thanks
Ian

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


Re: Haskell 2010: libraries

2009-07-14 Thread Ian Lynagh
On Tue, Jul 14, 2009 at 12:23:51PM +0100, Duncan Coutts wrote:
> On Tue, 2009-07-14 at 00:20 +0100, Ian Lynagh wrote:
> > On Mon, Jul 13, 2009 at 09:56:50PM +0100, Duncan Coutts wrote:
> > > 
> > To take one example, since List was immortalised in the H98 report with
> > 104 exports, Data.List has gained an additional 7 exports:
> >
> > The last change (making the behaviour of the generic* functions
> > consistent with their non-generic counterparts) was less than a year
> > ago, and the last additions were less than 2.
> 
> Though also note that we have not changed any of the existing ones.

Yes we have, less than a year ago:

GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
Prelude> Data.List.genericTake (-1) "abc"
"*** Exception: List.genericTake: negative argument

GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Prelude> Data.List.genericTake (-1) "abc"
""

> Is there a problem with specifying in the libraries section of the report
> that the exports are a minimum and not a maximum?

We wouldn't be able to fix the generic* functions, or the way exceptions
work.

> > But to me, the most compelling argument for dropping them from the
> > report is that I can see no benefit to standardising them as part of the
> > language, rather than in a separate "base libraries" standard.
> 
> Some functions, especially the pure ones are really part of the
> character of the language

The Haskell language could be thought of as being composed of "Haskell
Language 2010 report" and "Haskell Libraries 1.0 report".

> (and some are specified as part of the
> syntax)

Yes, some types functions may need to be specified by the report as
being somewhere for desugaring etc. Although maybe we could even
eliminate most of these if rebindable syntax became part of the
language?


Thanks
Ian

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


Re: Haskell 2010: libraries

2009-07-13 Thread Ian Lynagh
On Mon, Jul 13, 2009 at 09:56:50PM +0100, Duncan Coutts wrote:
> 
> I'd advocate 4. That is, drop the ones that are obviously superseded.
> Keep the commonly used and uncontroversial (mostly pure) modules and
> rename them to use the new hierarchical module names.
> 
> Specifically, I suggest:
> 
>  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
> 11. Directory drop
> 12. Systemdrop (superseded by System.Process)
> 13. Time  drop
> 14. Localedrop
> 15. CPUTime   drop
> 16. Randomdrop

We've been fortunate recently that, because the hierarchical modules
haven't been in the standard, we've been able to extend and improve them
without breaking compatibility with the language definition. In some
cases, such as the changes to how exceptions work, we haven't had this
freedom as the relevant functions are exposed by the Prelude, and that
has been causing us grief for years.

To take one example, since List was immortalised in the H98 report with
104 exports, Data.List has gained an additional 7 exports:
foldl'
foldl1'
intercalate
isInfixOf
permutations
stripPrefix
subsequences
The last change (making the behaviour of the generic* functions
consistent with their non-generic counterparts) was less than a year
ago, and the last additions were less than 2.

It seems unlikely to me that all these libraries are finally perfect. If
we freeze them too solidly then I'm sure that we will regret it.

It is true that, with yearly language revisions, we have an annual
opportunity to fix any problems. However, we also want the
implementations to support several releases at once, and maintaining
those old base libraries would be a lot of work and confusion for the
minimal amount of benefit they would provide.

But to me, the most compelling argument for dropping them from the
report is that I can see no benefit to standardising them as part of the
language, rather than in a separate "base libraries" standard. We would
be able to act as if they were one standard if that were most
convenient, but we would have the flexibility to take advantage of them
being separate if necessary.


Thanks
Ian

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


Re: Haskell 2010: libraries

2009-07-11 Thread Ian Lynagh
On Fri, Jul 10, 2009 at 10:05:52AM +0100, Simon Marlow wrote:
> 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?

OK, will do.


Thanks
Ian

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


Re: Haskell 2010: libraries

2009-07-08 Thread Ian Lynagh
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


Thanks
Ian

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


Re: Mutually-recursive/cyclic module imports

2008-08-15 Thread Ian Lynagh
On Fri, Aug 15, 2008 at 09:27:16AM -0400, Isaac Dupree wrote:
> Haskell-98 specifies that module import cycles work 
> automatically with cross-module type inference.
> 
> It has some weird interactions with defaulting and the 
> monomorphism restriction.  In Haskell-prime we're planning 
> on removing artificial monomorphism, but defaulting will 
> still be necessary (and can still be set differently per 
> module).

I'm not sure if defaulting actually makes this worse, but regardless, I
think we should seriously consider removing defaulting anyway:

http://hackage.haskell.org/trac/haskell-prime/wiki/Defaulting#Proposal4-removedefaulting


Thanks
Ian

___
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-30 Thread Ian Lynagh
On Wed, Apr 30, 2008 at 12:18:47PM +0100, Ross Paterson wrote:
> On Wed, Apr 23, 2008 at 10:32:24AM -0700, Simon Marlow wrote:
> > The current proposal on the table for what to do about the monomorphism  
> > restriction (henceforth MR) is
> >
> >   * remove the MR entirely
> 
> Just to be clear, are we talking only about Rule 1 of the MR?
> 
> Rule 2 seems unavoidable, but it should probably say "entire group of
> mutually recursive modules" rather than "entire module".

Rule 2

Any monomorphic type variables that remain when type inference for
an entire module is complete, are considered ambiguous, and are
resolved to particular types using the defaulting rules.

Sounds right to me.

Although personally I think defaulting should be removed from the
language (but left in the interactive environments), but that's another
debate!


Thanks
Ian

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


Re: Composition again

2008-04-29 Thread Ian Lynagh
On Tue, Apr 29, 2008 at 02:05:58PM -0700, Simon Marlow wrote:
> 
> that with the qualified operator change, this becomes:
> 
> f.g f . g   (three tokens)
> F.g F.g (qualified `g')
> f.(.)   f . (.) (three tokens)  *
> F.(.)   F.(.)   (qualified `.')
> F.  F . (two tokens)

And [f..], [F..] etc will parse as we want them to too. Sounds OK to me.


Thanks
Ian

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


Re: Composition again

2008-04-28 Thread Ian Lynagh
On Mon, Apr 28, 2008 at 10:39:09AM -0700, Simon Marlow wrote:
> 
> Ok, I'm going to try to make some progress on this.  I think it's fair 
> to say that the only possible options are (0) do nothing, or (2) require 
> spaces around "." as an operator.

If we are considering requiring spaces around "." then I think it would
make sense to also consider requiring spaces around
* "-" (so we can make "-2" and "map (- 3) xs" both do what you expect)
* "!" (meaning that "f !x" isn't valid but differently parsed for
   patterns and expressions - assuming we plan to accept
   BangPatterns).

I don't think it makes sense to make a special case for requiring spaces
around "$", as TH won't be in H'.


Thanks
Ian

___
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-28 Thread Ian Lynagh
On Mon, Apr 28, 2008 at 09:42:10AM -0700, Simon Marlow wrote:
> 
> Ok.  So I counter-propose that we deal with pattern bindings like this:
> 
>   The static semantics of a pattern binding are given by the following
>   translation.  A binding 'p = e' has the same meaning as the set of
>   bindings
> 
> z = e
> x1 = case z of { p -> x1 }
> ...
> xn = case z of { p -> xn }
> 
>   where z is fresh, and x1..xn are the variables of the pattern p.

Just to check, this is saying "no change relative to Haskell 98"
(although perhaps specifying it less ambiguously), right?

> Oh, and I also propose to use the terminology "variable binding" instead 
> of "simple pattern binding",

Good idea.


Thanks
Ian

___
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 Ian Lynagh
On Thu, Apr 24, 2008 at 12:21:26AM +0200, Niklas Broberg wrote:
> > I'm very suspicious about the power/weight ratio of this change.
> >  Normally, for simple value-level stuff like this, provide both options:
> >
> > mapM / forM. =<< >>=
> >
> >  So how about, rather than break things, just provide an alternative to ($).
> 
> Alright, I'm not sure what the proper channel for doing this is,

Please see
http://www.haskell.org/haskellwiki/Library_submissions

> f $$ x = f x

Note that this clashes with Text.PrettyPrint (which doesn't necessarily
mean it shouldn't be used anyway).


Thanks
Ian

___
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 Ian Lynagh
On Wed, Apr 23, 2008 at 09:52:11AM -0700, Simon Marlow wrote:
> 
> 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

But it's not a prefix operator in the sense that we could define it (in
a hypothetical language that allowed us to define prefix operators),
it's actually syntax, which makes it much less appealing to me.


Thanks
Ian

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


Re: Standard libraries

2007-11-15 Thread Ian Lynagh
On Thu, Nov 15, 2007 at 10:54:28AM +0300, Bulat Ziganshin wrote:
> 
> second, every year Haskell committee should decide which libraries of
> currently Hackage-available are most widely used, portable and free,
> and call this set a "Haskell- standard libraries", together with
> versions inspected.

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

(We should also write down somewhere exactly which libraries must follow
http://www.haskell.org/haskellwiki/Library_submissions)

> H2008 libs: base 3.0, FPS 1.0, Binary 1.0
> H2009 libs: base 3.0, FPS 2.0, SuperBinary 0.1
> 
> With above-mentioned versioning policy, this means that any
> "FPS 1.0.*" will comply to the H08 standard and this means that this
> line of version may continue to fix bugs, improve performance, add
> support for new systems, while keeping its interface

Note that according to the versioning policy FPS 1.0.1 can, for example,
export functions that 1.0.0 doesn't export.

> One important drawback that i see here is that "full" compiler
> downloads should be shipped with older library versions too - i.e.
> providing newest FPS library will be not enough, you need to ship
> older HSL libraries too

Personally I think it is best to avoid having more than one version of a
library installed. That way you don't have problems when you try to use
2 libraries, and one thinks that ByteString is
fps-1.0:Data.ByteString.ByteString and another that it is
fps-2.0:Data.ByteString.ByteString, resulting in type mismatch errors.


Thanks
Ian

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


Re: Newbie proposal: operator backquoting

2007-06-25 Thread Ian Lynagh
On Thu, Jun 21, 2007 at 09:14:55AM +0400, Dusty wrote:
>
> foo '-'1  has two arguments, (-) and 1,while  foo -1  has one 
> argument, -1

You mean
foo '-'1
is parsed as
(-) foo 1
and
foo -1
is parsed as
foo (-1)
right?

What would
foo - 1
mean? If it means
(-) foo 1
then putting the extra space in looks a lot nicer to me than using
backquotes. If it means
foo (-1)
then I think this will break a lot of code, and is also very
unintuitive.


Thanks
Ian, a member of the "Out with DMR, defaulting, unary negation and n+k
patterns" club

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


Re: strict bits of datatypes

2007-03-20 Thread Ian Lynagh
On Tue, Mar 20, 2007 at 01:53:47PM +, Malcolm Wallace wrote:
> 
> Now, in the definition
> x = x `seq` foo
> one can also make the argument that, if the value of x (on the lhs of
> the defn) is demanded, then of course the x on the rhs of the defn is
> also demanded.  There is no need for the `seq` here either.
> Semantically, the definition is equivalent to
> x = foo
> I am arguing that, as a general rule, eliding the `seq` in such a case
> is an entirely valid and correct transformation.

So does nhc98 print "Foo" for this program?

main = putStrLn $ let x = x `seq` "Foo" in x

(yhc tells me my program has deadlocked, but my recent attempt to
compile nhc98 failed so I can't check it).

I don't fully understand what your interpretation is; is it also true
that
y = x
x = y `seq` foo
is equivalent to
y = x
x = foo
?

And is it true that
y = if True then x else undefined
x = y `seq` foo
is equivalent to
y = x
x = foo
?

> The objection to this point of view is that if you have a definition
> x = x `seq` foo
> then, operationally, you have a loop, because to evaluate x, one must
> first evaluate x before evaluating foo.  But as I said at the beginning,
> `seq` does _not_ imply order of evaluation, so the objection is not
> well-founded.

I'm having trouble finding a non-operational description of the
behaviour I think seq should have. (Nor, for that matter, can I think of
a description that makes it clear that it has the semantics that you
think it should have). Anyone?

I think you could make a similar argument that
let x = x in x :: ()
is () rather than _|_, and similarly
let x = x in x :: Int
is 3, or is there some key difference I'm missing?


Thanks
Ian

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


type aliases and Id

2007-03-19 Thread Ian Lynagh

Hi all,

Suppose I have a datatype:

data Foo a = Foo {
 int :: a Int,
 char :: a Char
 }

where I start off with (Foo Nothing Nothing) :: Foo Maybe, gradually
accumulate values until I have (Foo (Just 5) (Just 'c')), and then I
want to remove the Maybe type so I can lose all the now-redundant Just
constructors.

Well, suppose in actual fact I prefer the name "CanBe" to Maybe.

Then for the first part I want

type CanBe a = Maybe a

foo :: Foo CanBe
foo = ...

but of course this fails because CanBe is a non-fully-applied type
synonym in "foo :: Foo CanBe", and I can fix this by eta-reducing thus:

type CanBe = Maybe

foo :: Foo CanBe
foo = ...

Now for the second part I want

type Id a = a

foo' :: Foo Id
foo' = ...

but again Id is not fully applied. However, this time I cannot
eta-reduce it! "type Id =" is a parse error, as is "type Id".

I'd really like to be able to define an eta-reduced Id; I see two
possibilities:

* Allow "type Id =" (I prefer this to "type Id" as I think we are more
  likely to want to use the latter syntax for something else later on).

* Implementations should eta-reduce all type synonyms as much as
  possible, e.g.
  type T a b c d = X a b Int c d
  is equivalent to
  type T a b = X a b Int
  and
  type Id a = a
  is equivalent to a type that cannot be expressed directly.


Any opinions?


Thanks
Ian

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


strict bits of datatypes

2007-03-16 Thread Ian Lynagh

Hi all,

A while ago there was a discussion on haskell-cafe about the semantics
of strict bits in datatypes that never reached a conclusion; I've
checked with Malcolm and there is still disagreement about the right
answer. The original thread is around here:
http://www.haskell.org/pipermail/haskell-cafe/2006-October/018804.html
but I will try to give all the relevant information in this message.

The question is, given:

data Fin a = FinCons a !(Fin a) | FinNil

w = let q = FinCons 3 q
in case q of
   FinCons i _ -> i

is w 3 or _|_?

-- The _|_ argument --

(Supporters include me, ghc and hugs)

q = FinCons 3 q
=== (by Haskell 98 report 4.2.1/Strictness Flags/Translation
q = (FinCons $ 3) $! q
=== (by definition of $, $!)
q = q `seq` FinCons 3 q
=== (solution is least fixed point of the equation)
q = _|_

Thus

w = case _|_ of
FinCons i _ -> i

so w = _|_.


-- The 3 argument --

(Supporters include Malcolm Wallace, nhc98 and yhc)

Here I will just quote what Malcolm said in his original message:

The definition of seq is
seq _|_ b = _|_
seq  a  b = b, if a/= _|_

In the circular expression
let q = FinCons 3 q in q
it is clear that the second component of the FinCons constructor is not
_|_ (it has at least a FinCons constructor), and therefore it does not
matter what its full unfolding is.

and in his recent e-mail to me:

Yes, I still think this is a reasonable interpretation of the Report.  I
would phrase it as "After evaluating the constructor expression to WHNF,
any strict fields contained in it are also be guaranteed to be in WHNF."

This also makes q a fixpoint of q = q `seq` FinCons 3 q, but not the
least fixed point.

--

So I think it would be good if we can all agree on what the meaning
should be, and then to clarify the wording in the report so that future
readers understand it correctly too.


Thanks
Ian

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


Re: [GHC] #1215: GHC fails to respect the maximal munch rule while lexing "qualified reservedids"

2007-03-13 Thread Ian Lynagh

Context if you haven't been following:
http://hackage.haskell.org/trac/ghc/ticket/1215

On Tue, Mar 13, 2007 at 03:12:33PM -, GHC wrote:
> 
>  Interesting.  It turns out I misinterpreted the Haskell lexical syntax:
>  GHC lexes `M.default` as `M` `.` `default`, because `M.default` is not a
>  valid qvarid but I neglected to take into account the maximal munch rule.
> 
>  We have an open ticket for Haskell' about this:
>  
> http://hackage.haskell.org/cgi-bin/haskell-prime/trac.cgi/wiki/QualifiedIdentifiers
>  which was until just now
>  inaccurate (I've now fixed it).  I propose to fix GHC in 6.8 to match the
>  Haskell' proposal.

If I understand correctly then the proposal would make e.g.

foo = Bar.where

a syntactically valid program, but one which would be guaranteed to fail
to compile with a not-in-scope error?

Wouldn't it be cleaner for it to be a lexical error? Unfortunately I'm
not sure how to say this in the grammar; the best I can come up with is:

program  ->  {lexeme | whitespace | error }
error->  [ modid . ] reservedid


Thanks
Ian

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


Re: New Layout Rule

2006-12-08 Thread Ian Lynagh
On Fri, Dec 08, 2006 at 02:33:47AM -0800, John Meacham wrote:
> Motivated by some recent discussion, I thought I would explore the
> possibilty of formalizing the haskell layout rule without the dreaded
> parse-error clause, as in, one that can be completly handled by the
> lexer.

There was some discussion about that a while ago on this list, e.g.
http://www.haskell.org/pipermail/haskell-prime/2006-March/000915.html
and other subthreads in that thread.

I'd still love to see a replacement which can be a separate phase
between lexing and parsing, even if it means we need to lay some things
out differently or tweak other bits of the syntax.


Thanks
Ian

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


Re: defaults

2006-11-27 Thread Ian Lynagh
On Mon, Nov 20, 2006 at 12:05:46PM +, Malcolm Wallace wrote:
> Prompted by recent discussion on the Hat mailing list about the problems
> of type-defaulting, I have added two new proposals for this issue to the
> Haskell-prime wiki at:
> 
> http://hackage.haskell.org/trac/haskell-prime/wiki/Defaulting

I don't see a proposal to remove defaulting defaulting altogether on
that page - has that been discussed already?

Am I the only one who puts an explicit type signature in whenever my
compiler warns me that it is having to do some defaulting? And probably
99% of those would be unnecessary if (^)'s second argument was an Int,
with a genericPower (or whatever) function providing the current type
signature (analogous to, for example, (!!) and genericIndex).

Defaulting is one wart I would be glad to be rid of.


Thanks
Ian

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


Re: Standard (core) libraries initiative: rationale

2006-11-27 Thread Ian Lynagh
On Mon, Nov 27, 2006 at 02:55:03PM -0800, David Roundy wrote:
> On Mon, Nov 27, 2006 at 10:28:09PM +0300, Bulat Ziganshin wrote:
> > [...]
> > and this leads us to other question - whether this set and API of each
> > library should be fixed in language standard or it can evolve during
> > the time?...
> 
> To me, this is the deciding issue.  The Haskell 98 libraries have some
> severe issues which are unfixable because they're defined as part of the
> standard.

Right, the problem is that there is a tension here between having the
ability to fix and evolve the libraries, and people wanting to write
books on how to use Haskell' (without having to define (+) and map etc
themselves).

We've been lucky thus far that having the hierarchial libraries
completely disjoint with the report has meant that we have been able add
to and alter things even in the base package without breaking anything
assuming Haskell98. We haven't had to worry about clashing with a user's
Data.Function module, or if adding an "on" function will cause
ambiguous-import errors in someone's program.

We still get the occasional person in #haskell asking why they can't
find the fromInt their book talks about, and I think that was probably
published in the 90s?

I've been pondering this all day, and I think my conclusion is that
books should be about "Haskell', base 3.0.* and mtl 2.1.*", and Haskell'
should say pretty much nothing about libraries (we'll probably want to
use things like head in examples, and talk about things like seq; hmm,
perhaps a very few functions like seq do belong in a package of their
own that Haskell' knows about, probably reexported elsewhere by the base
package).

This would be more reason for GHC to factor out the magic from base, as
it'll be possibly more important to be able to install base 3.0 and 4.1
simultaneously.


Thanks
Ian

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


Re: Pattern matching order for records

2006-10-13 Thread Ian Lynagh
On Fri, Oct 13, 2006 at 05:19:09PM +0100, Malcolm Wallace wrote:
> Ian Lynagh <[EMAIL PROTECTED]> wrote:
> 
> > Has clarifying the pattern matching order for records as described in
> > http://hackage.haskell.org/trac/ghc/ticket/246 been discussed for
> > haskell'? I couldn't see it on the proposals list.
> 
> Perhaps because this has already been fixed in the errata to the
> Haskell'98 Report?

Ooops, missed that. Sorry for the noise!


Ian

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


Pattern matching order for records

2006-10-13 Thread Ian Lynagh

Hi all,

Has clarifying the pattern matching order for records as described in
http://hackage.haskell.org/trac/ghc/ticket/246 been discussed for
haskell'? I couldn't see it on the proposals list.

Personally I actually think hugs is doing the right thing according to
the report and that there is no real ambiguity in the report's language,
just a bit of unclarity.

Furthermore, I think hugs' interpretation means that it is easier for
the programmer to understand how his program will behave if he only has
to look at the pattern to be matched, and not refer back to the
definition of the record, even if this does make for slightly more
desugaring work for the implementor.

Thus I would propose just clarifying the language for Haskell'.


Thanks
Ian

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


Re: New syntax

2006-03-31 Thread Ian Lynagh
On Fri, Mar 31, 2006 at 01:26:52PM +0100, Simon Peyton-Jones wrote:
> | > Template Haskell breaks expressions with $,
> | 
> | It's very bad that with TH enabled you cannot write sections of the
> form ($ x)
> | anymore which are sometimes very handy.
> 
> I'd prefer it if TH only sprang into action when you wrote
>   $x
> or
>   $(f x)
> 
> That is, no space after the $.  If you put spaces, you should get the
> H98 $.  

Isn't that the current behaviour?


Thanks
Ian

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


Re: the dreaded offside rule

2006-03-09 Thread Ian Lynagh
On Thu, Mar 09, 2006 at 04:53:52PM -, Simon Marlow wrote:
> On 09 March 2006 14:40, Simon Marlow wrote:
> 
> > But ISTR I later discovered a reason that counting brackets wouldn't
> > work so well, but for now it escapes me.  I'll try to dig it up.
> 
> I remember now: the problem is that 'let' does not always have a
> matching 'in', e.g. when it is used in 'do', pattern guards or list
> comprehensions.  So you can't consistently treat let/in as brackets.  I
> don't know a way around this.

Right, I mentioned that in my earlier mail. However, I think this can be
handled by rules like

 L (:ts) ((Let:bs,m):bsms)   =   L ts ((bs,m):bsms)  if m = n

but like I said, I haven't had time (nor do I expect to have time for
H') to work it all out and see if it can actually be made to work.


Incidentally, in my head the "," in "(case x of p -> e, 42)" acts as a
right and left bracketing lexeme, so this expression would still be
accepted. At the cost of rejecting more H98 programs you wouldn't have
to allow it, of course, although from the user's point of view I'd
prefer if it was allowed.


(By the way, have the mailing lists started being clever and not sending
you messages that look like they are also being sent directly to you?)


Thanks
Ian

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


Re: the dreaded offside rule

2006-03-09 Thread Ian Lynagh
On Wed, Mar 08, 2006 at 10:27:48PM +0100, Doaitse Swierstra wrote:
> It is with some hesitation that I want to bring up another point, in  
> which Haskell' could be an improvement above Haskell: the offside rule.

This is something I would have brought up too, except I don't think I'll
have time to look into it properly in the advertised timescale.

I conjecture that with a suitable set of bracketing keywords and symbols
(if/then, let/in, [/], ...) the "parse error => close implicit block"
rule could be dropped without significantly altering the set of
acceptable programs (just rejecting programs that people really oughtn't
be writing anyway (IMNSHO), like Lennart's examples).

Things are slightly complicated by things like [ ... | ... ] and "let"
not always being closed by "in" (so you just have to have it implicitly
closed when you want to insert a ; in a "do" block), but I haven't
thought of anything that'll actually break it. Then again, I haven't
thought too hard about it or tried it out yet.

I'm not sure how much easier this will make it to explain the rule to
people - if you just explain the gist using the simple examples of
bracketing, like if/then, then I think it would be significantly
simpler, but if you'd want to explain all the niggly details then it
might end up also being too complex.

The main advantage is it would make layout a separate pass between
lexical analysis and parsing.


Thanks
Ian

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


Re: Export lists in modules

2006-02-24 Thread Ian Lynagh

[sorry, I've lost the original post]

On Thu, Feb 23, 2006 at 04:47:37PM -0800, John Meacham wrote:
> On Thu, Feb 23, 2006 at 11:36:34AM +0100, Wolfgang Jeltsch wrote:
> > The remaining problem is that using "type" for every type is misleading, 
> > since 
> > "type" is otherwise used only for aliases.  Maybe it would be better to use 
> > something like "typealias" for type aliases, since using "type" for 
> > declaring 
> > type aliases is misleading anyway.

I'd be in favour of H' supporting "typealias" as well as "type". This
would lead the way, via compilers giving warning for uses of "type", to
dropping support for "type" more painlessly in a future standard. Too
much code has variables called "typ"...

I think the same with "data" and "datatype" would be nice too. I also
have a number of variables called "dat" dotted around.

We could still use "type" in export lists, if desired, in the same way
we use can still use things like "export" in FFI exports (i.e. you might
have to export "variable type" rather than an unqualified "type").


Thanks
Ian

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


  1   2   >