
On 30 January 2006 18:20, Isaac Jones wrote:
Can someone be sure to capture the pros, cons, and relationship to the !-patterns proposal as a ticket / wiki page?
I've been swayed by the arguments put forward by the ~-proponents, so I'm not going to champion the removal of ~ any more. We must find *something* to throw away though! :-) Cheers, Simon

On 1/31/06, Simon Marlow
I've been swayed by the arguments put forward by the ~-proponents, so I'm not going to champion the removal of ~ any more.
We must find *something* to throw away though! :-)
I still like the idea of splitting Haskell' into Haskell'-core and
Haskell'-lazy, and moving ~ and ! patterns into Haskell'-lazy.
--
Taral

On Tue, Jan 31, 2006 at 12:26:16PM -0600, Taral wrote:
On 1/31/06, Simon Marlow
wrote: I've been swayed by the arguments put forward by the ~-proponents, so I'm not going to champion the removal of ~ any more.
We must find *something* to throw away though! :-)
I still like the idea of splitting Haskell' into Haskell'-core and Haskell'-lazy, and moving ~ and ! patterns into Haskell'-lazy.
I'd flip the names though. since lazy programers are the ones that will create implementations that only conform to the lesser standard :) John -- John Meacham - ⑆repetae.net⑆john⑈

Taral
On 1/31/06, Simon Marlow
wrote: I've been swayed by the arguments put forward by the ~-proponents, so I'm not going to champion the removal of ~ any more.
We must find *something* to throw away though! :-)
I still like the idea of splitting Haskell' into Haskell'-core and Haskell'-lazy, and moving ~ and ! patterns into Haskell'-lazy.
The Haskell'98 Report already uses an informal notion of a "core" language, into which other syntactic constructs are translated. I think in Haskell-prime we ought to define this core precisely and formally. One can even imagine someone developing a pure H-core compiler, with the fuller language implemented as a pre-processor over the top! (I know at least one person who would prefer to write programs in core rather than Haskell'98...) Regards, Malcolm

On Feb 1, 2006, at 5:12 AM, Malcolm Wallace wrote:
Taral
writes: On 1/31/06, Simon Marlow
wrote: I've been swayed by the arguments put forward by the ~- proponents, so I'm not going to champion the removal of ~ any more.
We must find *something* to throw away though! :-)
I still like the idea of splitting Haskell' into Haskell'-core and Haskell'-lazy, and moving ~ and ! patterns into Haskell'-lazy.
The Haskell'98 Report already uses an informal notion of a "core" language, into which other syntactic constructs are translated.
I think in Haskell-prime we ought to define this core precisely and formally.
I'd like to second this.
One can even imagine someone developing a pure H-core compiler, with the fuller language implemented as a pre-processor over the top! (I know at least one person who would prefer to write programs in core rather than Haskell'98...)
In light of the recent post on optimizing core, it seems like this might be a very good way to allow people to optimize their inner loops without having to trick their favorite compiler to do the optimizations they want. Additionally, a standard for core would allow a new level of tool interoperability. Haskell front ends and backends could be cleanly separated along a well-defined border. DrIFT and Haddock and others as well could benefit. Happy could generate core directly.... anyway you get the idea. Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

On Wed, 1 Feb 2006, Robert Dockins wrote:
One can even imagine someone developing a pure H-core compiler, with the fuller language implemented as a pre-processor over the top! (I know at least one person who would prefer to write programs in core rather than Haskell'98...)
In light of the recent post on optimizing core, it seems like this might be a very good way to allow people to optimize their inner loops without having to trick their favorite compiler to do the optimizations they want.
Additionally, a standard for core would allow a new level of tool interoperability. Haskell front ends and backends could be cleanly separated along a well-defined border. DrIFT and Haddock and others as well could benefit. Happy could generate core directly.... anyway you get the idea.
I'm not convinced on that. You'd have to specify a surprisingly low-level language to allow that to the extent the real optimisation nuts want, and that's something that really should be beyond the scope of the standard. Even if we stick with something simple it's extremely likely that we'd end up specifying a dictionary-passing implementation of typeclasses - something that seriously disadvantages some valuable extensions and implementation techniques (it'd really mess up JHC from what I can tell, for example). -- flippa@flippac.org A problem that's all in your head is still a problem. Brain damage is but one form of mind damage.

On Wed, Feb 01, 2006 at 02:51:08PM +0000, Philippa Cowderoy wrote:
I'm not convinced on that. You'd have to specify a surprisingly low-level language to allow that to the extent the real optimisation nuts want, and that's something that really should be beyond the scope of the standard. Even if we stick with something simple it's extremely likely that we'd end up specifying a dictionary-passing implementation of typeclasses - something that seriously disadvantages some valuable extensions and implementation techniques (it'd really mess up JHC from what I can tell, for example).
I am thinking we don't specify any particular translation scheme. just a sudset of the language that is considered 'core' that every haskell program could _potentially_ be reduced to. whether compilers actually take the 'example' route given in the report is a different manner. for example jhc might leave in typeclasses because they can't be desugared into pure haskell without GADTs. I wouldn't want to see a dictionary passing implementations of type-classes prescribed either :) John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham
On Wed, Feb 01, 2006 at 02:51:08PM +0000, Philippa Cowderoy wrote:
specifying a dictionary-passing implementation of typeclasses -
I am thinking we don't specify any particular translation scheme. just a sudset of the language that is considered 'core' that every haskell program could _potentially_ be reduced to.
There is a potential confusion here between the H-core language as used in the Haskell'98 report, and ghc's current external-core language. The former contains classes, and the latter does not. Ghc-core has type-lambdas, but H-core does not. Ghc-core has unboxed values, H-core does not. The main conceptual difference is that H-core aims merely for simpler expression of common syntactic constructs, whereas ghc-core aims for low-level optimisability. H-core should be programmer-usable, whilst ghc-core is intended for automated tools to use. Regards, Malcolm

