RE: [Haskell-cafe] Interest in helping w/ Haskell standard

On 12 October 2005 23:50, Sebastian Sylvan wrote:
(I'm specifically interested in seeing SPJ's records proposal included, and a new module system).
Highly unlikely, IMHO. A new revision of the Haskell standard is not the place for testing new research, rather it's a clear specification of existing well-understood language features. If you want a new record system, or a new module system, now is the time to start designing and implementing them ready for the next standardisation process. Cheers, Simon

On Thursday 13 October 2005 09:42, Simon Marlow wrote:
On 12 October 2005 23:50, Sebastian Sylvan wrote:
(I'm specifically interested in seeing SPJ's records proposal included, and a new module system).
Highly unlikely, IMHO. A new revision of the Haskell standard is not the place for testing new research, rather it's a clear specification of existing well-understood language features.
... and, in the case of the Standard Prelude section, or equivalent, a specification of well-understood functions that the spec authors agree "should" be provided in all implementations. I would hope that arbitrary binary I/O - to cite an important example - would not be considered a "research topic", as it is actually quite trivial. (It is, however, one of the "must haves" for Haskell to be considered for use in production systems.) -- Robin

On Thu, Oct 13, 2005 at 11:29:57AM +0000,
Robin Green
... and, in the case of the Standard Prelude section, or equivalent, a specification of well-understood functions that the spec authors agree "should" be provided in all implementations. ... (It is, however, one of the "must haves" for Haskell to be considered for use in production systems.)
Regexps and XML are, IMHO, also "must haves".

Am Donnerstag, 13. Oktober 2005 13:39 schrieb Stephane Bortzmeyer:
[...]
Regexps and XML are, IMHO, also "must haves".
By the way, it should be possible to handle regular expressions in an Haskell-like way. I always couldn't understand why one has to write regular expressions as strings which have to be interpreted at runtime. I would prefer something like this: identifierRegExp = alpha +++ iterate (alpha ||| digit ||| underscore) alpha = ('A' `to` 'Z') ||| ('a' `to` 'z') digit = '0' `to` '9' underscore = only '_' What do others think? Best wishes, Wolfgang

On Fri, Oct 14, 2005 at 04:20:24PM +0200,
Wolfgang Jeltsch
By the way, it should be possible to handle regular expressions in an Haskell-like way.
If you like so, but as one more possibility, not as the only way.
I always couldn't understand why one has to write regular expressions as strings
Because the language used inside these strings is standard, multi-language, widely used and documented?

On Fri, 14 Oct 2005, Stephane Bortzmeyer wrote:
On Fri, Oct 14, 2005 at 04:20:24PM +0200, Wolfgang Jeltsch
wrote a message of 23 lines which said: By the way, it should be possible to handle regular expressions in an Haskell-like way.
If you like so, but as one more possibility, not as the only way.
I'm not sure I see the need to do that specifically given the existance of libraries like Parsec? -- flippa@flippac.org There is no magic bullet. There are, however, plenty of bullets that magically home in on feet when not used in exactly the right circumstances.

On 2005-10-14 at 16:25+0200 Stephane Bortzmeyer wrote:
On Fri, Oct 14, 2005 at 04:20:24PM +0200, Wolfgang Jeltsch
wrote a message of 23 lines which said: By the way, it should be possible to handle regular expressions in an Haskell-like way.
If you like so, but as one more possibility, not as the only way.
I always couldn't understand why one has to write regular expressions as strings
Because the language used inside these strings is standard, multi-language, widely used and documented?
10,000 lemmings can't be wrong? Using strings for regexps is a disaster. Not even the syntax of such regexps is checked at compile time. (This was part of the point of my April 1st "joke" by the way). The language would certainly benefit from the inclusion of regexps the way Wolfgang suggested, but if we really need the short-form syntax (I'm not convinced; it seems pretty much a write only notation), then do it by having special syntax as a shorthand for the proper Haskell. Since Unicode is increasingly adopted, we could just use «regexp» and specify some rules to convert the regexp into Haskell, as "..." is meant to stand for '.':'.':'.':[]. Jón -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk

