Re: Proposals and owners

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

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

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

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

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

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

Cheers,

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


ExplicitForall

2009-07-27 Thread Niklas Broberg
Hi all,

Per request I've made a ticket and proposal page for adding
ExplicitForall to Haskell'2010:
  http://hackage.haskell.org/trac/haskell-prime/ticket/133
  http://hackage.haskell.org/trac/haskell-prime/wiki/ExplicitForall

Cheers,

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


Re: Proposal: Deprecate ExistentialQuantification

2009-07-23 Thread Niklas Broberg
 Discussion period: 2 weeks

Returning to this discussion, I'm surprised that so few people have
actually commented yea or nay. Seems to me though that...
* Some people are clearly in favor of a move in this direction, as
seen both by their replies here and discussion over other channels.
* Others are wary of deprecating anything of this magnitude for
practical reasons.
* No one has commented in true support of the classic existential
syntax, only wanting to keep it for legacy reasons.

I'm in no particular hurry to see this deprecation implemented, and I
certainly understand the practical concerns, but I would still very
much like us to make a statement that this is the direction we intend
to go in the longer run. I'm not sure what the best procedure for
doing so would be, but some sort of soft deprecation seems reasonable
to me.

Further thoughts?

Cheers,

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


Re: Proposal: ExplicitForall

2009-07-23 Thread Niklas Broberg
 Alright, let's set an actual discussion period of 2 weeks for
 ExplicitForall. If there is no opposition by then, we can add
 ExplicitForall to the registered extensions in cabal as a first step.

Slightly more than two weeks later, there has been no voices against
and at least a few in favor.

The attached patch for Cabal adds ExplicitForall to the Extension
datatype, with documentation, and adds it to knownExtensions.

Cheers,

/Niklas


ExplicitForall.dpatch
Description: Binary data
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Proposal: Deprecate ExistentialQuantification

2009-06-28 Thread Niklas Broberg
 In other words, in your 2x3 grid of syntactic x expressiveness, I want
 the two points corresponding to classic syntax x {existential
 quantification, GADTs} to be removed from the language. My second
 semi-proposal also makes each of the three points corresponding to the
 new cool syntax a separate extension.

 I see, but why are you opposed to have the classic syntax still support
 existentials (though foralls) and GADTs (through equality constraints). I
 would make sense to me to keep this support around.

I am opposed since
a) it requires the addition of extra syntax to the language, and
b) we have another, better, way to do it.

Somewhat pointed, I don't think the C++ way of putting all imaginable
ways to do the same thing into the language is a sound design
principle. If we have two ways to do the same thing, and one of them
is considered prefered, then I see no reason at all to keep the other
around. What I'm arguing here is that the GADT style syntax is truly
preferable, and thus the other should be removed.

Cheers,

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


Re: Proposal: ExplicitForall

2009-06-24 Thread Niklas Broberg
 What you suggest would be fine with me. Presumably ExplicitForall would be 
 implied by RankNTypes and the other extensions?