Malcolm Wallace wrote:
The main conceptual difference is that H-core aims merely for simpler expression of common syntactic constructs, whereas ghc-core aims for low-level optimisability.
I think the fundamental difference is that the translation to GHC core is type-directed, while the translation to H98 core isn't. That means you can specify typecheckHaskell as typecheckCore.desugar if you use H98 core but not if you use GHC core, which I think is a major point in the former's favor as far as language specification goes. -- Ben

On Thu, Feb 02, 2006 at 11:19:09AM +0000, Malcolm Wallace wrote:
There is a potential confusion here between the H-core language as used in the Haskell'98 report, and ghc's current external-core language. The former contains classes, and the latter does not. Ghc-core has type-lambdas, but H-core does not. Ghc-core has unboxed values, H-core does not.
Yeah, core is a pretty overloaded term in haskell. Here I was definitly thinking of Haskell Core, as in a subset of haskell' that is still pure haskell and will compile via any haskell' compiler. I try to get in the habit of alway saying the full haskell core, ghc core, or jhc core (is there an nhc core?) but sometimes get sloppy. John -- John Meacham - ⑆repetae.net⑆john⑈

john:
On Thu, Feb 02, 2006 at 11:19:09AM +0000, Malcolm Wallace wrote:
There is a potential confusion here between the H-core language as used in the Haskell'98 report, and ghc's current external-core language. The former contains classes, and the latter does not. Ghc-core has type-lambdas, but H-core does not. Ghc-core has unboxed values, H-core does not.
Yeah, core is a pretty overloaded term in haskell. Here I was definitly thinking of Haskell Core, as in a subset of haskell' that is still pure haskell and will compile via any haskell' compiler. I try to get in the habit of alway saying the full haskell core, ghc core, or jhc core (is there an nhc core?) but sometimes get sloppy.
Oh, I use "Core" for GHC's IR, and "the Haskell core" for the lang in the report. -- Don

habit of alway saying the full haskell core, ghc core, or jhc core (is there an nhc core?) but sometimes get sloppy.
Yhc ~= nhc, and Yhc has a Core: http://www.haskell.org/haskellwiki/Yhc/API/Core http://yhc06.blogspot.com/2005/12/yhc-core.html Thanks Neil

