RE: Dates in Haskell

1999-10-20 Thread Simon Peyton-Jones
George If you engage in discussion with other people (e.g. Fergus) who'd like to contribute, come up with a revised specification, and document and implement it, we'll gladly include it in the GHC distribution (and I expect the Hugs team will too). We can't change "Time" though; it's a Haskell 9

RE: Dates in Haskell

1999-10-20 Thread Simon Peyton-Jones
| > And once you have that, maybe they could all return the | > same type (TimeDiff) and then the need for the class goes away. | >diffMinutes :: ClockTime -> ClockTime -> TimeDiff | I suppose TimeDiff is then a disjunction (Minutes of Int | | Days of Int | etc.) | But I don't really see

RE: Haskell reports & licensing

1999-10-25 Thread Simon Peyton-Jones
| Several months ago there was discussion about changing the | Haskell spec | license to be more liberal. It is my understanding that we reached a | consensus, yet nothing has been done about it. There is something on the bugs page, but it isn't quite as I think you wanted. Sorry that I forgot

Job at GHC HQ

1999-10-29 Thread Simon Peyton-Jones
(we distribute GHC on Windows). Although you will an employee of the University of Glasgow, you will work here at Microsoft's (relatively) new Research Lab in Cambridge. The immedidate team consists of myself, Prof Simon Peyton Jones, Dr Simon Marlow and Dr Julian Seward, in the context of

RE: Default declarations

1999-11-02 Thread Simon Peyton-Jones
| The Haskell 98 report, section 4.3.4 states: | |[...] In situations where an ambiguous type is discovered, an |ambiguous type variable is defaultable if at least one of its |classes is a numeric class (that is, Num or a subclass of Num) |and if all of its classes are defined in

RE: Thanks, and new question re existensials

1999-11-08 Thread Simon Peyton-Jones
| Which is what we did in Hope+C (you have to say it out loud | ;-)) as well. Yes it was, and all credit to you for doing it then. hbc followed suit some years ago. GHC and Hugs are latecomers. | So that's good, I was concerned my earlier answer and | reference to a paper on implementation wa

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 i

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

Standard Haskell

1998-09-07 Thread Simon Peyton-Jones
I hope that represents agreement rather 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

Int vs Integer

1998-09-15 Thread Simon Peyton-Jones
There's been quite a bit of mail about the Int vs Integer thing. Here's what I conclude: * Integer should be the *default* integral type. That is, if you say (length xs > length ys), where the type at which length is computed is ambiguous, then that type should default to Integer. * The Int ty

RE: Int vs Integer

1998-10-06 Thread Simon Peyton-Jones
> As a plain, ordinary punter could I ask for one of two things: > >1) More or less kill Int as a general-purpose type and > adopt unbounded > integers (Integer) as the standard integral type. > >2) Stay with the current situation. > Following quite a bit of discussion a

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

Haskell 98

1998-10-15 Thread Simon Peyton-Jones
it is.) The proposed decisions are at http://research.microsoft.com/Users/simonpj/Haskell/haskell98.html Comments to me directly ([EMAIL PROTECTED]), or the Haskell mailing list. Simon Peyton Jones

RE: Haskell 98

