RE: behaviour of System.system?

1999-11-16 Thread Simon Peyton-Jones
| Obviously it would be useful if the expected behaviour were documented | more tightly, and conformed across compilers. Which result should we | choose to be standard? (And can the decision please be | recorded in the Haskell 98 errata?) I would welcome a tightened definition, and would add

Glasgow Haskell compiler: pre-release 0.06 is available

1992-03-28 Thread Professor Simon Peyton-Jones
queries to glasgow-haskell-request@same. Simon Peyton Jones (and his GRASPing colleagues) .. References ^^ [1] Simon L Peyton Jones and John Launchbury, "Unboxed values as first class citizens", Functional Progr

RE: Current state of GUI libraries for Haskell

1998-09-03 Thread Simon Peyton-Jones
We have developed here a large Haskell program with ghc-2.08. Now we want to extend it by a graphical user interface, preferably using Haskell as well. I am aware of Fudgets and Haggis, but it seems that their development ceased in 1996 (correct?). Obviously we are searching for a

Standard Haskell

1998-09-07 Thread Simon Peyton-Jones
than exhaustion. Last chance! Simon PS: since this is going to lots of people, I'll piggy-back on my change-of-address info: I've moved from Glasgow to Microsoft Research Ltd in Cambridge. Here are my new contact details: Simon Peyton Jones Microsoft Research Ltd, St George

RE: Nested pattern guards.