Just for larks, here is a side by side of the various compilers core for the example on that page: Haskell:
module FibMain where
main xs = pam daeh xs
daeh (x:xs) = x
pam f [] = [] pam f (x:xs) = f x : pam f xs
Yhc:
FibMain.pam v220 v221 = case v221 of Prelude.[] -> (Prelude.[]) Prelude.: v222 v223 -> (Prelude.: (YHC.Internal._apply1 v220 v222) (FibMain.pam v220 v223))
FibMain.daeh v224 = case v224 of Prelude.: v225 v226 -> v225 _ -> (Prelude.error (LAMBDA228))
LAMBDA228 = (prim_STRING "FibMain: Pattern match failure in function at 7:1-7:15.")
FibMain.main v227 = (FibMain.pam FibMain.daeh v227)
Jhc: (unicodey!)
FibMain.main = ΛFibMain.v22.λFibMain.1_xs∷[[FibMain.v22]].(let x9282∷[FibMain.v22] → FibMain.v22 = λx9284∷[FibMain.v22].(case x9284 of (x9286∷FibMain.v22):(x9288∷[FibMain.v22]) → x9286; Prelude.[] → <⊥:test/fibmain.hs:5:13: Unmatched pattern∷FibMain.v22>;); x9280∷⋆ = [FibMain.v22]; in FibMain.pam x9280 FibMain.v22 x9282 FibMain.1_xs) FibMain.pam = ΛFibMain.v5.ΛFibMain.v10.λx9296∷FibMain.v5 → FibMain.v10.λx9298∷[FibMain.v5].(case x9298 of (x9300∷FibMain.v5):(x9302∷[FibMain.v5]) → let x9316∷[FibMain.v10] = FibMain.pam FibMain.v5 FibMain.v10 x9296 x9302; x9314∷FibMain.v10 = x9296 x9300; in x9314:x9316; Prelude.[] → "";) FibMain.daeh = ΛFibMain.v15.λx9284∷[FibMain.v15].(case x9284 of (x9286∷FibMain.v15):(x9288∷[FibMain.v15]) → x9286; Prelude.[] → <⊥:test/fibmain.hs:5:13: Unmatched pattern∷FibMain.v15>;)
ghc:
daeh :: %forall a . [] a -> a = \ @ a (ds::[] a) -> %case (a) ds %of (wild::[] a) {[] -> GHC.Err.patError @ a ("test/fibmain.hs:5:0-14|function daeh"::Addr#); : (x::a) (xs::[] a) -> x}; pam :: %forall a a1 . (a -> a1) -> [] a -> [] a1 = \ @ a @ a1 -> %let %rec {pam1 :: (a -> a1) -> [] a -> [] a1 = \ (f::a -> a1) (ds::[] a) -> %case (([] a1)) ds %of (wild::[] a) {[] -> [] @ a1; : (x::a) (xs::[] a) -> : @ a1 (f x) (pam1 f xs)}} %in pam1; main :: %forall a . [] ([] a) -> [] a = \ @ a (xs::[] ([] a)) -> FibMain.pam @ ([] a) @ a (FibMain.daeh @ a) xs;
I don't think a common compiler level core is forthcoming :) John -- John Meacham - ⑆repetae.net⑆john⑈

On Wed, Feb 01, 2006 at 09:40:20AM -0500, Robert Dockins wrote:
Additionally, a standard for core would allow a new level of tool interoperability. Haskell front ends and backends could be cleanly separated along a well-defined border. DrIFT and Haddock and others as well could benefit. Happy could generate core directly.... anyway you get the idea.
Yeah, i have always wanted ghc to allow one to inject a preprocessor (midprocessor?) after desugaring but while it is still haskell. it would allow preprocessors to not worry about a lot of the front-end extensions and let the compiler have first crack at reporting type errors to the user before they are obfcusiated by any preproccesing. I think a formal definition of core-haskell would be an excellent thing. John -- John Meacham - ⑆repetae.net⑆john⑈

On 31/01/2006, at 9:31 PM, Simon Marlow wrote:
We must find *something* to throw away though! :-)
One small issue that I'd love to see thrown away is the special handling the the unary "-" operator in Haskell 98. It's been described as "embarrassing", "ugly", and even "inconvenient" I, for one, find myself creating sections of the form `+ (-x)` all the time, and it feels wrong. The proposal would be to remove the unary "-" altogether, and, instead, extend the lexical syntax of numeric constant to allow "+" and "-" prefix. Further, we would need to extend the prelude with an additional definition: negate :: Num a -> Num a negate x = 0 - x Pros: 1. Removes an embarrassing special case from the grammar. 2. Makes the section `- x` work as expected. 3. Expressions such as "-1" would not require paranthesizing. 4. Expressions such as "-1" would be permitted in k-patterns even if n+k patterns end up being thrown out. 5. You can say "negate $ 1 + 2" if you don't like parentheses. 6. The precedent of making an operator symbol behave differently when not separated from its argument by a space has already been made by the "." operator. Cons: 1. Expressions of the form "-x" (where "x" is not a constant) need to be rewritten as "negate x" (which, to me, looks much cleaner anyway, especially as, more often than not, "x" ends up being a complex expression anyway! 2. Possible confusion to the beginners (can write "-1" but cannot write "-x".) However, I think that the strange behaviour of sections and the need for parentheses around "-1" is already confusing enough to beginners, and therefore this chance would actually make Haskell *easier* to learn, not harder. "negate x" looks so much more like ordinary Haskell code! What do people think? - Pat.

On Wed, Feb 01, 2006 at 11:32:28AM +1100, Patryk Zadarnowski wrote:
On 31/01/2006, at 9:31 PM, Simon Marlow wrote:
We must find *something* to throw away though! :-)
One small issue that I'd love to see thrown away is the special handling the the unary "-" operator in Haskell 98. It's been described as "embarrassing", "ugly", and even "inconvenient" I, for one, find myself creating sections of the form `+ (-x)` all the time, and it feels wrong. What do people think?
yeah, I really want to see this change too. I think it would be a whole lot nicer. plus, a syntax highlighting editor would be able to determine the difference between - used as an operator and - used as part of a number. John -- John Meacham - ⑆repetae.net⑆john⑈