1998-10-21 Thread Simon Peyton-Jones
> So '---' is not a valid operator symbol, but '-->' is. A line > of hyphens of > any length introduces a comment. > > > ] I do not understand the example: if every lexeme consisting of two > ] or more hyphens begins a comment, `-->' begins a comment! No, '-->' does not consist of two or more

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 th

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.0

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 the

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 > Ye

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 > nam

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 q

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... > mfa

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 happ

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

Two prelude/library matters

1998-11-06 Thread Simon Peyton-Jones
I have three small (and late) prelude/library proposals to add: 1. The Show class ~~ One of the first things proposed when StdHaskell started was to make it possible to make a type an instance of Show by defining 'show' rather than by defining 'showsPrec'. More elaborate things

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 > > Y

Haskell 98: getting there

1998-11-09 Thread Simon Peyton-Jones
Folks, I want to thank everyone who's contributed to the Haskell 98 discussion; it's been very helpful to me. However, to save the bandwidth of those who are less interested, pls consider replying direct to me, and other contributors on a particular topic, where the focus is narrow. (I'd start

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: Haskell 98: getting there

1998-11-09 Thread Simon Peyton-Jones
> This message summarises where we are. The web page > http://research.microsoft.com/Haskell/haskell98-final.html > is up to date. I am sorry to be so careless. The URL should be http://research.microsoft.com/Users/simonpj/Haskell/haskell98-final.html Simon

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: Haskell 98 progress...

1998-11-23 Thread Simon Peyton-Jones
> I REALLY dislike the idea of having my comments lexed. Can't we leave > this part of the language spec alone? OK, ok, ok. I am suitably berated and I yield. * Comments *start* with a lexeme, as previously discussed, and I think this is fine. * The opening lexeme may be '--', '---' etc

Haskell 98 draft report

1998-11-23 Thread Simon Peyton-Jones
Folks, I have now completed the draft report on Haskell 98, both language and libraries. I have dated them both 'Draft: 1 Dec 1998'. You can find them at http://research.microsoft.com/users/simonpj/Haskell/haskell98.html There's an allegedly-complete list of changes, along with the re

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... g

Why I hate n+k

1998-11-27 Thread Simon Peyton-Jones
Just to amuse you all, here's a quick Haskell 98 quiz: What do the following definitions do: 1 x + 1 = f x 2 (x + 1) = f 2 3 (x + 1) * 2 = f x 4 (x + 1) 2 = g x That's right! (1) partially defines (+). One could add more equations, thus: x + 1 = f x

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

RE: ANNOUNCE: GHC version 4.01

1998-12-01 Thread Simon Peyton-Jones
[Please consider taking followups to [EMAIL PROTECTED]; this stuff is system specific (and was discussed here recently.) -moderator] > I remember there was uncertainty on the terms for use, modification > and distribution. Was this addressed: ie. is there a license covering > these terms and con

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 f

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: Haskell 98 draft report

1998-12-02 Thread Simon Peyton-Jones
> 3.11 (restricting monad comprehensions to list comprehensions) > Generally I don't like to lose generality without a strong > necessity. Can someone refer me to the rationale for that change? > I've found only a reference that there can be confusing (for people > in the process of learning Haske

RE: library for bitwise operation?

1998-12-04 Thread Simon Peyton-Jones
You could also try the GHC/Hugs extension libraries http://www.dcs.gla.ac.uk/fp/software/ghc/lib/hg-libs.html There's a Bits library in there. These libraries are supported by GHC and Hugs. Simon > -Original Message- > From: Wishnu Prasetya [mailto:[EMAIL PROTECTED]] > Sent: Th

RE: Efficiencies of containers

1998-12-04 Thread Simon Peyton-Jones
> Well, this was only my understanding and was qualified as > one of the things that were not clear to me. I still > have my doubts and I would really like to find some > authoritative answer instead of heresays about slugishness > of Haskell arrays that I see here a

Random library

1998-12-04 Thread Simon Peyton-Jones
Folks, Thank you for lots of input on the random library. If we can evolve a sensible proposal fast then we can put it in Haskell 98. I propose that we discuss this among the people who have already contributed, rather than saturate the main Haskell list further. The union of contributors is in

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) => > >

Haskell 98 -- status

1998-12-11 Thread Simon Peyton-Jones
Gentlefolk, Haskell 98 is gettting there. Draft version 3 of both Language and Library Reports are on the Web now, along with an updated 'complete list of changes'. http://research.microsoft.com/users/simonpj/Haskell/haskell98.html I decided a few things I'd previously canvassed opinio

RE: Haskell as a relational database language

1998-12-15 Thread Simon Peyton-Jones
Don't forget to read about CPL and Kleisli http://sdmc.krdl.org.sg/kleisli/limsoon.html Simon > -Original Message- > From: Tom Pledger [mailto:[EMAIL PROTECTED]] > Sent: Tuesday, December 15, 1998 12:17 AM > To: [EMAIL PROTECTED] > Subject: Haskell as a relational database langu

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 r

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 () > > | otherwi

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 vo

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 thi

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 their

RE: on Haskell-98

1999-01-04 Thread Simon Peyton-Jones
> FiniteMap > implemented via balanced binary trees. > Such a useful thing - has not it to move to the Standard library? > To my mind, it is more important for Haskell than arrays. Perhaps, but I'm not willing to add anything to the library at this stage. Two months ago maybe. Now, no. > Stan

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.

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

PS

1999-01-28 Thread Simon Peyton-Jones
I propose to remove Show (IO a) as well as Show (a->b), for the same reason Simon

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: 3 small questions

1999-01-28 Thread Simon Peyton-Jones
> 1. > Haskell-98 description > - is it ready to print as the final, accepted and approved document? Design frozen: but I'm working right now on the actual final document. > class Num' a where add,sub :: a -> a -> a > neg :: a -> a > sub x y = a

RE: Query re gcd() in Haskell 98

1999-02-01 Thread Simon Peyton-Jones
x27;re past that point. Simon > -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 ra

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 libraries

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 l

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 t

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 >

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 conside

FW: GHC & Hugs | TREX & FFI Status?

1999-03-30 Thread Simon Peyton-Jones
> I would like to know that anything I do in hugs is portable to GHC. > It seems like the two main big differences between the two > are TREX and the FFI (is there more?). > Is there a plan for GHC to support TREX? > What is the status of support for the new FFI? Yes, the FFI will be supported b

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 ] '? I'm all for this (in addition to, not instead of, the current

RE: Plea for Change #1: Why, O why, `Main'?