On Fri, Oct 14, 2005 at 03:34:33PM +0100,
Jon Fairbairn
Because the language used inside these strings is standard, multi-language, widely used and documented?
10,000 lemmings can't be wrong?
Right, disregard ASCII and specify the lexemes of Haskell 2 in a new encoding scheme, much better than ASCII :-)
Not even the syntax of such regexps is checked at compile time.
Of course, from the compiler's PoV, they are just strings. May be a new form of strings, like in Perl, to show that this is a regexp?
Since Unicode is increasingly adopted, we could just use «regexp»
The Unicode standard for regexps, UTR #18 (http://www.unicode.org/reports/tr18/) uses the very same standard syntax that you criticize.

On 2005-10-14 at 16:56+0200 Stephane Bortzmeyer wrote:
On Fri, Oct 14, 2005 at 03:34:33PM +0100, Jon Fairbairn
wrote: Because the language used inside these strings is standard, multi-language, widely used and documented?
10,000 lemmings can't be wrong?
Right, disregard ASCII and specify the lexemes of Haskell 2 in a new encoding scheme, much better than ASCII :-)
Haskell 98 isn't ASCII, but Unicode (Report, 2.1), current compiler inadequacies notwithstanding. So we've done that already. (And incidentally I'm on record as having argued for ASCII rather than Unicode for Haskell source).
Not even the syntax of such regexps is checked at compile time.
Of course, from the compiler's PoV, they are just strings.
That's what I'm complaining about.
May be a new form of strings, like in Perl, to show that this is a regexp?
That's what I'm suggesting.
Since Unicode is increasingly adopted, we could just use «regexp»
The Unicode standard for regexps, UTR #18 (http://www.unicode.org/reports/tr18/) uses the very same standard syntax that you criticize.
So if we must have a short-form syntax, perhaps we should use that one as I already intimated. However, as I read that report, it's a standard way of adapting (any, standard or otherwise) REs to handle unicode, not a standardisation of regexps per se. Specifically Note: This is only a sample syntax for the purposes of examples in this document. (Regular expression syntax varies widely: the issues discussed here would need to be adapted to the syntax of the particular implementation. [...] So it's not a Unicode standard for the syntax of regexps. Jón -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk

On Fri, Oct 14, 2005 at 03:34:33PM +0100, Jon Fairbairn wrote:
On 2005-10-14 at 16:25+0200 Stephane Bortzmeyer wrote:
On Fri, Oct 14, 2005 at 04:20:24PM +0200, Wolfgang Jeltsch
wrote a message of 23 lines which said: By the way, it should be possible to handle regular expressions in an Haskell-like way.
If you like so, but as one more possibility, not as the only way.
I always couldn't understand why one has to write regular expressions as strings
Because the language used inside these strings is standard, multi-language, widely used and documented?
10,000 lemmings can't be wrong?
Using strings for regexps is a disaster. Not even the syntax of such regexps is checked at compile time. (This was part of the point of my April 1st "joke" by the way).
The language would certainly benefit from the inclusion of regexps the way Wolfgang suggested, but if we really need the short-form syntax (I'm not convinced; it seems pretty much a write only notation), then do it by having special syntax as a shorthand for the proper Haskell.
Since Unicode is increasingly adopted, we could just use «regexp» and specify some rules to convert the regexp into Haskell, as "..." is meant to stand for '.':'.':'.':[].
my perl-like regexps for haskell package adds (=~) that works very similarly to the perl operator, but is much more flexible since we have so many types to work with rather than just scalar or list context. in any case it uses a typeclass for regexs and what sort of thing they work on. so you could do foo =~ ".*foo$" let regex = mkRegex ".*foo$" -- so the building of the regex will be shared foo =~ regex o foo =~ (my fancy regex domain specific language) I should cabalize it... John -- John Meacham - ⑆repetae.net⑆john⑈

Am Freitag, 14. Oktober 2005 16:25 schrieben Sie:
On Fri, Oct 14, 2005 at 04:20:24PM +0200, Wolfgang Jeltsch
wrote: I always couldn't understand why one has to write regular expressions as strings
Because the language used inside these strings is standard, multi-language, widely used and documented?
Well, in my opinion, the standard regexp syntax is rather awkward so that diverging from the standard might be a good thing. However, my proposal was not about introducing a new syntax. If I had just used a different syntax, I had used strings for representing regexps as well. But my main point is to not use strings for representing regexps at runtime because this means that parsing is done at runtime. This might result in a loss of efficiency. In addition, no syntax checks can be done at runtime. The situation gets worse if you try to manipulate regular expressions. Now lets consider using an algebraic datatype for regexps: data RegExp = Empty | Single Char | RegExp :+: RegExp | RegExp :|: RegExpt | Iter RegExp Manipulating regular expressions now becomes easy and safe – you are just not able to create "syntactically incorrect regular expressions" since during runtime you don't deal with syntax at all. In addition, the usage of a special datatype can provide more flexibility. Representing regexps as strings means that regexps can only denote sets of strings. In contrast, the above datatype could easily be extendend to allow arbitrary lists instead of just strings: data RegExp token = Empty | Single token | RegExp token :+: RegExp token | ... If you really need a Perl-like syntax for regular expressions, the strings representing the regexps should be parsed at compile-time and transformed into expressions of a special regexp datatype like the one above. However, I don't like the idea of extending the language with a special regexp syntax. Why handle a specific, albeit common, syntax for a special case of regexps (string-only) special? What about other things than regexps? Should they also get a language extension? I'd say that the better way would be to use Template Haskell for this purpose: myRegExp = $(regExp "[a-z0-9]") This way, special syntaxes are not hard-wired into the language but can be activated by importing a corresponding module. Best wishes, Wolfgang

Hi folks, Inspired by Ralf's post, I thought I'd just GADTize a dependently typed program I wrote in 2001. Wolfgang Jeltsch wrote:
Now lets consider using an algebraic datatype for regexps:
data RegExp = Empty | Single Char | RegExp :+: RegExp | RegExp :|: RegExpt | Iter RegExp
Manipulating regular expressions now becomes easy and safe – you are just not able to create "syntactically incorrect regular expressions" since during runtime you don't deal with syntax at all.
A fancier variation on the same theme...
data RegExp :: * -> * -> * where Zero :: RegExp tok Empty One :: RegExp tok () Check :: (tok -> Bool) -> RegExp tok tok Plus :: RegExp tok a -> RegExp tok b -> RegExp tok (Either a b) Mult :: RegExp tok a -> RegExp tok b -> RegExp tok (a, b) Star :: RegExp tok a -> RegExp tok [a]
data Empty
The intuition is that a RegExp tok output is a regular expression explaining how to parse a list of tok as an output. Here, Zero is the regexp which does not accept anything, One accepts just the empty string, Plus is choice and Mult is sequential composition; Check lets you decide whether you like a single token. Regular expressions may be seen as an extended language of polynomials with tokens for variables; this parser works by repeated application of the remainder theorem.
parse :: RegExp tok x -> [tok] -> Maybe x parse r [] = empty r parse r (t : ts) = case divide t r of Div q f -> return f `ap` parse q ts
Example *RegExp> parse (Star (Mult (Star (Check (== 'a'))) (Star (Check (== 'b'))))) "abaabaaabbbb" Just [("a","b"),("aa","b"),("aaa","bbbb")] The 'remainder' explains if a regular expression accepts the empty string, and if so, how. The Star case is a convenient underapproximation, ruling out repeated empty values.
empty :: RegExp tok a -> Maybe a empty Zero = mzero empty One = return () empty (Check _) = mzero empty (Plus r1 r2) = (return Left `ap` empty r1) `mplus` (return Right `ap` empty r2) empty (Mult r1 r2) = return (,) `ap` empty r1 `ap` empty r2 empty (Star _) = return []
The 'quotient' explains how to parse the tail of the list, and how to recover the meaning of the whole list from the meaning of the tail.
data Division tok x = forall y. Div (RegExp tok y) (y -> x)
Here's how it's done. I didn't expect to need scoped type variables, but I did...
divide :: tok -> RegExp tok x -> Division tok x divide t Zero = Div Zero naughtE divide t One = Div Zero naughtE divide t (Check p) | p t = Div One (const t) | otherwise = Div Zero naughtE divide t (Plus (r1 :: RegExp tok a) (r2 :: RegExp tok b)) = case (divide t r1, divide t r2) of (Div (q1 :: RegExp tok a') (f1 :: a' -> a), Div (q2 :: RegExp tok b') (f2 :: b' -> b)) -> Div (Plus q1 q2) (f1 +++ f2) divide t (Mult r1 r2) = case (empty r1, divide t r1, divide t r2) of (Nothing, Div q1 f1, _) -> Div (Mult q1 r2) (f1 *** id) (Just x1, Div q1 f1, Div q2 f2) -> Div (Plus (Mult q1 r2) q2) (either (f1 *** id) (((,) x1) . f2)) divide t (Star r) = case (divide t r) of Div q f -> Div (Mult q (Star r)) (\ (y, xs) -> (f y : xs))
Bureaucracy.
(***) :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) (f *** g) (a, c) = (f a, g c)
(+++) :: (a -> b) -> (c -> d) -> Either a c -> Either b d (f +++ g) (Left a) = Left (f a) (f +++ g) (Right c) = Right (g c)
naughtE :: Empty -> x naughtE = undefined
It's not the most efficient parser in the world (doing some algebraic simplification on the fly wouldn't hurt), but it shows the sort of stuff you can do. Have fun Conor