On Tue, 2006-01-31 at 16:47 -0800, John Meacham wrote:
On Wed, Feb 01, 2006 at 11:32:28AM +1100, Patryk Zadarnowski wrote:
On 31/01/2006, at 9:31 PM, Simon Marlow wrote:
We must find *something* to throw away though! :-)
One small issue that I'd love to see thrown away is the special handling the the unary "-" operator in Haskell 98. It's been described as "embarrassing", "ugly", and even "inconvenient" I, for one, find myself creating sections of the form `+ (-x)` all the time, and it feels wrong. What do people think?
yeah, I really want to see this change too. I think it would be a whole lot nicer. plus, a syntax highlighting editor would be able to determine the difference between - used as an operator and - used as part of a number.
Would one of you make sure that these pros & cons are reflected in this ticket or the linked wiki page: http://hackage.haskell.org/trac/haskell-prime/ticket/50 peace, isaac

Am Mittwoch, 1. Februar 2006 01:32 schrieb Patryk Zadarnowski:
[...]
The proposal would be to remove the unary "-" altogether, and, instead, extend the lexical syntax of numeric constant to allow "+" and "-" prefix.
Would this mean that (-x) is a section while (-1) isn't? That would be confusing. Apart from this, I would like to see the only unary operator of Haskell removed.
[...]
Best wishes, Wolfgang

On 03/02/2006, at 9:25 AM, Wolfgang Jeltsch wrote:
Am Mittwoch, 1. Februar 2006 01:32 schrieb Patryk Zadarnowski:
[...]
The proposal would be to remove the unary "-" altogether, and, instead, extend the lexical syntax of numeric constant to allow "+" and "-" prefix.
Would this mean that (-x) is a section while (-1) isn't? That would be confusing.
Apart from this, I would like to see the only unary operator of Haskell removed.
Yes, it *would* mean that (-x) and (- 1) are sections while (-1) isn't, and yes, that would be slightly confusing (and a good compiler might want to issue a warning whenever it sees a construct of the form (-identifier). However, it is NOT more confusing than what we already have with the (.) operator. Consider: (Just . not) is a perfectly reasonable function of type (Bool -> Maybe Bool) But: (Just.not) has a completely different meaning (and is probably illegal unless you have a module called "Just", which exports a function called (not).) In the case of the (.) operator, the confusion is more significant, since the meaning is context-sensitive. With the proposed "-" operator, it would be purely lexical, and therefore easy to warn about (if the compiler wishes to do so.) In both cases, accidentally omitting a space will result in a compiler or type error anyway, since (-x) has a different type than (- x), so such accidents will be picked by the compiler rather than generating invalid code. In summary: yes, the change would create *some* confusion. But much less confusion than that caused by the current treatment of (-). Pat.