1999-03-30 Thread Simon Peyton-Jones
Suppose there are three modules, all defining 'main': A.main, B.main, C.main. Which is to be treated as 'the' main? And if the module shouldn't be called 'Main' why should the value be called 'main'? Maybe you want ghc *.o -main A.wibble to treat A.wibble as the main function. But the

RE: question?

1999-04-06 Thread Simon Peyton-Jones
> so I want to create a proper set of linear algebra tools to > write a ray-tracer > in haskell, this includes a few types, a Point and a Vector > both of which can be > represented by 3 Floats, I would like the following operations.. > Vector+Vector = Vector > Point + Vector = Point > Point + P

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 c

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

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 n

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 star

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 >

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

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

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 forge

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 (unde

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 h

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

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 >

RE: Field names

1999-07-02 Thread Simon Peyton-Jones
You're right. I the report is reasonable too. One might want to say data Wib = Wib { (#) :: Int -> Int } and then say f :: Wib -> Int -> Int f w i = w # (i+2) Although it seems odd for a selector to be infix, it works rather well in situations like this. We'll fix GHC. Simon > -Origin

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 t

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

RE: Haskell 98

1999-07-13 Thread Simon Peyton-Jones
> Permission is granted by the authors to copy and > distribute this Report for any purpose, provided only that it is > reproduced in its entireity, including this Notice. Modified > copies of this Report may be copied and distributed for > any purpose, > provided that the co

RE: Haskell 98

1999-07-13 Thread Simon Peyton-Jones
l any more bugs have crept out. Death to revision 2. Opinions welcome. Simon > -Original Message- > From: Ross Paterson > Sent: Tuesday, July 13, 1999 2:05 PM > To: Simon Peyton-Jones > Cc: 'Antti-Juhani Kaijanaho'; 'Haskell list' > Subject: Re: Hask

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 diagonali

RE: Importing, hiding, and exporting

1999-07-26 Thread Simon Peyton-Jones
> I'm totally > confused. What does > >module M1(module M2) >import M2 hiding (H) >... > > exactly mean? The intention is this: M1 exports everything that M1 imports from M2. Since H is not imported, it should not be exported either. It does not make any difference whether or not

RE: Haskell 98 Report: do expression syntax

1999-07-26 Thread Simon Peyton-Jones
That seems extremely reasonable. I propose to treat it as a Haskell98 typo; it doesn't change the meaning of the language as described by the current report, since no meaning is given to do {} and friends. Does anyone think there is a reason *not* to do this? Simon > -Original Message---

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 eq

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 t

RE: Clarifying Defaults

1999-07-27 Thread Simon Peyton-Jones
> Current versions of Hugs 98 avoid this problem by adding an > extra, implicit > condition to the definition of defaulting, marked with * in the > following: > > If "v" is an ambiguous variable, and > if "v" appears only in constraints of the form "C v", and * > if one of "v"

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) >

  1   2   3   4   5   6   7   8   >