Hello Conor, Saturday, October 15, 2005, 4:47:02 PM, you wrote:
Now lets consider using an algebraic datatype for regexps:
data RegExp = Empty | Single Char | RegExp :+: RegExp | RegExp :|: RegExpt | Iter RegExp
btw, a year ago i written RE processing library, which used Parsec both to parse and compile regexpr itself and to parse input string according to compiled regexpr. i think, this have no practical meaning, but may be included in parsec library as intersting example of its usage :) unluckily, i dont debugged it and so don't send it to parsec author -- Best regards, Bulat mailto:bulatz@HotPOP.com

Very interesting Conor. Do you know Xi et al's APLAS'03 paper? (Hongwei, I'm not sure whether you're on this list). Xi et al. use GRDTs (aka GADTs aka first-class phantom types) to represent XML documents. There're may be some connections between what you're doing and Xi et al's work. I believe that there's an awful lot you can do with GADTs (in the context of regular expressions). But there're two things you can't accomplish: semantic subtyping and regular expression pattern matching a la XDuce/CDuce. Unless somebody out there proves me wrong. Martin Hi folks, Inspired by Ralf's post, I thought I'd just GADTize a dependently typed=20 program I wrote in 2001. Wolfgang Jeltsch wrote:
Now lets consider using an algebraic datatype for regexps:
data RegExp =3D Empty | Single Char | RegExp :+: RegExp | RegExp :|: RegExpt | Ite= r RegExp
Manipulating regular expressions now becomes easy and safe =E2=80=93 you= are just not=20 able to create "syntactically incorrect regular expressions" since durin= g=20 runtime you don't deal with syntax at all. =20
A fancier variation on the same theme...
data RegExp :: * -> * -> * where Zero :: RegExp tok Empty One :: RegExp tok () Check :: (tok -> Bool) -> RegExp tok tok Plus :: RegExp tok a -> RegExp tok b -> RegExp tok (Either a b) Mult :: RegExp tok a -> RegExp tok b -> RegExp tok (a, b) Star :: RegExp tok a -> RegExp tok [a]
data Empty
The intuition is that a RegExp tok output is a regular expression=20 explaining how to parse a list of tok as an output. Here, Zero is the=20 regexp which does not accept anything, One accepts just the empty=20 string, Plus is choice and Mult is sequential composition; Check lets=20 you decide whether you like a single token. Regular expressions may be seen as an extended language of polynomials=20 with tokens for variables; this parser works by repeated application of=20 the remainder theorem.
parse :: RegExp tok x -> [tok] -> Maybe x parse r [] =3D empty r parse r (t : ts) =3D case divide t r of Div q f -> return f `ap` parse q ts
Example *RegExp> parse (Star (Mult (Star (Check (=3D=3D 'a'))) (Star (Check (=3D=3D= =20 'b'))))) "abaabaaabbbb" Just [("a","b"),("aa","b"),("aaa","bbbb")] The 'remainder' explains if a regular expression accepts the empty=20 string, and if so, how. The Star case is a convenient=20 underapproximation, ruling out repeated empty values. =20
empty :: RegExp tok a -> Maybe a empty Zero =3D mzero empty One =3D return () empty (Check _) =3D mzero empty (Plus r1 r2) =3D (return Left `ap` empty r1) `mplus` (return Right `ap` empty r2) empty (Mult r1 r2) =3D return (,) `ap` empty r1 `ap` empty r2 empty (Star _) =3D return []
The 'quotient' explains how to parse the tail of the list, and how to=20 recover the meaning of the whole list from the meaning of the tail.
data Division tok x =3D forall y. Div (RegExp tok y) (y -> x)
Here's how it's done. I didn't expect to need scoped type variables, but=20 I did...
divide :: tok -> RegExp tok x -> Division tok x divide t Zero =3D Div Zero naughtE divide t One =3D Div Zero naughtE divide t (Check p) | p t =3D Div One (const t) | otherwise =3D Div Zero naughtE divide t (Plus (r1 :: RegExp tok a) (r2 :: RegExp tok b)) =3D case (divide t r1, divide t r2) of (Div (q1 :: RegExp tok a') (f1 :: a' -> a), Div (q2 :: RegExp tok b') (f2 :: b' -> b)) -> Div (Plus q1 q2) (f1 +++ f2) divide t (Mult r1 r2) =3D case (empty r1, divide t r1, divide t r2) of (Nothing, Div q1 f1, _) -> Div (Mult q1 r2) (f1 *** id) (Just x1, Div q1 f1, Div q2 f2) -> Div (Plus (Mult q1 r2) q2) (either (f1 *** id) (((,) x1) . f2)) divide t (Star r) =3D case (divide t r) of Div q f -> Div (Mult q (Star r)) (\ (y, xs) -> (f y : xs))
Bureaucracy.
(***) :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) (f *** g) (a, c) =3D (f a, g c)
(+++) :: (a -> b) -> (c -> d) -> Either a c -> Either b d (f +++ g) (Left a) =3D Left (f a) (f +++ g) (Right c) =3D Right (g c)
naughtE :: Empty -> x naughtE =3D undefined
It's not the most efficient parser in the world (doing some algebraic=20 simplification on the fly wouldn't hurt), but it shows the sort of stuff=20 you can do. Have fun Conor _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Oct 14, 2005 at 04:20:24PM +0200,
Wolfgang Jeltsch
alpha = ('A' `to` 'Z') ||| ('a' `to` 'z')
If you intend to seriously specify a new language for regexps, please consider Unicode. There are more letters than A to Z...