On Fri, Feb 03, 2006 at 09:54:59AM +1100, Patryk Zadarnowski wrote:
On 03/02/2006, at 9:25 AM, Wolfgang Jeltsch wrote:
Am Mittwoch, 1. Februar 2006 01:32 schrieb Patryk Zadarnowski:
[...]
The proposal would be to remove the unary "-" altogether, and, instead, extend the lexical syntax of numeric constant to allow "+" and "-" prefix.
Would this mean that (-x) is a section while (-1) isn't? That would be confusing.
Apart from this, I would like to see the only unary operator of Haskell removed.
Yes, it *would* mean that (-x) and (- 1) are sections while (-1) isn't, and yes, that would be slightly confusing (and a good compiler might want to issue a warning whenever it sees a construct of the form (-identifier).
I'd much prefer it gave a warning for (-1) as, with -1 being a single lexeme, parentheses would never be needed.
In both cases, accidentally omitting a space will result in a compiler or type error anyway, since (-x) has a different type than (- x), so such accidents
Do you mean (-1) and (- 1) here? Thanks Ian, in support of this proposal

On 03/02/2006, at 10:03 AM, Ian Lynagh wrote:
On Fri, Feb 03, 2006 at 09:54:59AM +1100, Patryk Zadarnowski wrote:
Yes, it *would* mean that (-x) and (- 1) are sections while (-1) isn't, and yes, that would be slightly confusing (and a good compiler might want to issue a warning whenever it sees a construct of the form (- identifier).
I'd much prefer it gave a warning for (-1) as, with -1 being a single lexeme, parentheses would never be needed.
Before we start another debate on warnings (which I would REALLY prefer to keep out of my already-swamped mailbox!) this really isn't an issue for the language design, but rather compiler implementation (and therefore out of scope of this mailing list.) The right thing would probably be warn about any instance of code that breaks between H98 and H' for now, and once the change becomes mainstream, change the compilers to generate whatever warnings turn out to be more useful. Either way, my point is that detecting these is a trivial lexical matter, while detecting (.) inconsistencies isn't. And I would NOT like to see (.) as the composition operator go - I use it in pretty much every piece of Haskell code I have ever written!
In both cases, accidentally omitting a space will result in a compiler or type error anyway, since (-x) has a different type than (- x), so such accidents
Do you mean (-1) and (- 1) here?
Both. Pat.

I don't know if this is something that's been argued before, but I came across an interesting example of why the unary '-' is bad, while searching for reasons that single line comments are bad. A section involving the binary minus operator must always be bracketed, and as such will always have a '(' infront of it. That means that this example can never happen: infixl 0 --> (-->) x y = print x >> print y f = do { -5 --> 5; return()} Delete the space after the '{' and you have a problem. This can't happen if you don't have a unary minus. Bob

On Thu, Feb 02, 2006 at 11:26:04PM +0000, Thomas Davie wrote:
infixl 0 -->
(-->) x y = print x >> print y
f = do { -5 --> 5; return()}
Delete the space after the '{' and you have a problem. This can't happen if you don't have a unary minus.
Holy Moly, you came up with an example that hits every dogshed discussion at once. now, just change the 'print's to something polymorphic and we can hit the MR too! :) John -- John Meacham - ⑆repetae.net⑆john⑈

On Thursday 02 February 2006 23:25, Wolfgang Jeltsch wrote:
Am Mittwoch, 1. Februar 2006 01:32 schrieb Patryk Zadarnowski:
[...]
The proposal would be to remove the unary "-" altogether, and, instead, extend the lexical syntax of numeric constant to allow "+" and "-" prefix.
Would this mean that (-x) is a section while (-1) isn't? That would be confusing.
Apart from this, I would like to see the only unary operator of Haskell removed.
I'd rather have operator sections removed. They are not very intuitive anyway and can be easily replaced, i.e. (+ x) ---> flip (+) x (x +) ---> (+) x which could profit from the proposal to generalize currying: f ? === (\x -> f x) [I prefer '?' for the 'left out' argument, rather than '_'] We could then replace the section (+ x) ---> (+) ? x or even (+ x) ---> (? + x) This would open the possibility to allow unary (prefix) operators in general which I find rather more useful than sections. Ben

On 2/2/06, Benjamin Franksen
This would open the possibility to allow unary (prefix) operators in general which I find rather more useful than sections.
Down that road lies APL.
--
Taral

