
.ehs stands for extended haskell and encapsulates the 90% case of people just wanting -fglasgow-exts with a minimum of fuss. Having a filetype seesm better than the alternatives of either adding boilerplate language/options pragmas to the top of your source files or putting them in a cabal file. -Alex-

Hi Alex,
.ehs stands for extended haskell and encapsulates the 90% case of people just wanting -fglasgow-exts with a minimum of fuss.
That goes against the general GHC direction of trying to wean people off -fglasgow-exts and on to more specific language pragmas. Thanks Neil

If you take away -fglasgow-exts, then you force me to have to look up the exact name of each language extension I use every time I want to use it. Since that is annoying and breaks flow, the simpler answer is just to put a big honking language pragma at the top of all my source files with every extension I commonly use. e.g. {-# LANGUAGE TemplateHaskell, FlexibleInstances, OverlappingInstances, UndecidableInstances, CPP, ScopedTypeVariables, PatternSignatures, GADTs, PolymorphicComponents, FlexibleContexts, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} FYI, I grabbed the above from a source file that had been upgraded to 6.8 in which I kept adding pragmas until it compiled. Forcing the user to do this sort of thing manually every time they write code is ridiculous. Taken to its logical conclusion, why don't we also add "RecordSyntax" and "DoSyntax" etc. The compiler obviously knows which extensions are actually being used when the user uses them. If you want to warn the user that they are using non-standard options that is totally ok, but forcing the user to type them in is just really unfriendly. -Alex- Neil Mitchell wrote:
Hi Alex,
.ehs stands for extended haskell and encapsulates the 90% case of people just wanting -fglasgow-exts with a minimum of fuss.
That goes against the general GHC direction of trying to wean people off -fglasgow-exts and on to more specific language pragmas.
Thanks
Neil

Am Dienstag, 20. November 2007 22:35 schrieb Alex Jacobson:
[…]
{-# LANGUAGE TemplateHaskell, FlexibleInstances, OverlappingInstances, UndecidableInstances, CPP, ScopedTypeVariables, PatternSignatures, GADTs, PolymorphicComponents, FlexibleContexts, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-}
FYI, I grabbed the above from a source file that had been upgraded to 6.8 in which I kept adding pragmas until it compiled. Forcing the user to do this sort of thing manually every time they write code is ridiculous.
It made me discover that I use more language extensions than I thought I was using. I think, it’s a good thing if you have to be clear about what extensions you use and what you don’t use. What if someone wants to compile your code with a different compiler which doesn’t support all of GHC’s extensions?
Taken to its logical conclusion, why don't we also add "RecordSyntax" and "DoSyntax" etc.
Because they are part of the standard. If Haskell' will be released at some point in the future, we won’t have to include MultiParamTypeClasses, Concurrency, etc. into our LANGUAGE pragmas.
The compiler obviously knows which extensions are actually being used when the user uses them.
I don’t think so. For example, if you don’t use rank-2 polymorphism and similar things, forall is a perfect name for a type variable.
[…]
-Alex-
Best wishes, Wolfgang

Wolfgang Jeltsch wrote:
It made me discover that I use more language extensions than I thought I was using.
yes, it is likely that many of those extensions are in so many people's codes that they are de-facto standards whether they have been written into a specification document or not.
I think, it’s a good thing if you have to be clear about what extensions you use and what you don’t use. What if someone wants to compile your code with a different compiler which doesn’t support all of GHC’s extensions?
That compiler also won't recognize the pragmas and the code won't compiler either way. Only now you have code that has lots of pragmas in it.
The compiler obviously knows which extensions are actually being used when the user uses them.
I don’t think so. For example, if you don’t use rank-2 polymorphism and similar things, forall is a perfect name for a type variable.
Actually it probably isn't a great name given the risk that forall may appear in a standard some time soon. But either way, if you are not using forall in the context of forall syntax, then the compiler knows that and can handle it appropriately. Proof that the compiler knows which extensions are being used: it can compile the program sucessfully when the extension is turned on and not otherwise. -Alex-

On Wed, 2007-11-21 at 15:03 -0500, Alex Jacobson wrote:
Proof that the compiler knows which extensions are being used: it can compile the program sucessfully when the extension is turned on and not otherwise.
Counterexample (not my own): http://hpaste.org/3855 {-# OPTIONS_GHC -fbang-patterns #-} foo _ = "lol" main = putStrLn (foo "wut") where foo !x = x Duncan

Ok, I'm game to default to haskell98 in the presence of ambiguity, but in most cases the extension involves new syntax and that should be enough. Note: I would also argue that extensions that change the meaning of old code are prime-facie a bad idea. It means that, if you start using the new syntax in your existing code, you have manually to audit your code to make sure nothing else got broken and that is difficult even for experts to do really well. The example you provide is actually evidence that this bang-pattern extension is probably a bad one. -Alex- Duncan Coutts wrote:
On Wed, 2007-11-21 at 15:03 -0500, Alex Jacobson wrote:
Proof that the compiler knows which extensions are being used: it can compile the program sucessfully when the extension is turned on and not otherwise.
Counterexample (not my own):
{-# OPTIONS_GHC -fbang-patterns #-} foo _ = "lol"
main = putStrLn (foo "wut") where foo !x = x
Duncan

On Wed, 2007-11-21 at 19:26 -0500, Alex Jacobson wrote:
Ok, I'm game to default to haskell98 in the presence of ambiguity, but in most cases the extension involves new syntax and that should be enough.
In these cases ghc does generally give an error message which mentions which extension it is that you should use. This is actually better than the case where you forget to import something when ghc doesn't helpfully tell you which module you forgot to import. As others have said, one major reason for declaring extensions is for portability.
Note: I would also argue that extensions that change the meaning of old code are prime-facie a bad idea. It means that, if you start using the new syntax in your existing code, you have manually to audit your code to make sure nothing else got broken and that is difficult even for experts to do really well. The example you provide is actually evidence that this bang-pattern extension is probably a bad one.
In general I'd agree. In the case of bang patterns it's actually very hard to construct examples where the code compiles both ways (and is actually used). Duncan

Duncan Coutts wrote:
On Wed, 2007-11-21 at 19:26 -0500, Alex Jacobson wrote:
Ok, I'm game to default to haskell98 in the presence of ambiguity, but in most cases the extension involves new syntax and that should be enough.
In these cases ghc does generally give an error message which mentions which extension it is that you should use. This is actually better than the case where you forget to import something when ghc doesn't helpfully tell you which module you forgot to import.
My point is that the default should be to give a warning rather than an error and provide the user with the ability to turn those warnings off.
As others have said, one major reason for declaring extensions is for portability.
The warning should be enough information for people who want to avoid accidentally adding features that will cause their code not to run on other compilers. For those that don't care, forcing them to add zillions of pragmas is an excessive burden. -Alex-

Am Donnerstag, 22. November 2007 02:07 schrieb Alex Jacobson:
Duncan Coutts wrote:
On Wed, 2007-11-21 at 19:26 -0500, Alex Jacobson wrote:
Ok, I'm game to default to haskell98 in the presence of ambiguity, but in most cases the extension involves new syntax and that should be enough.
In these cases ghc does generally give an error message which mentions which extension it is that you should use. This is actually better than the case where you forget to import something when ghc doesn't helpfully tell you which module you forgot to import.
My point is that the default should be to give a warning rather than an error and provide the user with the ability to turn those warnings off.
As others have said, one major reason for declaring extensions is for portability.
The warning should be enough information for people who want to avoid accidentally adding features that will cause their code not to run on other compilers. For those that don't care, forcing them to add zillions of pragmas is an excessive burden.
-Alex-
Dont’t just think in terms of single modules. If I have a Cabal package, I can declare used extensions in the Cabal file. A user can decide not to start building at all if he/she sees that the package uses an extension unsupported by the compiler. Best wishes, Wolfgang

On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote:
Dont’t just think in terms of single modules. If I have a Cabal package, I can declare used extensions in the Cabal file. A user can decide not to start building at all if he/she sees that the package uses an extension unsupported by the compiler.
Indeed. In theory Cabal checks all the extensions declared to be used by the package are supported by the selected compiler. In practise I'm not sure how well it does this or what kind of error message we get. Duncan

Am Freitag, 23. November 2007 03:37 schrieben Sie:
On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote:
Dont’t just think in terms of single modules. If I have a Cabal package, I can declare used extensions in the Cabal file. A user can decide not to start building at all if he/she sees that the package uses an extension unsupported by the compiler.
Indeed. In theory Cabal checks all the extensions declared to be used by the package are supported by the selected compiler. In practise I'm not sure how well it does this or what kind of error message we get.
Duncan
The problem is, of course, that you are not forced to specify all used extensions in the Cabal file since you can still use language pragmas. Sometimes it is even desirable to use LANGUAGE pragmas instead of information in the Cabal file. For example, even if some modules use undecidable instances, I might not want all modules of the package to be compiled with -XUndecidableInstances since this could hide problems with my class structure. Best wishes, Wolfgang

On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch wrote:
Am Freitag, 23. November 2007 03:37 schrieben Sie:
On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote:
Dont’t just think in terms of single modules. If I have a Cabal package, I can declare used extensions in the Cabal file. A user can decide not to start building at all if he/she sees that the package uses an extension unsupported by the compiler.
Indeed. In theory Cabal checks all the extensions declared to be used by the package are supported by the selected compiler. In practise I'm not sure how well it does this or what kind of error message we get.
The problem is, of course, that you are not forced to specify all used extensions in the Cabal file since you can still use language pragmas. Sometimes it is even desirable to use LANGUAGE pragmas instead of information in the Cabal file. For example, even if some modules use undecidable instances, I might not want all modules of the package to be compiled with -XUndecidableInstances since this could hide problems with my class structure.
Our tentative plan there is to separate the extensions field into those used in some module, and those applied by cabal to every module. So that would allow you to specify a feature in one file but not all, while still declaring to the outside world that the package uses the feature. As for enforcing that, that may come almost for free when we get dependency chasing as we'll be looking for imports anyway. It shouldn't be much harder to look for language pragmas too. Duncan

Cabal is not a solution to this problem because 1. you want your code to work via ghci and runhaskell and perhaps via searchpath. 2. you may want to move a module from one package to another and you don't want to have to examine the cabal file to figure out how to do that. The source file should have enough information. Extensions that change the interpretation of an already valid haskell source file really need to be declared explicitly e.g. undecidableinstances. Extensions that change syntax are effectively declared by the use of that syntax. If you can parse the source, then you know which extensions it uses. -Alex- Duncan Coutts wrote:
On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch wrote:
Am Freitag, 23. November 2007 03:37 schrieben Sie:
Dont’t just think in terms of single modules. If I have a Cabal package, I can declare used extensions in the Cabal file. A user can decide not to start building at all if he/she sees that the package uses an extension unsupported by the compiler. Indeed. In theory Cabal checks all the extensions declared to be used by
On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote: the package are supported by the selected compiler. In practise I'm not sure how well it does this or what kind of error message we get.
The problem is, of course, that you are not forced to specify all used extensions in the Cabal file since you can still use language pragmas. Sometimes it is even desirable to use LANGUAGE pragmas instead of information in the Cabal file. For example, even if some modules use undecidable instances, I might not want all modules of the package to be compiled with -XUndecidableInstances since this could hide problems with my class structure.
Our tentative plan there is to separate the extensions field into those used in some module, and those applied by cabal to every module. So that would allow you to specify a feature in one file but not all, while still declaring to the outside world that the package uses the feature.
As for enforcing that, that may come almost for free when we get dependency chasing as we'll be looking for imports anyway. It shouldn't be much harder to look for language pragmas too.
Duncan _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Fri, 2007-11-23 at 14:59 -0500, Alex Jacobson wrote:
Cabal is not a solution to this problem because
1. you want your code to work via ghci and runhaskell and perhaps via searchpath.
2. you may want to move a module from one package to another and you don't want to have to examine the cabal file to figure out how to do that. The source file should have enough information.
I agree. I'd prefer to see the extensions field in the .cabal be just the union of the ones specified in LANGUAGE pragmas in the source files and not have the meaning of applying those extensions. So I'd like to see it become a declaration to the outside world about what extensions are needed to compile the package, not a way of applying extensions to all modules in the package. In practise for backwards compatibility we'll have to have both for the time being. Duncan

Alex Jacobson wrote:
Extensions that change syntax are effectively declared by the use of that syntax. If you can parse the source, then you know which extensions it uses.
I thought we'd already established that this isn't possible. Here are some code fragments that parse differently depending on which extensions are enabled: f x y = x 3# y f x = [d|d<-xs] foreign x = x f :: forall -> forall -> forall You could argue that these syntax extensions are therefore badly designed, but that's a separate discussion. Cheers, Simon
-Alex-
Duncan Coutts wrote:
On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch wrote:
Am Freitag, 23. November 2007 03:37 schrieben Sie:
Dont’t just think in terms of single modules. If I have a Cabal package, I can declare used extensions in the Cabal file. A user can decide not to start building at all if he/she sees that the package uses an extension unsupported by the compiler. Indeed. In theory Cabal checks all the extensions declared to be used by
On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote: the package are supported by the selected compiler. In practise I'm not sure how well it does this or what kind of error message we get.
The problem is, of course, that you are not forced to specify all used extensions in the Cabal file since you can still use language pragmas. Sometimes it is even desirable to use LANGUAGE pragmas instead of information in the Cabal file. For example, even if some modules use undecidable instances, I might not want all modules of the package to be compiled with -XUndecidableInstances since this could hide problems with my class structure.
Our tentative plan there is to separate the extensions field into those used in some module, and those applied by cabal to every module. So that would allow you to specify a feature in one file but not all, while still declaring to the outside world that the package uses the feature.
As for enforcing that, that may come almost for free when we get dependency chasing as we'll be looking for imports anyway. It shouldn't be much harder to look for language pragmas too.
Duncan _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Simon, from what I can tell, with GHC 6.8.1, use of foreign as a function name or forall as a type variable or leaving out a space in a list-comprehension doesn't "parse differently" when the relevant extensions are enabled, it causes a parse error. Extensions allow the same code to parse but with different meanings need to be declared explicitly. But, extensions that are obvious from syntax should be allowed to be declared simply from the use of that syntax. I am not taking a position here on the merits of any extensions. -Alex- Simon Marlow wrote:
Alex Jacobson wrote:
Extensions that change syntax are effectively declared by the use of that syntax. If you can parse the source, then you know which extensions it uses.
I thought we'd already established that this isn't possible. Here are some code fragments that parse differently depending on which extensions are enabled:
f x y = x 3# y
f x = [d|d<-xs]
foreign x = x
f :: forall -> forall -> forall
You could argue that these syntax extensions are therefore badly designed, but that's a separate discussion.
Cheers, Simon
-Alex-
Duncan Coutts wrote:
On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch wrote:
Am Freitag, 23. November 2007 03:37 schrieben Sie:
Dont’t just think in terms of single modules. If I have a Cabal package, I can declare used extensions in the Cabal file. A user can decide not to start building at all if he/she sees that the package uses an extension unsupported by the compiler. Indeed. In theory Cabal checks all the extensions declared to be used by
On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote: the package are supported by the selected compiler. In practise I'm not sure how well it does this or what kind of error message we get.
The problem is, of course, that you are not forced to specify all used extensions in the Cabal file since you can still use language pragmas. Sometimes it is even desirable to use LANGUAGE pragmas instead of information in the Cabal file. For example, even if some modules use undecidable instances, I might not want all modules of the package to be compiled with -XUndecidableInstances since this could hide problems with my class structure.
Our tentative plan there is to separate the extensions field into those used in some module, and those applied by cabal to every module. So that would allow you to specify a feature in one file but not all, while still declaring to the outside world that the package uses the feature.
As for enforcing that, that may come almost for free when we get dependency chasing as we'll be looking for imports anyway. It shouldn't be much harder to look for language pragmas too.
Duncan _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Alex Jacobson wrote:
Simon, from what I can tell, with GHC 6.8.1, use of foreign as a function name or forall as a type variable or leaving out a space in a list-comprehension doesn't "parse differently" when the relevant extensions are enabled, it causes a parse error.
Extensions allow the same code to parse but with different meanings need to be declared explicitly. But, extensions that are obvious from syntax should be allowed to be declared simply from the use of that syntax.
So for the first example I gave, f x y = x 3# y the "MagicHash" extension is one that you'd require to be explicitly declared, because the expression parses both with and without the extension. Now, Let's take the Template Haskell example: f x = [d|d<-xs] So this is valid Haskell 98, but invalid H98+TH. You would therefore like this example to parse unambiguously as H98, correct? But in order to do that, our parser would need arbitrary lookahead: it can't tell whether the expression is legal H98+TH until it gets to the '<-' in this case. Certainly it's possible to implement this using a backtracking parser, but Haskell is supposed to be parsable with a shift-reduce parser such as the one GHC uses. Or we could try parsing the whole module with various combinations of extensions turned on or off, but I'm sure you can see the problems with that. So basically the problem is that you need a parser that parses a strict superset of Haskell98 - and that's hard to achieve. Cheers, Simon
I am not taking a position here on the merits of any extensions.
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
Extensions that change syntax are effectively declared by the use of that syntax. If you can parse the source, then you know which extensions it uses.
I thought we'd already established that this isn't possible. Here are some code fragments that parse differently depending on which extensions are enabled:
f x y = x 3# y
f x = [d|d<-xs]
foreign x = x
f :: forall -> forall -> forall
You could argue that these syntax extensions are therefore badly designed, but that's a separate discussion.
Cheers, Simon
-Alex-
Duncan Coutts wrote:
On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch wrote:
Am Freitag, 23. November 2007 03:37 schrieben Sie:
On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote: > Dont’t just think in terms of single modules. If I have a Cabal > package, > I can declare used extensions in the Cabal file. A user can > decide not > to start building at all if he/she sees that the package uses an > extension unsupported by the compiler. Indeed. In theory Cabal checks all the extensions declared to be used by the package are supported by the selected compiler. In practise I'm not sure how well it does this or what kind of error message we get.
The problem is, of course, that you are not forced to specify all used extensions in the Cabal file since you can still use language pragmas. Sometimes it is even desirable to use LANGUAGE pragmas instead of information in the Cabal file. For example, even if some modules use undecidable instances, I might not want all modules of the package to be compiled with -XUndecidableInstances since this could hide problems with my class structure.
Our tentative plan there is to separate the extensions field into those used in some module, and those applied by cabal to every module. So that would allow you to specify a feature in one file but not all, while still declaring to the outside world that the package uses the feature.
As for enforcing that, that may come almost for free when we get dependency chasing as we'll be looking for imports anyway. It shouldn't be much harder to look for language pragmas too.
Duncan _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Simon, I think we've been trying to be too clever... The simple question is: for a given extension, what is the risk of leaving it turned on by default? Clearly we don't want extensions turned on that causes code to compile but with a different meaning. We may not want extensions turned on that cause most reasonable code not to compile. But I would say neither risk is significant in the case of most extensions. To use your examples: * FFI doesn't not cause h98 code to compile to a different meaning. The worst case is that code that uses 'foreign' as a function name doesn't compile. That seems okay in that more code probably uses FFI than uses foreign as a function name and the user can apply a language pragma to turn it off if really desired. * Existential types won't cause h98 code to compile with a different meaning. The worst case is that code that uses 'forall' as a type variable won't compile. That seems ok.... * TemplateHaskell also not compatible with h98. The worst case is the loss "[d|" in list comprehensions. * MagicHash: Does not appear in the ToC or the Index of the user's guide so should probably be turned off. I have no idea what it does. Note, in all cases where the extension is turned on by default, there should be a language pragma to turn it off. -Alex- Simon Marlow wrote:
Alex Jacobson wrote:
Simon, from what I can tell, with GHC 6.8.1, use of foreign as a function name or forall as a type variable or leaving out a space in a list-comprehension doesn't "parse differently" when the relevant extensions are enabled, it causes a parse error.
Extensions allow the same code to parse but with different meanings need to be declared explicitly. But, extensions that are obvious from syntax should be allowed to be declared simply from the use of that syntax.
So for the first example I gave,
f x y = x 3# y
the "MagicHash" extension is one that you'd require to be explicitly declared, because the expression parses both with and without the extension.
Now, Let's take the Template Haskell example:
f x = [d|d<-xs]
So this is valid Haskell 98, but invalid H98+TH. You would therefore like this example to parse unambiguously as H98, correct? But in order to do that, our parser would need arbitrary lookahead: it can't tell whether the expression is legal H98+TH until it gets to the '<-' in this case. Certainly it's possible to implement this using a backtracking parser, but Haskell is supposed to be parsable with a shift-reduce parser such as the one GHC uses. Or we could try parsing the whole module with various combinations of extensions turned on or off, but I'm sure you can see the problems with that.
So basically the problem is that you need a parser that parses a strict superset of Haskell98 - and that's hard to achieve.
Cheers, Simon
I am not taking a position here on the merits of any extensions.
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
Extensions that change syntax are effectively declared by the use of that syntax. If you can parse the source, then you know which extensions it uses.
I thought we'd already established that this isn't possible. Here are some code fragments that parse differently depending on which extensions are enabled:
f x y = x 3# y
f x = [d|d<-xs]
foreign x = x
f :: forall -> forall -> forall
You could argue that these syntax extensions are therefore badly designed, but that's a separate discussion.
Cheers, Simon
-Alex-
Duncan Coutts wrote:
On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch wrote:
Am Freitag, 23. November 2007 03:37 schrieben Sie: > On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote: >> Dont’t just think in terms of single modules. If I have a Cabal >> package, >> I can declare used extensions in the Cabal file. A user can >> decide not >> to start building at all if he/she sees that the package uses an >> extension unsupported by the compiler. > Indeed. In theory Cabal checks all the extensions declared to be > used by > the package are supported by the selected compiler. In practise > I'm not > sure how well it does this or what kind of error message we get.
The problem is, of course, that you are not forced to specify all used extensions in the Cabal file since you can still use language pragmas. Sometimes it is even desirable to use LANGUAGE pragmas instead of information in the Cabal file. For example, even if some modules use undecidable instances, I might not want all modules of the package to be compiled with -XUndecidableInstances since this could hide problems with my class structure.
Our tentative plan there is to separate the extensions field into those used in some module, and those applied by cabal to every module. So that would allow you to specify a feature in one file but not all, while still declaring to the outside world that the package uses the feature.
As for enforcing that, that may come almost for free when we get dependency chasing as we'll be looking for imports anyway. It shouldn't be much harder to look for language pragmas too.
Duncan _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Am Dienstag, 27. November 2007 19:21 schrieb Alex Jacobson:
Simon, I think we've been trying to be too clever...
The simple question is: for a given extension, what is the risk of leaving it turned on by default?
The risk is that one thinks that one’s program is Haskell-98-compliant while it isn’t. Or that it is compatible with another compiler while it isn’t.
[…]
Best wishes, Wolfgang

I see, all you're saying is you'd like the default to be different. (That's not the same as saying "Extensions that change syntax are effectively declared by the use of that syntax", which is what you said earlier, BTW.) Well, we could change the default. I don't think it's a great idea personally - I think we should default to compiling whatever is the most recent standard, i.e. Haskell 98. But you're arguing that the proportion of Haskell 98 code that would fail to compile is relatively small; that might well be true. This isn't a decision we could take lightly, though. Furthermore, it's only something we could change in 6.10, by which time it is likely that we'll have a clearer idea of what Haskell' is, so there might well be a -fhaskell-prime flag (or it might even be the default). Cheers, Simon Alex Jacobson wrote:
Simon, I think we've been trying to be too clever...
The simple question is: for a given extension, what is the risk of leaving it turned on by default?
Clearly we don't want extensions turned on that causes code to compile but with a different meaning. We may not want extensions turned on that cause most reasonable code not to compile.
But I would say neither risk is significant in the case of most extensions. To use your examples:
* FFI doesn't not cause h98 code to compile to a different meaning. The worst case is that code that uses 'foreign' as a function name doesn't compile. That seems okay in that more code probably uses FFI than uses foreign as a function name and the user can apply a language pragma to turn it off if really desired.
* Existential types won't cause h98 code to compile with a different meaning. The worst case is that code that uses 'forall' as a type variable won't compile. That seems ok....
* TemplateHaskell also not compatible with h98. The worst case is the loss "[d|" in list comprehensions.
* MagicHash: Does not appear in the ToC or the Index of the user's guide so should probably be turned off. I have no idea what it does.
Note, in all cases where the extension is turned on by default, there should be a language pragma to turn it off.
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
Simon, from what I can tell, with GHC 6.8.1, use of foreign as a function name or forall as a type variable or leaving out a space in a list-comprehension doesn't "parse differently" when the relevant extensions are enabled, it causes a parse error.
Extensions allow the same code to parse but with different meanings need to be declared explicitly. But, extensions that are obvious from syntax should be allowed to be declared simply from the use of that syntax.
So for the first example I gave,
f x y = x 3# y
the "MagicHash" extension is one that you'd require to be explicitly declared, because the expression parses both with and without the extension.
Now, Let's take the Template Haskell example:
f x = [d|d<-xs]
So this is valid Haskell 98, but invalid H98+TH. You would therefore like this example to parse unambiguously as H98, correct? But in order to do that, our parser would need arbitrary lookahead: it can't tell whether the expression is legal H98+TH until it gets to the '<-' in this case. Certainly it's possible to implement this using a backtracking parser, but Haskell is supposed to be parsable with a shift-reduce parser such as the one GHC uses. Or we could try parsing the whole module with various combinations of extensions turned on or off, but I'm sure you can see the problems with that.
So basically the problem is that you need a parser that parses a strict superset of Haskell98 - and that's hard to achieve.
Cheers, Simon
I am not taking a position here on the merits of any extensions.
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
Extensions that change syntax are effectively declared by the use of that syntax. If you can parse the source, then you know which extensions it uses.
I thought we'd already established that this isn't possible. Here are some code fragments that parse differently depending on which extensions are enabled:
f x y = x 3# y
f x = [d|d<-xs]
foreign x = x
f :: forall -> forall -> forall
You could argue that these syntax extensions are therefore badly designed, but that's a separate discussion.
Cheers, Simon
-Alex-
Duncan Coutts wrote:
On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch wrote: > Am Freitag, 23. November 2007 03:37 schrieben Sie: >> On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote: >>> Dont’t just think in terms of single modules. If I have a >>> Cabal package, >>> I can declare used extensions in the Cabal file. A user can >>> decide not >>> to start building at all if he/she sees that the package uses an >>> extension unsupported by the compiler. >> Indeed. In theory Cabal checks all the extensions declared to be >> used by >> the package are supported by the selected compiler. In practise >> I'm not >> sure how well it does this or what kind of error message we get.
> The problem is, of course, that you are not forced to specify all > used extensions in the Cabal file since you can still use > language pragmas. Sometimes it is even desirable to use LANGUAGE > pragmas instead of information in the Cabal file. For example, > even if some modules use undecidable instances, I might not want > all modules of the package to be compiled with > -XUndecidableInstances since this could hide problems with my > class structure.
Our tentative plan there is to separate the extensions field into those used in some module, and those applied by cabal to every module. So that would allow you to specify a feature in one file but not all, while still declaring to the outside world that the package uses the feature.
As for enforcing that, that may come almost for free when we get dependency chasing as we'll be looking for imports anyway. It shouldn't be much harder to look for language pragmas too.
Duncan _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

My original point (refined) was that I'd like a file extension (.ehs) that defaults to including all extensions that don't change the meaning of a .hs program but that may cause a small subset of them not to compile (e.g. ones that use forall as a type variable, foreign as a function, or 'd' as the result value of a list comprehension) This does not seem like a major change, does not break any existing code, and has the advantage of making it really obvious when people are going beyond haskell98. -Alex- Simon Marlow wrote:
I see, all you're saying is you'd like the default to be different.
(That's not the same as saying "Extensions that change syntax are effectively declared by the use of that syntax", which is what you said earlier, BTW.)
Well, we could change the default. I don't think it's a great idea personally - I think we should default to compiling whatever is the most recent standard, i.e. Haskell 98. But you're arguing that the proportion of Haskell 98 code that would fail to compile is relatively small; that might well be true. This isn't a decision we could take lightly, though.
Furthermore, it's only something we could change in 6.10, by which time it is likely that we'll have a clearer idea of what Haskell' is, so there might well be a -fhaskell-prime flag (or it might even be the default).
Cheers, Simon
Alex Jacobson wrote:
Simon, I think we've been trying to be too clever...
The simple question is: for a given extension, what is the risk of leaving it turned on by default?
Clearly we don't want extensions turned on that causes code to compile but with a different meaning. We may not want extensions turned on that cause most reasonable code not to compile.
But I would say neither risk is significant in the case of most extensions. To use your examples:
* FFI doesn't not cause h98 code to compile to a different meaning. The worst case is that code that uses 'foreign' as a function name doesn't compile. That seems okay in that more code probably uses FFI than uses foreign as a function name and the user can apply a language pragma to turn it off if really desired.
* Existential types won't cause h98 code to compile with a different meaning. The worst case is that code that uses 'forall' as a type variable won't compile. That seems ok....
* TemplateHaskell also not compatible with h98. The worst case is the loss "[d|" in list comprehensions.
* MagicHash: Does not appear in the ToC or the Index of the user's guide so should probably be turned off. I have no idea what it does.
Note, in all cases where the extension is turned on by default, there should be a language pragma to turn it off.
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
Simon, from what I can tell, with GHC 6.8.1, use of foreign as a function name or forall as a type variable or leaving out a space in a list-comprehension doesn't "parse differently" when the relevant extensions are enabled, it causes a parse error.
Extensions allow the same code to parse but with different meanings need to be declared explicitly. But, extensions that are obvious from syntax should be allowed to be declared simply from the use of that syntax.
So for the first example I gave,
f x y = x 3# y
the "MagicHash" extension is one that you'd require to be explicitly declared, because the expression parses both with and without the extension.
Now, Let's take the Template Haskell example:
f x = [d|d<-xs]
So this is valid Haskell 98, but invalid H98+TH. You would therefore like this example to parse unambiguously as H98, correct? But in order to do that, our parser would need arbitrary lookahead: it can't tell whether the expression is legal H98+TH until it gets to the '<-' in this case. Certainly it's possible to implement this using a backtracking parser, but Haskell is supposed to be parsable with a shift-reduce parser such as the one GHC uses. Or we could try parsing the whole module with various combinations of extensions turned on or off, but I'm sure you can see the problems with that.
So basically the problem is that you need a parser that parses a strict superset of Haskell98 - and that's hard to achieve.
Cheers, Simon
I am not taking a position here on the merits of any extensions.
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
Extensions that change syntax are effectively declared by the use of that syntax. If you can parse the source, then you know which extensions it uses.
I thought we'd already established that this isn't possible. Here are some code fragments that parse differently depending on which extensions are enabled:
f x y = x 3# y
f x = [d|d<-xs]
foreign x = x
f :: forall -> forall -> forall
You could argue that these syntax extensions are therefore badly designed, but that's a separate discussion.
Cheers, Simon
-Alex-
Duncan Coutts wrote: > On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch wrote: >> Am Freitag, 23. November 2007 03:37 schrieben Sie: >>> On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote: >>>> Dont’t just think in terms of single modules. If I have a >>>> Cabal package, >>>> I can declare used extensions in the Cabal file. A user can >>>> decide not >>>> to start building at all if he/she sees that the package uses an >>>> extension unsupported by the compiler. >>> Indeed. In theory Cabal checks all the extensions declared to >>> be used by >>> the package are supported by the selected compiler. In practise >>> I'm not >>> sure how well it does this or what kind of error message we get. > >> The problem is, of course, that you are not forced to specify >> all used extensions in the Cabal file since you can still use >> language pragmas. Sometimes it is even desirable to use >> LANGUAGE pragmas instead of information in the Cabal file. For >> example, even if some modules use undecidable instances, I might >> not want all modules of the package to be compiled with >> -XUndecidableInstances since this could hide problems with my >> class structure. > > Our tentative plan there is to separate the extensions field into > those > used in some module, and those applied by cabal to every module. > So that > would allow you to specify a feature in one file but not all, while > still declaring to the outside world that the package uses the > feature. > > As for enforcing that, that may come almost for free when we get > dependency chasing as we'll be looking for imports anyway. It > shouldn't > be much harder to look for language pragmas too. > > Duncan > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users@haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Alex Jacobson wrote:
My original point (refined) was that I'd like a file extension (.ehs) that defaults to including all extensions that don't change the meaning of a .hs program but that may cause a small subset of them not to compile (e.g. ones that use forall as a type variable, foreign as a function, or 'd' as the result value of a list comprehension)
This does not seem like a major change, does not break any existing code, and has the advantage of making it really obvious when people are going beyond haskell98.
It'll break all sorts of things when .ehs has to get merged into .hs the next time this conversation comes around, unless it's guaranteed that all .hs processors will eventually be upgraded to cope with .ehs semantics. I don't think anyone's arguing for that... -- Alex
-Alex-
Simon Marlow wrote:
I see, all you're saying is you'd like the default to be different.
(That's not the same as saying "Extensions that change syntax are effectively declared by the use of that syntax", which is what you said earlier, BTW.)
Well, we could change the default. I don't think it's a great idea personally - I think we should default to compiling whatever is the most recent standard, i.e. Haskell 98. But you're arguing that the proportion of Haskell 98 code that would fail to compile is relatively small; that might well be true. This isn't a decision we could take lightly, though.
Furthermore, it's only something we could change in 6.10, by which time it is likely that we'll have a clearer idea of what Haskell' is, so there might well be a -fhaskell-prime flag (or it might even be the default).
Cheers, Simon
Alex Jacobson wrote:
Simon, I think we've been trying to be too clever...
The simple question is: for a given extension, what is the risk of leaving it turned on by default?
Clearly we don't want extensions turned on that causes code to compile but with a different meaning. We may not want extensions turned on that cause most reasonable code not to compile.
But I would say neither risk is significant in the case of most extensions. To use your examples:
* FFI doesn't not cause h98 code to compile to a different meaning. The worst case is that code that uses 'foreign' as a function name doesn't compile. That seems okay in that more code probably uses FFI than uses foreign as a function name and the user can apply a language pragma to turn it off if really desired.
* Existential types won't cause h98 code to compile with a different meaning. The worst case is that code that uses 'forall' as a type variable won't compile. That seems ok....
* TemplateHaskell also not compatible with h98. The worst case is the loss "[d|" in list comprehensions.
* MagicHash: Does not appear in the ToC or the Index of the user's guide so should probably be turned off. I have no idea what it does.
Note, in all cases where the extension is turned on by default, there should be a language pragma to turn it off.
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
Simon, from what I can tell, with GHC 6.8.1, use of foreign as a function name or forall as a type variable or leaving out a space in a list-comprehension doesn't "parse differently" when the relevant extensions are enabled, it causes a parse error.
Extensions allow the same code to parse but with different meanings need to be declared explicitly. But, extensions that are obvious from syntax should be allowed to be declared simply from the use of that syntax.
So for the first example I gave,
f x y = x 3# y
the "MagicHash" extension is one that you'd require to be explicitly declared, because the expression parses both with and without the extension.
Now, Let's take the Template Haskell example:
f x = [d|d<-xs]
So this is valid Haskell 98, but invalid H98+TH. You would therefore like this example to parse unambiguously as H98, correct? But in order to do that, our parser would need arbitrary lookahead: it can't tell whether the expression is legal H98+TH until it gets to the '<-' in this case. Certainly it's possible to implement this using a backtracking parser, but Haskell is supposed to be parsable with a shift-reduce parser such as the one GHC uses. Or we could try parsing the whole module with various combinations of extensions turned on or off, but I'm sure you can see the problems with that.
So basically the problem is that you need a parser that parses a strict superset of Haskell98 - and that's hard to achieve.
Cheers, Simon
I am not taking a position here on the merits of any extensions.
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
> Extensions that change syntax are effectively declared by the use > of that syntax. If you can parse the source, then you know which > extensions it uses.
I thought we'd already established that this isn't possible. Here are some code fragments that parse differently depending on which extensions are enabled:
f x y = x 3# y
f x = [d|d<-xs]
foreign x = x
f :: forall -> forall -> forall
You could argue that these syntax extensions are therefore badly designed, but that's a separate discussion.
Cheers, Simon
> -Alex- > > > Duncan Coutts wrote: >> On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch wrote: >>> Am Freitag, 23. November 2007 03:37 schrieben Sie: >>>> On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote: >>>>> Dont’t just think in terms of single modules. If I have a >>>>> Cabal package, >>>>> I can declare used extensions in the Cabal file. A user can >>>>> decide not >>>>> to start building at all if he/she sees that the package uses an >>>>> extension unsupported by the compiler. >>>> Indeed. In theory Cabal checks all the extensions declared to >>>> be used by >>>> the package are supported by the selected compiler. In >>>> practise I'm not >>>> sure how well it does this or what kind of error message we get. >> >>> The problem is, of course, that you are not forced to specify >>> all used extensions in the Cabal file since you can still use >>> language pragmas. Sometimes it is even desirable to use >>> LANGUAGE pragmas instead of information in the Cabal file. For >>> example, even if some modules use undecidable instances, I >>> might not want all modules of the package to be compiled with >>> -XUndecidableInstances since this could hide problems with my >>> class structure. >> >> Our tentative plan there is to separate the extensions field >> into those >> used in some module, and those applied by cabal to every module. >> So that >> would allow you to specify a feature in one file but not all, while >> still declaring to the outside world that the package uses the >> feature. >> >> As for enforcing that, that may come almost for free when we get >> dependency chasing as we'll be looking for imports anyway. It >> shouldn't >> be much harder to look for language pragmas too. >> >> Duncan >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users@haskell.org >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users@haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users >
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Alex, | Ok, I'm game to default to haskell98 in the presence of ambiguity, but | in most cases the extension involves new syntax and that should be enough. Trying to compile the program both ways (or 2^n ways) to check for ambiguity sounds like a pretty heavy hammer to crack this nut. GHC is a Haskell-98 compiler by default, and I think it's a good default. You are arguing to change the default, but that's always an uphill battle because there will be others with good user-based reasons (like yours) for preferring the current default. Better would be to make it easy to get what you want. It is certainly useful to have a name for a bundle of flags. Currently -O, -O2, and -fglasgow-exts, and -Wall are the only such names. But we don't currently have a "switch on all extensions" flag, -Xall say. If you'd find that useful, you could put {-# OPTIONS_GHC -Xall #-} at the top of all your modules, and you'd be done. In situations where you didn't want a particular extension (like Duncan's example) you can switch it off selectively with -XNoBangPatterns. Simon

It seems like use of a lot of extensions is so obvious from syntax that the compiler is able to suggest the correct pragma to turn on to enable that syntax. In fact the way I know to use most of these pragmas is because the compiler told me about them. So, my suggestion is that in any case where the compiler currently suggests use of a particular pragma in an error message, it should instead turn that pragma on and produce a warning. Does that make sense? -Alex- Simon Peyton-Jones wrote:
Alex,
| Ok, I'm game to default to haskell98 in the presence of ambiguity, but | in most cases the extension involves new syntax and that should be enough.
Trying to compile the program both ways (or 2^n ways) to check for ambiguity sounds like a pretty heavy hammer to crack this nut.
GHC is a Haskell-98 compiler by default, and I think it's a good default. You are arguing to change the default, but that's always an uphill battle because there will be others with good user-based reasons (like yours) for preferring the current default.
Better would be to make it easy to get what you want. It is certainly useful to have a name for a bundle of flags. Currently -O, -O2, and -fglasgow-exts, and -Wall are the only such names.
But we don't currently have a "switch on all extensions" flag, -Xall say. If you'd find that useful, you could put {-# OPTIONS_GHC -Xall #-} at the top of all your modules, and you'd be done. In situations where you didn't want a particular extension (like Duncan's example) you can switch it off selectively with -XNoBangPatterns.
Simon

| So, my suggestion is that in any case where the compiler currently | suggests use of a particular pragma in an error message, it should | instead turn that pragma on and produce a warning. In the cases where the compiler makes that suggestion, yes what you suggest would be feasible I think. But it would be patchy and ad hoc -- often the compiler would "do the right thing" (at least as you see it), but sometimes not. Nevertheless, patchy and ad-hoc solutions are sometimes very convenient. I certainly agree that messages of the form "bad programmer, you clearly meant X but you didn't *write* X; so go write X and then I'll compile your program" are tiresome. Why not make it a feature request and try to get people to vote for it (by adding themselves to the cc list and/or adding comments)? Simon

Ok, added as a feature request. http://hackage.haskell.org/trac/ghc/ticket/1921#preview Simon Peyton-Jones wrote:
| So, my suggestion is that in any case where the compiler currently | suggests use of a particular pragma in an error message, it should | instead turn that pragma on and produce a warning.
In the cases where the compiler makes that suggestion, yes what you suggest would be feasible I think. But it would be patchy and ad hoc -- often the compiler would "do the right thing" (at least as you see it), but sometimes not.
Nevertheless, patchy and ad-hoc solutions are sometimes very convenient. I certainly agree that messages of the form "bad programmer, you clearly meant X but you didn't *write* X; so go write X and then I'll compile your program" are tiresome.
Why not make it a feature request and try to get people to vote for it (by adding themselves to the cc list and/or adding comments)?
Simon

Alex Jacobson wrote:
Ok, added as a feature request.
this doesn't seem to say anything about perhaps let's have patchy ad-hoc-ness
Nevertheless, patchy and ad-hoc solutions are sometimes very convenient. I certainly agree that messages of the form "bad programmer, you clearly meant X but you didn't *write* X; so go write X and then I'll compile your program" are tiresome.
not the style of ghc at all, but it could be less _tiresome_ if it asks "do you want me to add that to the file's language pragma?" (which would make sense as an IDE's job, if we ever end up with one, I suppose) Isaac

Wolfgang Jeltsch
It made me discover that I use more language extensions than I thought I was using.
I think, it’s a good thing if you have to be clear about what extensions you use and what you don’t use. What if someone wants to compile your code with a different compiler which doesn’t support all of GHC’s extensions?
And - re the Hackage library rank - the next logical step is to
analyse the actual extension usage before deciding what goes into
Haskell'. (Not that it should be the sole deciding factor, of
course.)
Wolfgang Jeltsch
I don’t think so. For example, if you don’t use rank-2 polymorphism and similar things, forall is a perfect name for a type variable.
Without implicit parameters, you can use (?) as an operator regardless of spacing. And, I think, some constructs (list comprehensions?) have a different meaning with Template Haskell. Most of unintended usages would probably end up as errors, though. -k -- If I haven't seen further, it is by standing in the footprints of giants

Am Dienstag, 20. November 2007 22:15 schrieb Alex Jacobson:
.ehs stands for extended haskell and encapsulates the 90% case of people just wanting -fglasgow-exts with a minimum of fuss.
Having a filetype seesm better than the alternatives of either adding boilerplate language/options pragmas to the top of your source files or putting them in a cabal file.
-Alex-
And if a new Haskell standard is released, we have to rename lots of files from *.ehs to *.hs. :-( Extended Haskell is Haskell in a different version. So it’s still Haskell and should be put into *.hs files. Best wishes, Wolfgang

I'm fine with that as well. I'm just opposed to being force to look up the precise names the compiler happens to use for each language extension I happen to use. Having -fglasgow-exts turned on by default also works. -Alex- Wolfgang Jeltsch wrote:
Am Dienstag, 20. November 2007 22:15 schrieb Alex Jacobson:
.ehs stands for extended haskell and encapsulates the 90% case of people just wanting -fglasgow-exts with a minimum of fuss.
Having a filetype seesm better than the alternatives of either adding boilerplate language/options pragmas to the top of your source files or putting them in a cabal file.
-Alex-
And if a new Haskell standard is released, we have to rename lots of files from *.ehs to *.hs. :-(
Extended Haskell is Haskell in a different version. So it’s still Haskell and should be put into *.hs files.
Best wishes, Wolfgang _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

I'm very much in favor of listing the exact extensions used in each file,
because I try to keep them to a minimum.
I would like to see a LANGUAGE Haskell' which includes the things that are
likely to be in Haskell' (if there is ever a Haskell').
-- Lennart
On Nov 20, 2007 9:42 PM, Alex Jacobson
I'm fine with that as well. I'm just opposed to being force to look up the precise names the compiler happens to use for each language extension I happen to use. Having -fglasgow-exts turned on by default also works.
-Alex-
Am Dienstag, 20. November 2007 22:15 schrieb Alex Jacobson:
.ehs stands for extended haskell and encapsulates the 90% case of
Wolfgang Jeltsch wrote: people
just wanting -fglasgow-exts with a minimum of fuss.
Having a filetype seesm better than the alternatives of either adding boilerplate language/options pragmas to the top of your source files or putting them in a cabal file.
-Alex-
And if a new Haskell standard is released, we have to rename lots of files from *.ehs to *.hs. :-(
Extended Haskell is Haskell in a different version. So it's still Haskell and should be put into *.hs files.
Best wishes, Wolfgang _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

For people like Lennart, perhaps the correct answer is a compiler flag that enumerates the extensions used as a warning. The warning should be enough to help him keep the extensions to a minimum. -Alex- Lennart Augustsson wrote:
I'm very much in favor of listing the exact extensions used in each file, because I try to keep them to a minimum. I would like to see a LANGUAGE Haskell' which includes the things that are likely to be in Haskell' (if there is ever a Haskell').
-- Lennart
On Nov 20, 2007 9:42 PM, Alex Jacobson
mailto:alex@alexjacobson.com> wrote: I'm fine with that as well. I'm just opposed to being force to look up the precise names the compiler happens to use for each language extension I happen to use. Having -fglasgow-exts turned on by default also works.
-Alex-
Wolfgang Jeltsch wrote: > Am Dienstag, 20. November 2007 22:15 schrieb Alex Jacobson: >> .ehs stands for extended haskell and encapsulates the 90% case of people >> just wanting -fglasgow-exts with a minimum of fuss. >> >> Having a filetype seesm better than the alternatives of either adding >> boilerplate language/options pragmas to the top of your source files or >> putting them in a cabal file. >> >> -Alex- > > And if a new Haskell standard is released, we have to rename lots of files > from *.ehs to *.hs. :-( > > Extended Haskell is Haskell in a different version. So it's still Haskell and > should be put into *.hs files. > > Best wishes, > Wolfgang > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users@haskell.org mailto:Glasgow-haskell-users@haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org mailto:Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Alex Jacobson wrote:
I'm fine with that as well. I'm just opposed to being force to look up the precise names the compiler happens to use for each language extension I happen to use. Having -fglasgow-exts turned on by default also works.
-fglasgow-exts is a historical relic. It's just an arbitrary collection of extensions. It doesn't contain all the extensions provided by GHC, as many of them steal syntax and you probably don't want them all on at the same time. We're trying to move away from -fglasgow-exts, which is why GHC 6.8.1 provides separate flags for all the extensions we provide. Eventually we'll have a new standard (Haskell' or whatever) that will collect many of the extensions together, so you'll just have to write {-# LANGUAGE Haskell' #-}. Cheers, Simon

Isn't use of the extensions detectable by the compiler? If so, then forcing the user manually to enumerate them at the top of a source file seems like forcing the user to write a lot of unnecessary boilerplate. It seems preferable for the compiler ny default just to issue warnings about what extensions are used. Then the person doing the compiling can decide to modify code not to use those features, to add pragmas so as not to cause warning, or to add compiler flags that tells it not to issue them. In any case, I'm pretty sure the correct answer is not 50 language pragmas with arbitrary spellings for various language features at the top of each source file. -Alex- Simon Marlow wrote:
Alex Jacobson wrote:
I'm fine with that as well. I'm just opposed to being force to look up the precise names the compiler happens to use for each language extension I happen to use. Having -fglasgow-exts turned on by default also works.
-fglasgow-exts is a historical relic. It's just an arbitrary collection of extensions. It doesn't contain all the extensions provided by GHC, as many of them steal syntax and you probably don't want them all on at the same time. We're trying to move away from -fglasgow-exts, which is why GHC 6.8.1 provides separate flags for all the extensions we provide. Eventually we'll have a new standard (Haskell' or whatever) that will collect many of the extensions together, so you'll just have to write {-# LANGUAGE Haskell' #-}.
Cheers, Simon _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Alex Jacobson wrote:
[...][ 50 language pragmas with arbitrary spellings [...]
Indeed. For instance, I always get an error for -XMultiParameterTypeClasses . (Without looking at the documentation: do you see why?) PS: indeed I just checked the docs and found -XDisambiguateRecordFields Was this advertized? It seems that's what I've been missing for years. Best regards, Johannes.

So what is DisambiguateRecordFields? -Alex- Johannes Waldmann wrote:
Alex Jacobson wrote:
[...][ 50 language pragmas with arbitrary spellings [...]
Indeed.
For instance, I always get an error for -XMultiParameterTypeClasses .
(Without looking at the documentation: do you see why?)
PS: indeed I just checked the docs and found -XDisambiguateRecordFields Was this advertized? It seems that's what I've been missing for years.
Best regards, Johannes.

| So what is DisambiguateRecordFields? It's documented in the user manual (for the HEAD): http://www.haskell.org/ghc/dist/current/docs/users_guide/syntax-extns.html#d... Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell- | users-bounces@haskell.org] On Behalf Of Alex Jacobson | Sent: 21 November 2007 20:26 | To: Johannes Waldmann | Cc: glasgow-haskell-users@haskell.org; Simon Marlow | Subject: Re: suggestion: add a .ehs file type | | So what is DisambiguateRecordFields? | | -Alex- | | Johannes Waldmann wrote: | > Alex Jacobson wrote: | > | >> [...][ 50 language pragmas with arbitrary spellings [...] | > | > Indeed. | > | > For instance, I always get an error for -XMultiParameterTypeClasses . | > | > (Without looking at the documentation: do you see why?) | > | > | > PS: indeed I just checked the docs and found -XDisambiguateRecordFields | > Was this advertized? It seems that's what I've been missing for years. | > | > Best regards, Johannes. | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Nice feature but feel like a band-aid. In particular it makes SYB style programming more difficult because field labels aren't types. Almost every other record syntax plan involves field labels as types so you can do interesting type dispatch. With this syntax, there is increasing probability that salary becomes a standard field name rather than a type. What would be really much more useful would be an alternative newtype syntax like this: label Salary = salary::Float deriving Show which would be equivalent of newtype Salary = Salary Float deriving Show salary (Salary x) = x Does this make sense? -Alex- Tracking these open issues: * too many pragma declarations * recursive deriving * labels * : for reload in ghci * not reloading all the modules on :r Simon Peyton-Jones wrote:
| So what is DisambiguateRecordFields?
It's documented in the user manual (for the HEAD):
http://www.haskell.org/ghc/dist/current/docs/users_guide/syntax-extns.html#d...
Simon
| -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell- | users-bounces@haskell.org] On Behalf Of Alex Jacobson | Sent: 21 November 2007 20:26 | To: Johannes Waldmann | Cc: glasgow-haskell-users@haskell.org; Simon Marlow | Subject: Re: suggestion: add a .ehs file type | | So what is DisambiguateRecordFields? | | -Alex- | | Johannes Waldmann wrote: | > Alex Jacobson wrote: | > | >> [...][ 50 language pragmas with arbitrary spellings [...] | > | > Indeed. | > | > For instance, I always get an error for -XMultiParameterTypeClasses . | > | > (Without looking at the documentation: do you see why?) | > | > | > PS: indeed I just checked the docs and found -XDisambiguateRecordFields | > Was this advertized? It seems that's what I've been missing for years. | > | > Best regards, Johannes. | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

| Nice feature but feel like a band-aid. In particular it makes SYB style | programming more difficult because field labels aren't types. | | Almost every other record syntax plan involves field labels as types so | you can do interesting type dispatch. Record systems are indeed an interesting area. You might like to contribute to the discussion centred here: http://hackage.haskell.org/trac/ghc/wiki/ExtensibleRecords | Tracking these open issues: | * too many pragma declarations | * recursive deriving | * labels | * : for reload in ghci | * not reloading all the modules on :r Discussing these issues by email is an excellent way to characterise the issue and evolve a proposed design. But the way to track them is to use Trac -- so do go ahead and submit bug reports and/or feature requests. Simon

Simon Peyton-Jones wrote:
| Nice feature but feel like a band-aid. In particular it makes SYB style | programming more difficult because field labels aren't types. | | Almost every other record syntax plan involves field labels as types so | you can do interesting type dispatch.
Record systems are indeed an interesting area. You might like to contribute to the discussion centred here: http://hackage.haskell.org/trac/ghc/wiki/ExtensibleRecords
| Tracking these open issues: | * too many pragma declarations | * recursive deriving | * labels | * : for reload in ghci | * not reloading all the modules on :r
Discussing these issues by email is an excellent way to characterise the issue and evolve a proposed design. But the way to track them is to use Trac -- so do go ahead and submit bug reports and/or feature requests.
I've created tickets for the last two: http://hackage.haskell.org/trac/ghc/ticket/1914 http://hackage.haskell.org/trac/ghc/ticket/1915 Cheers, Simon

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 Alex Jacobson wrote:
So what is DisambiguateRecordFields?
http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#di... -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.4-svn0 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFHRKOL3ZnXZuOVyMIRAsCeAKCmSdefclDcNk4ERx1Km3JgADZpxACeJjdy i8/gb70DMXF68pS9ivZGClA= =3ohO -----END PGP SIGNATURE-----

On Wed, Nov 21, 2007 at 07:55:51PM +0100, Johannes Waldmann wrote:
PS: indeed I just checked the docs and found -XDisambiguateRecordFields Was this advertized?
It's in the 6.8.1 release notes (well, the -fdisambiguate-record-fields flag is, but we should have advertised -XDisambiguateRecordFields instead). Thanks Ian

Am Mittwoch, 21. November 2007 19:55 schrieb Johannes Waldmann:
[…]
PS: indeed I just checked the docs and found -XDisambiguateRecordFields Was this advertized? It seems that's what I've been missing for years.
You may thank me since I asked the GHC developers for this. ;-) And of course, you should thank the GHC developers who finally implemented it. ;-) So my conclusion is: Just ask the developers. They care for the wishes of their users.
Best regards, Johannes.
Best wishes, Wolfgang

Alex Jacobson wrote:
Isn't use of the extensions detectable by the compiler?
Not always, no. Some extensions modify the syntax, such that programs accepted with the extension turned on are not necessarily a superset of those accepted with the extension turned off. For example: MagicHash (modifies the meaning of a # suffix on an identifier), RankNTypes (steals 'forall' and '.' from the type-variable namespace), etc. Cheers, Simon
If so, then forcing the user manually to enumerate them at the top of a source file seems like forcing the user to write a lot of unnecessary boilerplate. It seems preferable for the compiler ny default just to issue warnings about what extensions are used. Then the person doing the compiling can decide to modify code not to use those features, to add pragmas so as not to cause warning, or to add compiler flags that tells it not to issue them.
In any case, I'm pretty sure the correct answer is not 50 language pragmas with arbitrary spellings for various language features at the top of each source file.
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
I'm fine with that as well. I'm just opposed to being force to look up the precise names the compiler happens to use for each language extension I happen to use. Having -fglasgow-exts turned on by default also works.
-fglasgow-exts is a historical relic. It's just an arbitrary collection of extensions. It doesn't contain all the extensions provided by GHC, as many of them steal syntax and you probably don't want them all on at the same time. We're trying to move away from -fglasgow-exts, which is why GHC 6.8.1 provides separate flags for all the extensions we provide. Eventually we'll have a new standard (Haskell' or whatever) that will collect many of the extensions together, so you'll just have to write {-# LANGUAGE Haskell' #-}.
Cheers, Simon _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Alex Jacobson wrote:
In any case, I'm pretty sure the correct answer is not 50 language pragmas with arbitrary spellings for various language features at the top of each source file.
You probably won't like any of these, but there are many ways to avoid writing out all the pragmas at the top of each file. 1. Use Cabal's extensions field. 2. Use CPP MyExtensions.h: {-# LANGUAGE TemplateHaskell, FlexibleInstances, OverlappingInstances, UndecidableInstances, CPP, ScopedTypeVariables, PatternSignatures, GADTs, PolymorphicComponents, FlexibleContexts, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} MyModule.hs: {-# LANGUAGE CPP #-} #include "MyExtensions.h" 3. Use a shell alias alias ghce='ghc -XTemplateHaskell -XFlexibleInstances ...' 4. use a script wrapper for GHC #!/bin/sh exec ghc -XTemplateHaskell -XFlexibleInstances ... $* I'm sure there are more... Cheers, Simon
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
I'm fine with that as well. I'm just opposed to being force to look up the precise names the compiler happens to use for each language extension I happen to use. Having -fglasgow-exts turned on by default also works.
-fglasgow-exts is a historical relic. It's just an arbitrary collection of extensions. It doesn't contain all the extensions provided by GHC, as many of them steal syntax and you probably don't want them all on at the same time. We're trying to move away from -fglasgow-exts, which is why GHC 6.8.1 provides separate flags for all the extensions we provide. Eventually we'll have a new standard (Haskell' or whatever) that will collect many of the extensions together, so you'll just have to write {-# LANGUAGE Haskell' #-}.
Cheers, Simon _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Or use a preprocessor that inserts a LANGUAGE pragma. :)
On Nov 22, 2007 9:14 AM, Simon Marlow
Alex Jacobson wrote:
In any case, I'm pretty sure the correct answer is not 50 language pragmas with arbitrary spellings for various language features at the top of each source file.
You probably won't like any of these, but there are many ways to avoid writing out all the pragmas at the top of each file.
1. Use Cabal's extensions field.
2. Use CPP
MyExtensions.h: {-# LANGUAGE TemplateHaskell, FlexibleInstances, OverlappingInstances, UndecidableInstances, CPP, ScopedTypeVariables, PatternSignatures, GADTs, PolymorphicComponents, FlexibleContexts, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-}
MyModule.hs: {-# LANGUAGE CPP #-} #include "MyExtensions.h"
3. Use a shell alias
alias ghce='ghc -XTemplateHaskell -XFlexibleInstances ...'
4. use a script wrapper for GHC
#!/bin/sh exec ghc -XTemplateHaskell -XFlexibleInstances ... $*
I'm sure there are more...
Cheers, Simon
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
I'm fine with that as well. I'm just opposed to being force to look up the precise names the compiler happens to use for each language extension I happen to use. Having -fglasgow-exts turned on by default also works.
-fglasgow-exts is a historical relic. It's just an arbitrary collection of extensions. It doesn't contain all the extensions provided by GHC, as many of them steal syntax and you probably don't want them all on at the same time. We're trying to move away from -fglasgow-exts, which is why GHC 6.8.1 provides separate flags for all the extensions we provide. Eventually we'll have a new standard (Haskell' or whatever) that will collect many of the extensions together, so you'll just have to write {-# LANGUAGE Haskell' #-}.
Cheers, Simon _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Alex, Lennart's suggestion makes me think: Why not make SearchPath
into a preprocessor? It could recognize a .ehs extension, and then do
some very simple preprocessing (adds pragmas according to user's
settings).
--
Robin Bate Boerop
On 22/11/2007, Lennart Augustsson
Or use a preprocessor that inserts a LANGUAGE pragma. :)
On Nov 22, 2007 9:14 AM, Simon Marlow
wrote: Alex Jacobson wrote:
In any case, I'm pretty sure the correct answer is not 50 language pragmas with arbitrary spellings for various language features at the top of each source file.
You probably won't like any of these, but there are many ways to avoid writing out all the pragmas at the top of each file.
1. Use Cabal's extensions field.
2. Use CPP
MyExtensions.h :
{-# LANGUAGE TemplateHaskell, FlexibleInstances, OverlappingInstances, UndecidableInstances, CPP, ScopedTypeVariables, PatternSignatures, GADTs, PolymorphicComponents, FlexibleContexts, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-}
MyModule.hs: {-# LANGUAGE CPP #-} #include "MyExtensions.h"
3. Use a shell alias
alias ghce='ghc -XTemplateHaskell -XFlexibleInstances ...'
4. use a script wrapper for GHC
#!/bin/sh exec ghc -XTemplateHaskell -XFlexibleInstances ... $*
I'm sure there are more...
Cheers, Simon
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
I'm fine with that as well. I'm just opposed to being force to look up the precise names the compiler happens to use for each language extension I happen to use. Having -fglasgow-exts turned on by default also works.
-fglasgow-exts is a historical relic. It's just an arbitrary collection of extensions. It doesn't contain all the extensions provided by GHC, as many of them steal syntax and you probably don't want them all on at the same time. We're trying to move away from -fglasgow-exts, which is why GHC 6.8.1 provides separate flags for all the extensions we provide. Eventually we'll have a new standard (Haskell' or whatever) that will collect many of the extensions together, so you'll just have to write {-# LANGUAGE Haskell' #-}.
Cheers, Simon

Right now I have it automatically add -glasgow-exts unless the user explicitly turns it off. I prefer to have packages that are also cabal compatible.... If there is a way to get cabal also to preprocess .ehs correctly then we are good to go! -Alex- Robin Bate Boerop wrote:
Alex, Lennart's suggestion makes me think: Why not make SearchPath into a preprocessor? It could recognize a .ehs extension, and then do some very simple preprocessing (adds pragmas according to user's settings).

Distribution.Simple.PreProcess could be extended to register
SearchPath as a preprocessor for .ehs files (see stuff near
PPSuffixHandler). Of course, this requires changing Cabal.
Alternately, I think the same effect could be had using Cabal's
UserHooks (see stuff near hookedPreProcessors).
That way, SearchPath users could continue to ignore Cabal, but Cabal
would preprocess .ehs files correctly (if users have SearchPath
installed) and Cabal users would be happy.
(This discussion interests me because I share Alex's opinion about
adding LANGUAGE pragmas to source files.)
On 12/12/2007, Alex Jacobson
Right now I have it automatically add -glasgow-exts unless the user explicitly turns it off. I prefer to have packages that are also cabal compatible.... If there is a way to get cabal also to preprocess .ehs correctly then we are good to go!
-Alex-
Robin Bate Boerop wrote:
Alex, Lennart's suggestion makes me think: Why not make SearchPath into a preprocessor? It could recognize a .ehs extension, and then do some very simple preprocessing (adds pragmas according to user's settings).
-- Robin Bate Boerop

Yeah, since I use searchpath rather than cabal, I made searchpath default to adding -fglasgow-exts when the "compiler" is ghc, ghci, or runghc. Passing -fno-glasgow-exts on the command line turns this off. -Alex- Simon Marlow wrote:
Alex Jacobson wrote:
In any case, I'm pretty sure the correct answer is not 50 language pragmas with arbitrary spellings for various language features at the top of each source file.
You probably won't like any of these, but there are many ways to avoid writing out all the pragmas at the top of each file.
1. Use Cabal's extensions field.
2. Use CPP
MyExtensions.h: {-# LANGUAGE TemplateHaskell, FlexibleInstances, OverlappingInstances, UndecidableInstances, CPP, ScopedTypeVariables, PatternSignatures, GADTs, PolymorphicComponents, FlexibleContexts, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-}
MyModule.hs: {-# LANGUAGE CPP #-} #include "MyExtensions.h"
3. Use a shell alias
alias ghce='ghc -XTemplateHaskell -XFlexibleInstances ...'
4. use a script wrapper for GHC
#!/bin/sh exec ghc -XTemplateHaskell -XFlexibleInstances ... $*
I'm sure there are more...
Cheers, Simon
-Alex-
Simon Marlow wrote:
Alex Jacobson wrote:
I'm fine with that as well. I'm just opposed to being force to look up the precise names the compiler happens to use for each language extension I happen to use. Having -fglasgow-exts turned on by default also works.
-fglasgow-exts is a historical relic. It's just an arbitrary collection of extensions. It doesn't contain all the extensions provided by GHC, as many of them steal syntax and you probably don't want them all on at the same time. We're trying to move away from -fglasgow-exts, which is why GHC 6.8.1 provides separate flags for all the extensions we provide. Eventually we'll have a new standard (Haskell' or whatever) that will collect many of the extensions together, so you'll just have to write {-# LANGUAGE Haskell' #-}.
Cheers, Simon _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Am Mittwoch, 21. November 2007 19:38 schrieb Alex Jacobson:
Isn't use of the extensions detectable by the compiler?
So you want extension inference. ;-)
[…]
In any case, I'm pretty sure the correct answer is not 50 language pragmas with arbitrary spellings for various language features at the top of each source file.
You can put them into a Cabal file.
-Alex-
Best wishes, Wolfgang

What about literate files? the inclusion of extended haskell files expand to
too much file extension in my opinion.
*.hs
*.lhs
*.ehs
*.elhs
On Nov 20, 2007 10:15 PM, Alex Jacobson
.ehs stands for extended haskell and encapsulates the 90% case of people just wanting -fglasgow-exts with a minimum of fuss.
Having a filetype seesm better than the alternatives of either adding boilerplate language/options pragmas to the top of your source files or putting them in a cabal file.
-Alex- _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Luis Cabellos, http://malcodigo.blogspot.com
participants (14)
-
Alex Jacobson
-
Alex Young
-
Duncan Coutts
-
Ian Lynagh
-
Isaac Dupree
-
Johannes Waldmann
-
Ketil Malde
-
Lennart Augustsson
-
Luis Cabellos
-
Neil Mitchell
-
Robin Bate Boerop
-
Simon Marlow
-
Simon Peyton-Jones
-
Wolfgang Jeltsch