Am Freitag, 14. Oktober 2005 16:26 schrieben Sie:
On Fri, Oct 14, 2005 at 04:20:24PM +0200, Wolfgang Jeltsch
wrote a message of 23 lines which said:
alpha = ('A' `to` 'Z') ||| ('a' `to` 'z')
If you intend to seriously specify a new language for regexps, please consider Unicode. There are more letters than A to Z...
Yes, of course. This was just an example. alpha should probably be predefined. Best wishes, Wolfgang

Regexps and XML are, IMHO, also "must haves".
By the way, it should be possible to handle regular expressions in an Haskell-like way.
Harp? :-) http://www.cs.chalmers.se/~d00nibro/harp /Niklas

On 2005-10-13, Stephane Bortzmeyer
On Thu, Oct 13, 2005 at 11:29:57AM +0000, Robin Green
wrote a message of 22 lines which said: ... and, in the case of the Standard Prelude section, or equivalent, a specification of well-understood functions that the spec authors agree "should" be provided in all implementations. ... (It is, however, one of the "must haves" for Haskell to be considered for use in production systems.)
Regexps and XML are, IMHO, also "must haves".
Bah, simple libraries. They don't have to be part of the Standard Prelude. (See http://haskell.org/hawiki/RegexSyntax , BTW, which cantains some DWIM operators overloaded on return type -- perl's scalar/list distinction on steroids.) -- Aaron Denney -><-