Hello Benjamin, Friday, February 03, 2006, 2:29:47 AM, you wrote: (+ x) --->> (? + x) i like this idea! but i tink that it's too late for such incompatible change :( really, unary operators can be added to language without any troubles. we need only to prohibit using of the same symbol for unary and binary operators: unary 9 # #n = n-1 f = #1-1 we can even allow prefix and postfix operators as long as they all have different names -- Best regards, Bulat mailto:bulatz@HotPOP.com

On Feb 3, 2006, at 9:34 AM, Bulat Ziganshin wrote:
Hello Benjamin,
Friday, February 03, 2006, 2:29:47 AM, you wrote:
(+ x) --->> (? + x)
i like this idea! but i tink that it's too late for such incompatible change :(
really, unary operators can be added to language without any troubles. we need only to prohibit using of the same symbol for unary and binary operators:
unary 9 #
#n = n-1
f = #1-1
we can even allow prefix and postfix operators as long as they all have different names
The notable exception in this case, '-' (or anything starting with -), which breaks block comment syntax (see my earlier example). Bob

Hello Simon, Tuesday, January 31, 2006, 1:31:26 PM, you wrote: SM> We must find *something* to throw away though! :-) "newspeak is the only language whose dictionary is decreasing" (c) "1984" :) at least from library we should throw many things, including old exceptions, data.array and of course Handles ;) as a rule of thumb, anything without class-defined interface is not good enough to be included in the Standard :) -- Best regards, Bulat mailto:bulatz@HotPOP.com

We must find *something* to throw away though! :-) Simon
Indeed. One of the things I had been hoping for in Haskell' was the removal of the many conservative restrictions put into earlier definitions: they complicate the language definition, restrict expressiveness, and have prompted various extensions. - mr - the whole bunch of "you can't do this (we think)" in type classes and their instances, when nowadays we know that type class instances are all about logical meta-programming at the type level. non-decidability should still be optional, but also, at least standardised. - .. (btw, I hope I'm not misquoting, but I think it was Mark Jones who said that permitting complex type parameters was more important than having multiple parameters in type classes - you can simulate multiple parameters by tupling) anyway. Just as I was disturbed by the many not-yet-existing features under discussion, I am worried about the new trend of proposing not to include old friends (MPTC, concurrency, functional dependencies, ..). If that should happen, Haskell' will be just as irrelevant as Haskell98 was, before the FFI addendum (how many Haskell98 programs were there that did not use "primitives"?). So I repeat my opinion: the committee should not limit itself to a single, all-encompassing standard. There are things that can and need to be standardised, for which we do not yet know whether they should be frozen into _the_ standard forever, and there are things that need to be standardized, for which the standardization might take too long to match the Haskell' timeline. The established answer to such changeability in software is to modularize, and the same should happen for the language standard. I agree with Patryk here (I even like the idea of abusing imports to specify language extensions in use, though I would simply use a combination of imports and reserved parts of the module hierarchy, without modifying the import syntax at all). Perhaps we cannot have Concurrent Haskell in all Haskell' implementations, or perhaps Functional Dependencies will be replaced by something else in the future. But when I use either of them, I want to be able to write code that any supporting Haskell'+CH+FD implementation will understand and interpret the same way, and about which any non-supporting Haskell' implementation will be able to tell me exactly what it is that it doesn't support (instead of giving obscure syntax errors). Scanning over the import lines and reporting that "no, sorry, we don't have Language.Haskell. Extensions.Types.FancyRankN here" should do the latter quite nicely, and allows to document the former in the same way as libraries. Cheers, Claus PS Someone suggested searching the libraries for features that are in use and should therefore be included in Haskell'. Another thing to look for are preprocessor directives protecting differences between implementations. Also, perhaps someone could write a simple program analyzer that people could run over their own code repositories to report features in use back here (perhaps based on the extended Haskell syntax parser)? You'll need something like this anyway, as part of moving code from Haskell98 and Haskell(GHC), ... to Haskell'.
participants (17)
-
Ben Rudiak-Gould
-
Benjamin Franksen
-
Bulat Ziganshin
-
Claus Reinke
-
dons@cse.unsw.edu.au
-
Ian Lynagh
-
isaac jones
-
John Meacham
-
Malcolm Wallace
-
Neil Mitchell
-
Patryk Zadarnowski
-
Philippa Cowderoy
-
Robert Dockins
-
Simon Marlow
-
Taral
-
Thomas Davie
-
Wolfgang Jeltsch