Yes, that's the idea. Rank2Types, RankNTypes, PolymorphicComponents,
ScopedTypeVariables and LiberalTypeSynonyms would all imply
ExplicitForall.

 There is a danger of having too *many* choices. 
 (http://www.joelonsoftware.com/items/2006/11/21.html)  In particular, you 
 might consider making ScopedTypeVariables synonymous with ExplicitForAll.  
 Once you have given up the keyword, it seems a shame not to allow lexically 
 scoped type variables!

While I agree with you (and Joel) in principle, I think this is the
wrong level to hold that discussion. I think the long-term solution
should be to keep the registered extensions cleanly separated, and
instead supply extension *groups* as a way to limit choice.
-fglasgow-exts has fit that niche admirably for a long time, I think a
lot of people just use that without thinking twice about what
particular extensions they actually use, and nothing wrong with that.
I think the move towards LANGUAGE pragmas instead of compiler options
is a good one from a standardisation and implementation point of view,
but to avoid tedium and unnecessary choice for the programmer I
strongly feel that extension groups need to be introduced at this
level too. But as I said, that's for a different discussion...

 On ExistentialQuantification, I personally think we should deprecate the 
 entire construct, suggesting GADT-style syntax instead.

+1, though I was afraid to suggest something that radical. I might
write a separate proposal for that then, to keep the discussion here
focused on ExplicitForall.

 If you can form a consensus, go for it.

Alright, let's set an actual discussion period of 2 weeks for
ExplicitForall. If there is no opposition by then, we can add
ExplicitForall to the registered extensions in cabal as a first step.

Cheers,

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


Proposal: ExplicitForall

2009-06-23 Thread Niklas Broberg
Hi all,

(I'm writing this to several lists since it involves GHC
(implementation of extensions), cabal (registration of extensions) and
some future Haskell standard (formalisation of extensions).)

In my quest to implement all known syntactic extensions to Haskell in
my haskell-src-exts package, I've become painfully aware of the
sometimes ad-hoc nature that these extensions have been added to GHC.
This should not be taken as criticism per se, GHC is awesome and I'm
sure a lot of thought and research has gone into all of these
extensions. I think the problem (from my point of view) is rather that
most of the extensions are only really interesting on a type system
level, whereas the syntactic level is rather trivial, and thus the
latter has (rightly) gotten far less formal attention. I hope my
putting the light on these issues will be a help and a kickoff towards
improving the state of formalisation of the known and registered (with
Cabal) extensions.

One of the most blatant and (to me) problematic such issues is the
matter of using 'forall'. GHC has a number of extensions relating to
the use of forall-quantified types in various interesting ways. With
none of these extensions on, forall is not considered a keyword, so
the syntax with explicit forall quantification cannot be used at all
('forall' is considered a varid). However, with *any* extension on
that relates to forall-quantified types, forall is a keyword, and can
syntactically be used in types *anywhere*. This doesn't mean all such
types will pass the type checker, most of them won't in fact, but
syntactically there is really no (or at least very little) difference.

Conceptually, all of these extensions (specifically
PolymorphicComponents, Rank2Types, RankNTypes, LiberalTypeSynonyms and
ScopedTypeVariables (and strangely also ExistentialQuantification))
thus have one thing in common. They all enable syntactically
forall-quantified types. They allow different uses of these types as
far as the type system is concerned, but syntactically there is no
difference between type and type (in fact there cannot be, as I
discussed in a recent blog post [1]).

Funnily enough there are also some uses of forall-quantified types
that are common to all of these extensions - using a forall just to
make polymorphism explicit in a type doesn't change anything as far as
the type system is concerned, so e.g. the types '(Eq a) = a - Bool'
and 'forall a . (Eq a) = a - Bool' are equivalent. The latter type
can be given to a function when any of the listed six extensions are
given, even if most of them have nothing to do with this at all!

So, what I'm getting at is an idea that Isaac Dupree gave as a comment
to my blog post. He said:

   I wish there was a plain old ExplicitForall extension that enabled
the keyword in types (without extending the type checker -- only like
(id :: forall a. a - a) would be allowed).

I think this is a really great idea. I find it conceptually appealing,
since I think it covers exactly that blind spot that is the seemingly
unintended intersection between all these extensions. And it also
makes the separation of concern between the syntactic level and the
type system more clear. Any formalisation of any of the type system
extensions would not need to bother with syntactic details, but can
simply be said to imply ExplicitForall.

I would thus like to propose the following formalisation of the
ExplicitForall extension:

=
ExplicitForall enables the use of the keyword 'forall' to make a type
explicitly polymorphic. Syntactically, it would mean the following
change to Haskell 98:

* 'forall' becomes a reserved word.
* '.' (dot) becomes a special (not reserved) operator.
* The following syntactic rule changes:

type  - 'forall' tyvars '.' type
   | context '=' type
   | ftype

ftype - btype '-' type
   | btype

gendecl   - vars '::' type

It does not allow the use of explicitly polymorphic types in any way
not already allowed by Haskell 98 for implicitly polymorphic types.
=

One thing to note is that I haven't touched the matter of
ExistentialQuantification in the above. Syntactically this is a
different beast entirely, and could well be handled separately, though
it's really an artifact of the way we (by default) write our data type
declarations. Using GADT-style declarations, existential
quantification goes nicely along with the others by following the same
syntactic rules for types, even though from a type system it is of
course still quite different from the rest. But with the ordinary
Haskell 98 declaration style, we could define the syntactic part of
the ExistentialQuantification extension as the following:

=
ExistentialQuantification allows data constructors to take
existentially quantified arguments. Syntactically, it means the
following changes to Haskell98:

* 'forall' becomes a 

Re: Composition again

2008-04-28 Thread Niklas Broberg
  I don't think it makes sense to make a special case for requiring spaces
  around $, as TH won't be in H'.

I agree, there's absolutely no need to treat $ differently in H'. The
situation will already be better than it is now, since by the special
treatment of . (and - and !, which I also agree with), there will be a
precedent to follow (assuming it gets accepted of course). That alone
makes it much easier to define the meaning of extensions like $ in TH.

Cheers,

/Niklas
___
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 Niklas Broberg
When I first saw this thread, my gut response was Aw gawds no, don't
touch my $ !! I love $, I use it all the time, it really helps making
code more readable and more nicely structured. I would really hate for
someone to take that away from me.

So when I came across this:

   This wouldn't work, you'd have to rewrite it as:

   withSomeResource foo .
 withSomeOtherThing bar .
   yetAnotherBlockStructured thing $ ...


 it is very inconvenient - we should use either . or $ depending on
  that it's last block or not. imagine all the changes when editing the
  code

... my initial response to it was yeah, Bulat is right, that's rather
inconsistent, and it would mean a lot of changes when editing (and
it's ugly too!).

But then I started questioning my own motives. What changes would that
be? Changing a . to a $ if I decided to remove the previous last piece
of the pipeline? Doesn't seem too hairy, and I have to do far worse
than that already when refactoring. Inconsistent? Doesn't it actually
make perfect sense that the actual application of the pipeline of
functions to some value is handled differently? Like Cale said,
wouldn't it actually be a Good Thing that we treated these things as
composition chains instead of application chains? And I could no
longer defend my own position, and so I started thinking for real.

Refactoring doesn't become harder with this suggestion - it becomes
easier in general, just as Dan points out in #1. And I know I've been
bitten by his #2 a bunch of times, even if I haven't realized the
source of the problem until I read this thread. It's messy having to
use a lot of parenthesis just because some argument to a function
isn't the last one, and I've found myself wishing for a way to get rid
of them. I know I have at times refactored my function definitions,
switching their arguments around just to get the one that would need
the parenthesis to be the last one.

So I dug through some of my code, picking large modules at random. As
I said I use $ *a lot*, anywhere that I can get away with it. In the
first 10 modules I looked at, I found one (1) place where I would need
to change a $ to a . to make it work. So I went to look at a bigger
module, and in what is possibly my largest self-contained module (1800
loc including comments) I had 211 uses of $, and I would have had to
change 23 of them into . instead to make it work with a
left-associative version. All the ones where the left operand is just
a function (like return) will still work. All the ones that are
followed by a '\x - ...' will still work. All the ones followed by a
'do ...' will still work. On the other hand, I found 10 places where I
could immediately have gotten rid of some extra parentheses, and that
just by searching for uses of fmap in the code!

It should be said though that changing the associativity of $ doesn't
make all code nice and clean. Consider for instance

f (g (h x)) (k y)

We could change that into one of

f $ g (h x) $ k y
f (g $ h x) $ k y

but not get rid of the parenthesis altogether, i.e. uses of $ for
different applications won't mix. But with right-associative $, the
second one would be our only option, so at least we're no worse off
than before, and perhaps it could be argued we are better off (in this
kind of situation).


I think it is reasonable to look closely at the motivations for
wanting to retain the $ as is. Looking through this thread, I can find
only a single complaint raised (albeit an important one), namely
backwards compatibility. Yes, such a change would likely break quite a
few my modules. But like Cale, I would never have expected H' to be
fully backwards compatible with H98, and thus there would have to be
some way to migrate anyway. This one seems pretty simple, just let the
old Prelude be Haskell98.Prelude and import that in old code. Of
course changes that break backwards compatibility should not be made
frivolously, but I find it hard to buy having only that as an argument
for a change that otherwise seems highly reasonable.

We live in a beautiful statically typed world. If the proposed change
was such that existing code would still compile, but with a different
behavior, it would be really dangerous. That's clearly not the case
here, there's no way that code that uses $-chaining would still
compile if the associativity was changed, and any other use of $ would
still compile and work as before. The type checker is there to help
us, and it's literally a moment's work to clean up existing code to
meet these standards. (And it's even faster to import
Haskell98.Prelude if you're lazy).

So come on, give me an argument for why $ should be right-associative
instead of complaining about broken code (that I argue won't break
even half as bad as some of you would have it). Is there really no
reason at all why right-associative is to be preferred over
left-associative? And if there is, why don't we hear it? Are you truly
arguing this because you think there's 

Re: Meta-point: backward compatibility

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

I would hope it is both. Some changes simply cannot become current
practice since they would not be compatible with existing code, and
the only place that such changes *could* be made is in a new language
version. Like you say, fail in the Monad class is one such issue that
would not be backwards compatible, and couldn't become a current
practice without some help. Chicken or egg first?

Cheers,

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


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

2008-04-23 Thread Niklas Broberg
 it's not refactoring! it's just adding more features - exception
  handler, progress indicator, memory pool and so on. actually, code
  blocks used as a sort of RAII for Haskell. are you wanna change all
  those ';' when you add new variable to your C++ code?

   bracketCtrlBreak (archiveReadFooter command arcname) (archiveClose.fst) $ 
 \(archive,footer) - do
 bad_crcs - withList $ \bad_crcs - do
   doChunks arcsize sector_size $ \bytes - do
 uiWithProgressIndicator command arcsize $ do
  or
 handleCtrlBreak  (ignoreErrors$ fileRemove arcname_fixed) $ do
 bracketCtrlBreak (archiveCreateRW arcname_fixed) (archiveClose) $ 
 \new_archive - do
 withJIT (fileOpen = originalURL originalName arcname) fileClose $ 
 \original' - do

  is just two examples from my code

... and neither of those examples would be broken by changing the
associativity of $. If that kind of code had been broken, I would have
complained too. So what was your point again? ;-)

Cheers,

/Niklas
___
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 Niklas Broberg
 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, but I
reckon here is as good as anywhere. I would like to propose that the
Haskell' Prelude includes the function

f $$ x = f x

with the same fixity level as $ (presumably 0) but being left
associative instead. And that $ is left as is.

Cheers,

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


Re: overlapping instances and constraints

2006-02-28 Thread Niklas Broberg
On 2/28/06, Ben Rudiak-Gould [EMAIL PROTECTED] wrote:
 Simon Peyton-Jones wrote:
  - A program that type checks can have its meaning changed by adding an
  instance declaration
 
  - Similarly adding import M() can change the meaning of a program (by
  changing which instances are visible
 
  - Haskell would need to be a lot more specific about exactly where
  context reduction takes place.

 I think all of these problems would go away if overlap was permitted within
 a module but forbidden across modules. Are there uses of overlapping
 instances for which this isn't flexible enough?

Certainly! In HSP [1] there is a class (simplified here)

class IsXML xml where
  toXML :: xml - XML

data XML = Element  | CDATA String

that deals with how things should be represented as XML. There are a
number of basic instances for this, such as

instance IsXML String where
 toXML = CDATA

instance (Show a) = IsXML a where
 toXML = toXML . show

The intention of the latter is to be a default instance unless another
instance is specified. These instances can be found in the base HSP
module, but the idea is that HSP users should be able to work with
their own datatypes and only need to define the translation into XML
via instanciating IsXML. This would have to be done in the user
modules, so overlap across module boundaries are essential for this to
work. :-)

/Niklas

[1] http://www.cs.chalmers.se/~d00nibro/hsp/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: overlapping instances and constraints

2006-02-28 Thread Niklas Broberg
Claus Reinke wrote:
 most of us would be happy if instance contexts
 would be required to uniquely determine the instance to be
 chosen, a rather conservative extension of current practice.

I'm not so sure about the most of us, as you note yourself the
defaulting pattern is quite popular (and useful). I certainly couldn't
live without it. And even that aside, I'd much rather have the type
system infer a most particular instance than to have to specify that
myself.

Also IMHO, adding a new construct (type (in)equality) to the language
is a lot more obtrusive than to do something meaningful of the
constructs that the language already provides. So I'd have issues with
conservative as well...

Of course, this is all from the perspective of a user, not a type
inference engine implementor... ;-)

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