On Fri, Oct 14, 2005 at 07:15:11PM +0000, Aaron Denney wrote:
On 2005-10-13, Stephane Bortzmeyer
wrote: On Thu, Oct 13, 2005 at 11:29:57AM +0000, Robin Green
wrote a message of 22 lines which said: ... and, in the case of the Standard Prelude section, or equivalent, a specification of well-understood functions that the spec authors agree "should" be provided in all implementations. ... (It is, however, one of the "must haves" for Haskell to be considered for use in production systems.)
Regexps and XML are, IMHO, also "must haves".
Bah, simple libraries. They don't have to be part of the Standard Prelude.
I completely agree. I'd rather decrease the number of libraries defined in the language itself and decouple library standardization from the definition of the language standard. Libraries can much more easily be developed and improved. -- David Roundy

David Roundy
Bah, simple libraries. They don't have to be part of the Standard Prelude.
I completely agree. I'd rather decrease the number of libraries defined in the language itself and decouple library standardization from the definition of the language standard. Libraries can much more easily be developed and improved.
I'd vote for moving map, null and lookup from Prelude to an explicit List import (like insert already is). They tend to be used by collections (Data.Set, Map etc), which complicates imports or requires unnecessary qualification. Alternatively, as (List.)map and null are very common, use different names for other collections (fmap? isEmpty?). As a general rule, I think libraries shouldn't overload names imported implicitly from the Prelude. (I know it is fashionable to qualify everything this week, but I prefer to be able to use unqualified names occasionally as well). -k -- If I haven't seen further, it is by standing in the footprints of giants