1998-10-05 Thread Simon Peyton-Jones
Hi all. Was there ever any sort of consensus about whether pattern guards ought to be "nestable", or not? And if not, was there some semantic objection to this, was the syntax just considered to Unspeakable to be spoken of, or is the feature just largely redundant? (I think you can

RE: Haskell in Scientific Computing?

1998-10-16 Thread Simon Peyton-Jones
Could Haskell ever be used for serious scientific computing? What would have to be done to promote it from a modelling tool to a more serious number crunching engine? Maybe not necessarily competing with Cray, but not terribly lagging far behind the other languages?

RE: Haskell 98

1998-10-16 Thread Simon Peyton-Jones
Classes appear in *contexts*, not in types. So there's no confusion. This is another `bug fix' which simplifies the language, and I think we should do it. Consider the function t :: T a = T a - T a I think that it's far from clear what each of the T's mean! Worse, in Haskell 2

RE: Fixing imports for and namespaces (was: Simon's H98 Notes)

1998-10-21 Thread Simon Peyton-Jones
That being said, if Haskell simply added support for hierarchical namespace and a standard path convention for finding libraries and source, I would be ecstatic. Better scoping, nicer import operators, and more visibility control are just bonus. Personally I'm quite sympathetic to the

RE: type error, why?

1998-10-27 Thread Simon Peyton-Jones
Alternatively, since GHC 4.0 is there a way to run just the type-checker part of GHC 4.0 without waiting for it to compile everything? Also, has anyone manageed to build GHC4.0 for win32? The -S flag compiles just as far as an assembly-code file, but you can't do less than that. 3.02

RE: Ix Bool

1998-11-02 Thread Simon Peyton-Jones
I propose that we add an Ix Bool instance to the Ix library. It doesn't seem to be there just now. For Haskell 98? It does seem reasonable on the face of it. Comments from anyone else? Simon

MonadZero

1998-11-03 Thread Simon Peyton-Jones
Folks, I'm working on the Haskell 98 report this week, but I'm *still* not sure what to do about the dreaded MonadZero issue, so this message has one last go at presenting the issues. Here are the two proposals I suggested in http://research.microsoft.com/Users/simonpj 1.Fix up the

Haskell 98

1998-11-03 Thread Simon Peyton-Jones
Folks Just to keep you informed, here's a quick summary of what I'm up to. I plan to implement the changes proposed on http://research.microsoft.com/Users/simonpj/Haskell/haskell98.html with the following exceptions * I'm still undecided about MonadZero (see last message) * Ditto

RE: MonadZero

1998-11-03 Thread Simon Peyton-Jones
2.Nuke MonadZero altogether. add mfail :: m a to Monad instead Sorry, I don't understand option 2, can you please explain? * Eliminate MonadZero * Add 'mfail :: m a' to Monad, with a suitable default decl * Every do expression has a type in Monad Yes.

RE: MonadZero

1998-11-03 Thread Simon Peyton-Jones
* Eliminate MonadZero * Add 'mfail :: m a' to Monad, with a suitable default decl * Every do expression has a type in Monad I must be dense this morning, as I'm still in the dark. What is the intended meaning of `mfail'? If `mfail' is `mzero', why change the name?

RE: Polymorphic recursion

1998-11-04 Thread Simon Peyton-Jones
I don't know whether ghc uses an iteration limit mechanism -- my guess is that it probably uses the same technique as Hugs. No, it's an iteration limit. (When you say -fallow-undecideable-instances). Simon

RE: Monolithic and Large prelude

1998-11-04 Thread Simon Peyton-Jones
I would like to lobby to move sum and product to the list library. Or, to rename them listSum, listProduct. (so that a user can use the names sum and product for whatever is their primary data structure e.g. tree) As someone said, I think 'hiding' is what you want. Your suggestion is quite

RE: MonadZero (concluded?)

1998-11-05 Thread Simon Peyton-Jones
There is no need to have both `mzero' and `mfail' in every monad. Just have `mfail'. Leave `zero' and `plus' to MonadPlus. This should make Eric partially happy. It also means one can simply write instance Monad [] where ...return, =, as before... mfail s = []

RE: composed contexts

1998-11-06 Thread Simon Peyton-Jones
class (Monad m, Monad (t m)) = MonadT t m where lift :: m a - t m a instance (Monad m, Monad (StateT s m)) = MonadT (StateT s) m where lift m = \s - m = \x - return (s,x) If the definitions from the paper can be turned into valid Haskell 98 w.l.o.g. now, then I'm happy. No,

MonadZero (concluded)

1998-11-06 Thread Simon Peyton-Jones
OK, I think we have enough agreement to decide: class Monad m where return :: m a (=) :: m a - (a - m b) - m b () :: m a - m b - m b fail :: String - m a fail s = error s (I'm still a bit nervous about capturing 'fail' but there

RE: MonadZero (concluded)

1998-11-06 Thread Simon Peyton-Jones
| class Monad m = MonadPlus m where | mzero :: m a | mplus :: m a - m a - m a | | Why is this here? It doesn't need to be in the prelude. Just | leave it for the user to define (and then the user may pick | better names, like Ringad, zero, and +). -- P Yes, nuke

RE: MonadZero (concluded)

1998-11-09 Thread Simon Peyton-Jones
Following many protests, the right thing to do seems to be to move MonadPlus to the Monad library. Specifically: class Monad m = MonadPlus m where mzero :: m a mplus :: m a - m a - m a filterM :: MonadZero m = (a - m Bool) - [a] - m [a] guard ::

RE: hugs and ghc compatibility and features

1998-11-10 Thread Simon Peyton-Jones
2. Does the new GHC support TREX? If yes, how does one enable it? TREX is Mark and Ben's excellent record system for Haskell. No, GHC doesn't support it. I'd be interested to know how high a priority adding TREX would be to GHC users. Simon

Haskell 98 progress...

1998-11-13 Thread Simon Peyton-Jones
We're nearly done with Haskell 98. * In my last progress report I said: However a couple of other similar proposals have been made - add succ and pred to class Enum - add atan2 to class RealFloat I've had no complaints so I consider this done. * Still no decision about the

RE: Reduction count as efficiency measure?

1998-11-26 Thread Simon Peyton-Jones
I'm still curious about my first question, though, about the specific optimizations included in ghc and hbc. If in fact they don't do CSE, are there optimizations which they do perform which would change the asymptotic running time? GHC doesn't do CSE, and this is part of the reason...

RE: H98 bugs

1998-11-27 Thread Simon Peyton-Jones
Report p41: why can't newtypes make use of labelled field syntax? newtype T = MkT { unT :: Int }, for example, is a nice way to define both parts of the newtype isomorphism. (Hugs already does this, but perhaps I should make it reject such code when it is running in Haskell 98

Leading underscores

1998-12-01 Thread Simon Peyton-Jones
Bjarte sugggests the following: Regarding id.s starting with _: should the report encourage compilers to do the following: f _ = 1 -- no warning g _a = 1 -- no warning h a = 1 -- warning: a unused in h I though this was one of the reasons

FW: Haskell 98: randomIO

1998-12-01 Thread Simon Peyton-Jones
Olaf makes good suggestions about Haskell 98 library module Random. I propose to write them into the report. Simon -Original Message- From: Olaf Chitil [mailto:[EMAIL PROTECTED]] Sent: Monday, November 30, 1998 1:42 PM To: Simon Peyton-Jones Subject: Haskell 98: randomIO Hi Simon

RE: Interesting class and instance question

1998-12-08 Thread Simon Peyton-Jones
The *only* way I have been able to make this work, after lots of trying and mind-bending, is to introduce a "phantom" type to allow me to combine things appropriately: data MkFinMap m k a = MkFinMap (m (Pair k a)) instance (SortedList m (Pair k a), ZeroVal a) = FiniteMap

RE: Why change the monomorphism rules?

1998-12-15 Thread Simon Peyton-Jones
Simon's latest report changes the relationship between monomorphism and defaulting. This issue was never discussed at length by the committee so I think I'll bring the discussion out here. ... Please take the time look into this issue and voice your opinions. Let me second John's

RE: Haskell 98: fixity of =

1998-12-16 Thread Simon Peyton-Jones
whereas under 1.3 fixity it parses as: main :: IO () main = f (dropOut cond1 $ (g (dropOut cond2 $ h) dropOut :: Bool - IO () - IO () dropOut gotError cont | gotError = return () | otherwise = cont which is what

RE: Why change the monomorphism rules?

1998-12-21 Thread Simon Peyton-Jones
Simon's latest report changes the relationship between monomorphism and defaulting. This issue was never discussed at length by the committee so I think I'll bring the discussion out here. John objected quite strongly to changing the way top-level monomorphism is resolved. I count the

RE: Haskell 98 draft report

1998-12-21 Thread Simon Peyton-Jones
p. 83 'Coercions and Component Extraction' I find it quite odd that round 3.5 returns 4, but round 2.5 returns 2. I always thought that round x.5 returns x+1 (instead of the even integer). That's the behaviour in most math books and programming languages It looks odd to me too. I think

Haskell 98 is done

1998-12-23 Thread Simon Peyton-Jones
Folks, Haskell 98 is finished! You will find 'Final Draft' versions of the Language Report and Library Report at http://research.microsoft.com/~simonpj/Haskell/haskell98.html A dozen or so people have contributed a lot to getting typos etc out of the Reports, and I thank them for

RE: A simple question on Haskell style

1999-01-28 Thread Simon Peyton-Jones
Is it better to type the derived methods inside the class definition or out? Are there any efficiency penalties in any of the styles? In Haskell98 Prelude there is a mixture of both styles, for example, () is defined inside the Monad class, but (=) is left out. Good question. The

Haskell 98 final stuff

1999-01-28 Thread Simon Peyton-Jones
Folks, I've been doing the final clean-up of typographical errors in the Haskell report. This messages summarises anything non-trivial that I've done. I'll put out the final version shortly. There are two points that came up that seem substantial: 1. I think we decided a while ago to remove

RE: fail

1999-01-28 Thread Simon Peyton-Jones
Ralph, you said that `fail' intentionally calls `error' in the IO monad because it corresponds to pattern matching failure. I would buy this argument if `fail' were used only internally. But it is exposed to the user: she or he is free to call `fail'. Now, in the list monad `fail s'

RE: Query re gcd() in Haskell 98

1999-02-01 Thread Simon Peyton-Jones
-Original Message- From: michael abbott [mailto:[EMAIL PROTECTED]] Sent: Monday, February 01, 1999 10:47 AM To: Simon Peyton-Jones Cc: [EMAIL PROTECTED] Subject: Query re gcd() in Haskell 98 It seems a bit late to raise this, but I notice that the standard prelude for Haskell 98

Libraries

1999-02-11 Thread Simon Peyton-Jones
Folks, Those of you who are interested in the important question of designing good libraries for Haskell may find it intersting to look at what the Scheme community is doing: http://srfi.schemers.org/ John: perhaps worth adding a cross-link to this from the Haskell tools and

Haskell 98 announcement

1999-02-04 Thread Simon Peyton-Jones
Folks, Haskell 98 is done! You can find the Language Report and Standard Library Report at http://haskell.org/definition (To get the online HTML Language Report, click on the 'Haskell 98 Report' item, and similarly for the Library Report. You'll also find postcript, PDF, etc.) The

Haskell 98 library: Directory.lhs

1999-03-10 Thread Simon Peyton-Jones
Folks, A Haskell 98 addendum Lennart points out that in a fit of enthusiasm I made the Permissions data type abstract, adding functions for readable, writable, executable, searchable :: Permissions - Bool What I totally failed to notice is that you then can't *set* the permissions

RE: Permission to distribute the Haskell 98 reports as part of De bian?

1999-03-18 Thread Simon Peyton-Jones
Hmm. It's not clear who *can* give you permission. But if anyone can, it must be the editor. That's me, and I hereby give you permission. Please include also the errata noted at http://research.microsoft.com/~simonpj/haskell/haskell98-bugs.html Simon Peyton Jones -Original

RE: Permission to distribute the Haskell 98 reports as part of De bian?

1999-03-22 Thread Simon Peyton-Jones
two libs, which caused the creation of fgmp), I'd like to know what the legal status of the various Haskells is exactly. As I think many people know, I'm trying to get a BSD style license for GHC (minus the advertising clause). Microsoft are happy with this; Glasgow University are

RE: Plea for Change #2: Tools

1999-03-30 Thread Simon Peyton-Jones
The report should state the least common denominator interface to command line tools, at least up to relatively simple tasks like compiling a multi-module program (spanning several directories). How about `haskell2 [-I dirs] main module'? I'm all for this (in addition to, not instead of,

RE: STL Like Library For Haskell

1999-04-28 Thread Simon Peyton-Jones
Chris Okasaki is working on just such a thing. He'll be ready soon... Simon -Original Message- From: Kevin Atkinson [mailto:[EMAIL PROTECTED]] Sent: Tuesday, April 27, 1999 5:20 PM To: [EMAIL PROTECTED] Subject: STL Like Library For Haskell Has anyone done any work on comings

Type signatures in Haskell 98

1999-04-28 Thread Simon Peyton-Jones
Folks, Here's a good Haskell 98 question: is this a valid H98 module? module F where sin :: Float - Float sin x = (x::Float) f :: Float - Float f x = Prelude.sin (F.sin x) The 'sin' function is defined by the (implicitly

RE: Type signatures in Haskell 98

1999-05-07 Thread Simon Peyton-Jones
Here's a good Haskell 98 question: is this a valid H98 module? module F where sin :: Float - Float sin x = (x::Float) f :: Float - Float f x = Prelude.sin (F.sin x) That sounds like a fine thing to do if the signature is

RE: Another Haskell 98 question

1999-05-10 Thread Simon Peyton-Jones
Will this change be compatible with the first class (extensible?) records work? I know that first class records will not be part of Haskell98, but it would be nice if Haskell2000 (or whatever) could be close to the stable language of H98. Can we expect first class records in the near

RE: rules

1999-05-10 Thread Simon Peyton-Jones
Thanks to everyone who has contributed to the discussion about transformation rules. There is clearly something inteeresting going on here! There is clearly a huge spectrum of possibilities, ranging from nothing at all to a full theorem-proving system. In adding rules to GHC I'm trying to

Another Haskell 98 question

1999-05-10 Thread Simon Peyton-Jones
A question about Haskell 98: is this legal: data T = T1 Int Int Int | T2 Float Float Float f (T1 {}) = True f (T2 {}) = False The point is that T is not declared using record syntax, but f nevertheless uses record syntax in the pattern match to mean "T1

RE: rule and binding

1999-05-13 Thread Simon Peyton-Jones
I'm not sure exactly what you are asking here. For example, in {rules (map f).(map g) = map (f.g) } f xs = let g = ... h = ... h1 = map g h2 = map h in

RE: rule and binding

1999-05-13 Thread Simon Peyton-Jones
Are ($) and (.) actually treated specially within ghc then and optimized away from the rules? If so then rule rewriting becomes more powerful than I'd thought, beacuse the one of the problems I thought was there was that the idea that `several maps can be be turned into a single map

RE: rules for type casting

1999-05-17 Thread Simon Peyton-Jones
{rules Num a= x::a, y::[a] == x+y = [x]+y} instance Num a = Num [a] where ... one could expect for x :: Num b=b the casting x + [x,y] -- [x] + [x,y] Provided the two sides of the rules

RE: rules for type casting

1999-05-14 Thread Simon Peyton-Jones
Another question on *rules*. Could they help the implicit type casting? For example, with {rules Num a= x::a, y::[a] == x+y = [x]+y} instance Num a = Num [a] where ... one could expect for x :: Num b=b the casting

RE: Contexts on data type declarations

1999-05-18 Thread Simon Peyton-Jones
Folks, Interesting! Phil, Mark, and Jeff all have a different interpretation of how contexts on how data type declarations work than I did. So unless some other people chime in, I will therefore adopt their interpretation, since (a) I'm in the minority and (b) it's not a big deal at all. But

Contexts on data type declarations

1999-05-17 Thread Simon Peyton-Jones
Folks Julian has discovered another ambiguity in the Haskell 98 Report. Consider: data Ord a = T a = MkT a a We know that MkT has type MkT :: Ord a = a - a - MkT a a We also know that the dictionary passed to MkT is simply discarded. The constraint simply makes sure that

RE: Haskell Type System Nameable type parameters

1999-05-18 Thread Simon Peyton-Jones
Kevin You might also find my paper "Bulk types with class" useful http://research.microsoft.com/~simonpj/papers/collections.ps.gz For a discussion of the type-class design space you might find this helpful http://research.microsoft.com/~simonpj/papers/multi.ps.gz And don't

RE: Contexts on data type declarations

1999-05-17 Thread Simon Peyton-Jones
I'm happy with either of the following choices: * Class constraints on constructors have effect everywhere (as in Hugs). * Class constraints on constructors are eliminated (call it a typo if you must). I'd be delighted to eliminate them, but we had a long H98 debate about it (under

RE: how to write a simple cat

1999-06-02 Thread Simon Peyton-Jones
I know, we all have something else to do than to take on extra responsibilities. But if someone could donate an access to a fast web server (mine is just too slow) then we could go along Wiki-Wiki Web Server concepts (http://c2.com:8080/WikiWikiWeb) and have

RE: strict data field

1999-06-11 Thread Simon Peyton-Jones
Here is my situation: I have a state monad. It seems to me that if states are built out of lazy types, then there may be many states all live at the same time, thus blowing up the space. But deep in my state data types, I have strings. Also some monad operations return strings. So I need

RE: Projects using HUGS or Haskell

1999-06-11 Thread Simon Peyton-Jones
Idea 1: Export Haskell declarations to a theorem prover, such as HOL or PVS. Then permit the user of the theorem prover to state and prove properties of the Haskell program, using the exported definitions. Ideas 2: There was recently a discussion about adding "rules" to Haskell,

Haskell 98

1999-07-12 Thread Simon Peyton-Jones
Folks, For a long time an item on my to-do list has been to update the Haskell 98 bugs page. http://research.microsoft.com/~simonpj/haskell/haskell98-bugs.html I have now done so, adding a dozen or so bug fixes and clarifications that have arisen over the last few months. I believe

RE: Diagonalisations (was: Re: Deriving Enum)

1999-07-12 Thread Simon Peyton-Jones
DiagMPJ 0:00.16 0:02.32 0:37.55 DiagMPJ1 0:00.12 0:01.50 0:23.83 DiagWK1 0:00.12 0:01.34 0:19.02 DiagWK2 0:00.12 0:01.35 0:19.09 DiagWK3 0:00.12 0:01.34 0:18.82 The only thing that surprises me is that the compiler does not do the optimization from DiagWK2 to

RE: diagonalization

1999-07-16 Thread Simon Peyton-Jones
Folks, | To me, it seems unsatisfactory to have a solution to this pure | list problem with auxiliary functions relying on integers. | It turns out to be a nice exercise to implement | | diagonalise :: [[a]] - [a] | | without any reference to numbers. I havn't been following the

RE: Importing, hiding, and exporting

1999-07-26 Thread Simon Peyton-Jones
OK, then I'll rephrase my question: What's the rationale of throwing different namespaces together in the hiding clause? Maybe they shouldn't be -- but if not, then hiding( Ding ) would hide a type constructor or class Ding, but not a constructor Ding, which is arguably odd. But

RE: Again: Referential Equality

1999-07-27 Thread Simon Peyton-Jones
The expression let x=[1..] in x==x would not terminate in the first case but succeed in the second. But, much worse let x = (a,b) in x `req` x = True but (a,b) `req` (a,b) = False So referential transparency is lost. This is a high price to

RE: Importing, hiding, and exporting

1999-07-26 Thread Simon Peyton-Jones
The strange thing about this part of Haskell 98 is that given -- Baz.hs -- module Baz where newtype Ding = MakeDing Int -- Bar.hs -- module Bar(module Baz) where import Baz hiding (Ding)

RE: The dreaded layout rule

1999-07-30 Thread Simon Peyton-Jones
In other words, it is a bug (and GHC and Hugs don't do it right - see my previous message; from your comment, I presume HBC also doesn't follow the definition). I think, the only Right Thing is to remove this awful rule (unless somebody comes up with a rule that can be decided locally).

RE: Wiki Sites

1999-08-23 Thread Simon Peyton-Jones
One possible solution would be a Wiki (formerly WikiWiki) site. This was also mentioned some time ago, but, again, no-one seemed to know how to go about doing it. It would be great to have a Haskell Wiki. As I understand it, to host a Haskell Wiki would require: a) providing a suitable

RE: Units of measure

1999-08-26 Thread Simon Peyton-Jones
Good idea. Andrew Kennedy wrote a whole thesis about this, and a paper or two besides. http://research.microsoft.com/~akenn/ -Original Message- From: Tom Pledger Sent: Thursday, August 26, 1999 7:56 AM To: [EMAIL PROTECTED] Cc: [EMAIL PROTECTED] Subject: Units of measure

RE: Full laziness (was Re: Q: hugs behavior...)

1999-08-27 Thread Simon Peyton-Jones
There's a whole chapter on full laziness in my book; and a paper in Software Practice and Experience A modular fully-lazy lambda lifter in Haskell, SL Peyton Jones and D Lester, Software Practice and Experience 21(5), May 1991, pp479-506. The latter is available on my publications page

Wish list for Hugs and GHC

1999-08-31 Thread Simon Peyton-Jones
Gentle colleagues It has gradually become clear that the GHC and Hugs developers (mostly, but not entirely, at Microsoft Research and OGI) have become a bottleneck when it comes to discussing and refining proposals for enhancements to GHC, Hugs, and (soon, soon) the glorious combination thereof.

FW: ICFP programming contest

1999-08-31 Thread Simon Peyton-Jones
Folks, don't forget the ICFP programming contest! It's a 3-day programming challenge, aimed primarily at the FP community. There's a 1-day 'blitzkrieg' version, aimed at people (like me) who have families that won't tolerate absence for a weekend. You can do it all 5pm Thurs - 5pm Fri!

RE: Data constructor not in scope: `:='

1999-09-01 Thread Simon Peyton-Jones
Haskell changed. Use pairs (a,b) instead of a special constructor (a := b), thus array (1, n) [(i, xa!i :+ xa!(i+n)) | i - [1..n]] -Original Message- From: Jan-Friso Evers Sent: Wednesday, September 01, 1999 11:02 AM To: [EMAIL PROTECTED] Subject: Data constructor not in

RE: Haskell Wish list: library documentation

1999-09-10 Thread Simon Peyton-Jones
* There have been lots of messages --- more so than most topics that appear on the list. Obviously there is lots of interest; the topic seems be one with which most people have encountered problems in the past so are keen to do something about. I think Richard has it right here.

RE: Haskell Wish list: library documentation

1999-09-13 Thread Simon Peyton-Jones
what ghc compiles. I'd like to also use Hugs, for a more interactive development environment, but it shows little sign of ever being sufficiently compatible (it is becoming increasing compatible in core aspects, but I want to use most of the features of ghc, and the benefit of having an

RE: ICFP programming contest

1999-09-15 Thread Simon Peyton-Jones
at "Si^3" stands for Simon Marlow, Simon Peyton-Jones, Sigbjorn Finne? If so, congratulations guys! It looks like you topped them all, with lightning entries to boot! (Well, that OCaml entry is close on your heels, but it wasn't a lightning entry.) I found it particularly interes

RE: ICFP programming contest

1999-09-17 Thread Simon Peyton-Jones
Just curious, a few questions : - How long was your program? - How did you do the parsing? with happy? parser combinators? ... - Which compiler did you use ? (Okay, i think i know ... :-)) - Other information you want to share with us ... (eg. - which optimization algoritm did you use?

RE: CPP is not part of Haskell

1999-10-04 Thread Simon Peyton-Jones
Either, cpp (or some preprocessor standard), should be made part of the Haskell language definition or Haskell files that require a preprocessor should have a different extension. GHC dodges this by allowing you to say {-# OPTIONS -cpp #-} at the start of your Haskell file Foo.hs.

RE: ++ vs comprehension

1999-10-05 Thread Simon Peyton-Jones
The latter, using the comprehension, is a bit better in GHC, because if c' gets inlined the list comprehension might get deforested with its consumer. WIth an explicitly recursive c, that won't happen. Simon -Original Message- From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]] Sent:

RE: OO in Haskell

1999-10-06 Thread Simon Peyton-Jones
Kevin writes: | I strongly agree that Haskell can become a *much* more | powerful language | with out losing any of clean syntax or semantics. However, | when ever I | bring up limitations of Haskell type system on this list I either get | ignorance or resistance. I strongly agree that

Journal of Functional Programming

1999-10-06 Thread Simon Peyton-Jones
Simon Peyton Jones Phil Wadler Paul Hudak Thierry Coquand Greg Morrisset

The Haskell mailing list

1999-10-08 Thread Simon Peyton-Jones
Folks, Traffic on the Haskell mailing list has jumped dramatically of late. In many ways that's a good thing: I take it a symptomatic that Haskell is getting used for more things by more people. But it has a bad side: if traffic is too heavy, large numbers of people will unsubscribe (indeed,

RE: GHugsC?

1999-10-08 Thread Simon Peyton-Jones
| What progress on the Great Hugs Collaboration? That is, | being able to run | Hugs bytecode inside GHC or GHC compiled code inside Hugs. I | don't expect much detail but if the marriage is expected Real Soon Now, or | alternatively has been postponed indefinitely, I would like to know! An

RE: Haskell 98 progress...

1998-11-23 Thread Simon Peyton-Jones
Folks, here's a clarification about comment syntax. Simon |The new draft (which you won't have seen) says: | |"An ordinary comment begins with a lexeme consisting of |two or more consecutive dashes (e.g. @--@) and extends to the following |newline. The comment must begin with a lexeme

RE: Haskell 98 progress...

1998-11-23 Thread Simon Peyton-Jones
I don't understand this remark. Are you telling me that after a '{-' token the usual lexical process is used to find the matching '-}' token? That's what I intended. Provided that scanning can't given an error, that is actually *easier* than searching for the first '-}' sequence. And it

Monomorphism wierdness

1998-11-18 Thread Simon Peyton-Jones
someone objects. Simon -Original Message- From: Mark P Jones [mailto:[EMAIL PROTECTED]] Sent: Wednesday, November 18, 1998 4:15 PM To: Simon Peyton-Jones Cc: 'John Launchbury'; Jeffrey R. Lewis; Mark P Jones; [EMAIL PROTECTED]; [EMAIL PROTECTED] Subject: Re: monomorphism wierdness

RE: `sum' in ghc-4.02

1999-05-27 Thread Simon Peyton-Jones
foldl looks like this: foldl k z [] = z foldl k z (x:xs) = foldl k (z `k` x) xs To work in constant space, foldl needs to evaluate its second argument before the call, rather than building a thunk that is later forced (which in turn builds stack). But in general, foldl is not strict in z.

RE: Partial Type Declarations

1999-01-15 Thread Simon Peyton-Jones
| Here is how we could specify partial type information | about foo: | | foo :: (..) = a - b - c Good idea. Mark and I discussed something very like this when we were writing our Haskell workshop paper, but it didn't make it into the paper. Seems easy to use and to implement. Fergus

RE: The Haskell compiler of my dreams...

1999-11-25 Thread Simon Peyton-Jones
| My question is: Why Haskell compiler makers do not try to | catch with Clean | team, and surpass them? After all, there are many more people working | with Haskell than with Clean. A brief response. First, Clean is indeed an excellent system, and its implementors are fearsomely talented. As

RE:

1999-11-25 Thread Simon Peyton-Jones
| ourselves on Haskell. I infer from your letter that the GHC | team has no | interest on building a practical Haskell compiler, but to | play and experiment with the language. I didn't speak clearly enough if that is your inference! First, GHC is certainly a practical Haskell compiler in the

RE: The Haskell compiler of my dreams...

1999-11-26 Thread Simon Peyton-Jones
| Does that mean that (to borrow from the GHC docs) "smaller, faster, | stingier" are acceptable items for the wishlist? That | possibility had never occurred to me. Certainly they are acceptable wishes! Of course, they are wishes we all have -- who would not want smaller, faster? However,

RE: ghc-4.05 slower then hugs?

1999-11-26 Thread Simon Peyton-Jones
Ronald Thanks for your program, which had the amazing property that Hugs runs it 20x as fast as GHC4.05 -O! The reason turns out to be that you have hit on an optimisation that Hugs makes and GHC doesn't! But it is one that I don't expect to happen often enough to be worth adding to GHC. I'd

RE: Dynamic scopes in Haskell

1999-12-01 Thread Simon Peyton-Jones
| - Does other Haskell implementations (ghc, nhc, hbc, ...) | would provide this extension in next releases? (This way, | even been an extension, my system would be portable) Jeff Lewis is well advanced with adding functional dependencies into GHC; I believe that he plans then to add

RE: Graph reduction and lambda lifting

1999-12-07 Thread Simon Peyton-Jones
For a detailed description, try the book that David Lester and I wrote: Implementing Functional Languages: a tutorial The full text is at http://research.microsoft.com/~simonpj/Papers/papers.html | -Original Message- | From: Matthias Kilian [mailto:[EMAIL PROTECTED]] | Sent: 07

The Haskell 98 Report

1999-12-23 Thread Simon Peyton-Jones
John I'd like to update the Haskell 98 report to fix all the accumulated typos. But before I do that I want to put the Report under CVS somewhere. One possibility is to add it to the same repository that holds GHC and Hugs (but as a separate CVS module of course). That respository is already

RE: suggestion for Random.randomR

1999-12-23 Thread Simon Peyton-Jones
Sergey The essence of your message is that the H98 Random library defn of randomR doesn't really make sense if the type does not belong to Ord. I don't want to specify that | It is required randomR (lo,hi) g == randomR (hi,lo) g as you suggest. That would be counter-intuitive for

RE: De facto Haskell 2000?

2000-01-24 Thread Simon Peyton-Jones
| So will the features of Hugs eventually be supported by all | platforms and integrated into a future version of Haskell or will I have to | keep seperate versions of my code? No one is going to guarantee that. However, the GHC team and the Hugs team are making a conscious effort to align

RE: partition and lifted products

2000-01-24 Thread Simon Peyton-Jones
| Can we have extensional products and functions (or at least the means | to define them) please? Does anyone want to come up with a concrete language proposal? Language issues ~~~ A significant difficulty is that seq is essentially un-implementable for unlifted products (requires

Haskell 98: partition; and take,drop,splitAt

2000-01-24 Thread Simon Peyton-Jones
Folks The recent discussion has highlighted three things that I propose to treat as 'Haskell 98 typos'. Even if you have not been reading the dicussion, please read this, since I have my H98 editor's hat on, and I propose some minor changes to the published H98. Simon Partition ~

RE: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Simon Peyton-Jones
| Why not do what python does? Thanks for an interesting suggestion, Alex! However, we are in typo-fixing mode here. In the interests of helping this discussion converge I'm going to exercise my dictatorial powers. Though Alex's suggestion has its attractions, I judge it too big a change to

  1   2   3   4   5   6   7   8   9   10   >