On 15/10/05, Ketil Malde
David Roundy
writes: Bah, simple libraries. They don't have to be part of the Standard Prelude.
I completely agree. I'd rather decrease the number of libraries defined in the language itself and decouple library standardization from the definition of the language standard. Libraries can much more easily be developed and improved.
I'd vote for moving map, null and lookup from Prelude to an explicit List import (like insert already is). They tend to be used by collections (Data.Set, Map etc), which complicates imports or requires unnecessary qualification.
Alternatively, as (List.)map and null are very common, use different names for other collections (fmap? isEmpty?).
As a general rule, I think libraries shouldn't overload names imported implicitly from the Prelude. (I know it is fashionable to qualify everything this week, but I prefer to be able to use unqualified names occasionally as well).
-k -- If I haven't seen further, it is by standing in the footprints of giants
Or fix the "Set is not an instance of Functor" problem and then rename fmap to map. :) John Hughes' proposal works, though I don't know if I'd like all the wft's cluttering up my class contexts. I've been thinking of some other ways to solve the problem by extending the kind system (as the problem is that the kind of the type parameter to Set should not really be *, but a subkind thereof consisting of the types satisfying Ord). It looks like this approach should work, but I either need to do more reading or more talking to people knowledgeable about type theory, and the existing implementations in order to completely formalise it. I agree somewhat about the qualified names, but I think in a lot of cases, when things are called the same thing, it is because they are doing the same thing, and so there should be a typeclass for them. - Cale

Ketil Malde
David Roundy
writes: Bah, simple libraries. They don't have to be part of the Standard Prelude.
I completely agree. I'd rather decrease the number of libraries defined in the language itself and decouple library standardization from the definition of the language standard. Libraries can much more easily be developed and improved.
I'd vote for moving map, null and lookup from Prelude to an explicit List import (like insert already is).
I hope we decide to reduce the size of the Prelude to the minimum possible. Most of what is currently in there can be more conveniently dumped into libraries. Then we could have one or more standard aggregations of useful libraries, e.g. BeginnersPrelude which has no classes, IntermediatePrelude, and AdvancedPrelude. Regards, Malcolm

On 10/13/05, Simon Marlow
On 12 October 2005 23:50, Sebastian Sylvan wrote:
(I'm specifically interested in seeing SPJ's records proposal included, and a new module system).
Highly unlikely, IMHO. A new revision of the Haskell standard is not the place for testing new research, rather it's a clear specification of existing well-understood language features.
I can certainly understand this point of view. I am (as primarily a user and not a language designer) perhaps too eager to get my hands on cool new stuff :-)
If you want a new record system, or a new module system, now is the time to start designing and implementing them ready for the next standardisation process.
Okay then. Consider this my contribution to the discussion. First of all I would like to urge the people who do end up working on this to seriously consider replacing H98's records system. I may be wrong but the impression I get is that enough people dislike the current system enough to warrant a replacement. And to me it seems to be a pretty much "slam-dunk" case that the proposal is *a lot* better than what we current have. On the module system. You may consider this a proposal. There have been discussions on this mailing lists about it but let me recap the main gist of it. Conservatively extend the current ghc hierarchical module system by allowing you to re-export modules "qualified". So you could write module GTK (..., qualified module GTK.Button as Button, ...) where Then the user could just import GTK and get all of the contents of GTK.Button imported qualifed as Button automatically. This allow libraries written using the current hierarchcical system to work without any changes, while new libraries can use the new feature (I'm guessing GTK2HS would benefit a lot from this, getting rid of all the ugly "buttonNew"-style functions). /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Hello Sebastian, Thursday, October 13, 2005, 4:09:55 PM, you wrote:
(I'm specifically interested in seeing SPJ's records proposal included, and a new module system).
SS> First of all I would like to urge the people who do end up working on SS> this to seriously consider replacing H98's records system. I may be yes, it is a common viewpoint, afaik. the only problem is what this new record system was never really implemented, partially because it is not backward-compatible with H98, partially because Simons are not very like such syntax sugar extensions, they prefer "real semantic beasts" :) so, this proposal is a bit out of luck :))) -- Best regards, Bulat mailto:bulatz@HotPOP.com

On Thu, Oct 13, 2005 at 02:09:55PM +0200, Sebastian Sylvan wrote:
Okay then. Consider this my contribution to the discussion. First of all I would like to urge the people who do end up working on this to seriously consider replacing H98's records system. I may be wrong but the impression I get is that enough people dislike the current system enough to warrant a replacement. And to me it seems to be a pretty much "slam-dunk" case that the proposal is *a lot* better than what we current have.
How about a standard HList-style library specified in the report? then we get fancy records without having to change the language. Then we could work on syntatic sugar to make HList records as easy to use as built in ones. John -- John Meacham - ⑆repetae.net⑆john⑈

On Thu, 13 Oct 2005, Simon Marlow wrote:
On 12 October 2005 23:50, Sebastian Sylvan wrote:
(I'm specifically interested in seeing SPJ's records proposal included, and a new module system).
Highly unlikely, IMHO. A new revision of the Haskell standard is not the place for testing new research, rather it's a clear specification of existing well-understood language features.
In that context, how well-understood is the combination of impredicative types via boxy types and a proper existential quantifier at the moment? It's certainly something that has many uses in an industrial context. -- flippa@flippac.org Society does not owe people jobs. Society owes it to itself to find people jobs.

Hello Simon, Thursday, October 13, 2005, 1:42:24 PM, you wrote:
(I'm specifically interested in seeing SPJ's records proposal included, and a new module system).
SM> Highly unlikely, IMHO. A new revision of the Haskell standard is not SM> the place for testing new research, rather it's a clear specification of SM> existing well-understood language features. +1 :) but we may add them to standard definition as "Possible extensions" appendix. moreover, if some already implemented language extensions (f.e., Template Haskell) are not good enough to be included in standard itself, it may be also included here - just to have one place where many language extensions are described. and also a source for new features which MAY be included in Haskell2 -- Best regards, Bulat mailto:bulatz@HotPOP.com

On Thu, Oct 13, 2005 at 10:42:24AM +0100, Simon Marlow wrote:
On 12 October 2005 23:50, Sebastian Sylvan wrote:
(I'm specifically interested in seeing SPJ's records proposal included, and a new module system).
Highly unlikely, IMHO. A new revision of the Haskell standard is not the place for testing new research, rather it's a clear specification of existing well-understood language features.
Indeed. I'd love to have a new Haskell 06 that adds just a carefully (and conservatively) selected subset of ghc's extensions, if that meant that my code would also run on hugs and jhc. Like everyone else, there are *some* experimental features I'd love to see go in, most particularly John Meacham's class aliases proposal, which seems like (perhaps from my naive perspective) a moderately conservative change that opens up huge possibilities for improved libraries (which could then be developed to the new standard). -- David Roundy
participants (17)
-
Aaron Denney
-
Bulat Ziganshin
-
Cale Gibbard
-
Conor McBride
-
David Roundy
-
John Meacham
-
Jon Fairbairn
-
Ketil Malde
-
Malcolm Wallace
-
Martin Sulzmann
-
Niklas Broberg
-
Philippa Cowderoy
-
Robin Green
-
Sebastian Sylvan
-
Simon Marlow
-
Stephane Bortzmeyer
-
Wolfgang Jeltsch