Re: Modules again

1992-02-17 Thread Simon L Peyton Jones
| Well, here's another problem I've encountered. Consider this module: | | module M(T) where | data T = T | | Is this legal? Clearly I am just trying to export the type T, but it happens | that the type has a constructor with the same name. Naming a constructor | in the export list

Postgraduate research in FP at Glasgow

1996-02-01 Thread Simon L Peyton Jones
Postgraduate research in FUNCTIONAL PROGRAMMING at the University of Glasgow OK, you *could* do buzzword-compliant programming for company X on their test harness for their test rig for the GTI (General Toaster Interface). You'd make a g

Re: Anarchy and Sets: Restoring Abstraction in GHC

1995-11-17 Thread Simon L Peyton Jones
| The problem, I think, stems from the need for *efficient implementation* | which has unfortunately totally destroyed the abstraction. You're quite right of course. Actually there's a hierarchy of increasingly constrained implementations sets with element equality only sets

Re: Modules and interfaces

1995-09-27 Thread Simon L Peyton Jones
The goal of having a human-written interface is to give the programmer the opportunity to say (and document) just what the interface of a module is. I think of this as analogous to specifying a type signature for a function... often illuminating, but should not be obligatory. Especially when w

Modules and interfaces

1995-09-24 Thread Simon L Peyton Jones
This message makes some proposals about the module system for Haskell 1.3. I'm circulating it to the full Haskell list in the hope that we may get some new ideas that way. One thing I would really like to know from the Great Haskell Public is how pressing a problem the module system is. How

Re: Haskell 1.3 (newtype)

1995-09-14 Thread Simon L Peyton Jones
Phil says: | I think its vital that users know how to declare a new isomorphic | datatype; it is not vital that they understand strictness declarations. | Hence, I favor that | | newtype Age = Age Int | data Age = Age !Int | | be synonyms, but that both syntaxes exist. | | This i

Re: Haskell 1.3 (newtype)

1995-09-13 Thread Simon L Peyton Jones
Lennart writes: | So if we had | | data Age = Age !Int | foo (Age n) = (n, Age (n+1)) | | it would translate to | | foo (MakeAge n) = (n, seq MakeAge (n+1)) | | [makeAge is the "real" constructor of Age] | | Now, surely, seq does not evaluate its first argument when the |

Re: Haskell 1.3 (newtype)

1995-09-12 Thread Simon L Peyton Jones
Phil writes: | By the way, with `newtype', what is the intended meaning of | | case undefined of Foo _ -> True ? | | I cannot tell from the summary on the WWW page. Defining `newtype' | in terms of `datatype' and strictness avoids any ambiguity here. | | Make newtype equivalent to a

ANNOUNCE: Glasgow Haskell 0.26 release

1995-07-25 Thread Simon L Peyton Jones
The Glasgow Haskell Compiler -- version 0.26 We are proud to announce a new public release of the Glasgow Haskell Compiler (GHC, version 0.26). Sources and binaries are freely available by anonymous FTP and on the World-Wide

Re: Happy New Year!

1995-02-05 Thread Simon L Peyton Jones
This is a response to Paul's "State of Haskell" message. Maybe everyone is busy writing Haskell programs --- nobody's said a word! Simon | So what have we learned? What's wrong with Haskell, and what's right? | What's in store for Haskell in the future? | | I'd like to engage in some dialo

Haskell vs C

1995-01-09 Thread Simon L Peyton Jones
Folks, We're trying to do a "Haskell vs anything-else (preferably C)" study. We're interested both in their size and structure, and in their performance. We intend to make quite detailed comparative measurements of their performance. Do you have programs we could have a look at? We

Glasgow Haskell 0.23 released

1994-12-21 Thread Simon L Peyton Jones
The Glasgow Haskell Compiler -- version 0.23 A new public release of the Glasgow Haskell Compiler is now available (GHC, version 0.23). Binaries and sources are freely available by anonymous FTP; details below. Haskell is "

FPCA: topics

1994-12-08 Thread Simon L Peyton Jones
Folks, I've added a list of topics to the WWW page for FPCA '95. If you specify what topic(s) your paper covers, I'll have a better chance of assigning your paper to appropriate referees. Doing so is strictly optional, however. Details at URL: ftp://ftp.dcs.glasgow.ac.uk/pub/fpca95/

Glasgow Haskell 0.22 released

1994-07-28 Thread Simon L Peyton Jones
The Glasgow Haskell Compiler -- version 0.22 A new public release of the Glasgow Haskell Compiler is now available (GHC, version 0.22). Binaries and sources are freely available by FTP; details below. Highlights of what's n

Records and type classes

1994-05-16 Thread Simon L Peyton Jones
Here's a thought, engendered by a glass of beer in the Lamplighter's pub in Gastown, Vancouver by John Hughes, Lennart Augustsson, and Simon PJ: type classes can model extensible records. Suppose we want to define a record for a person: record Person = { Age : Int; Weight : In

Re: haskell

1994-02-25 Thread Simon L Peyton Jones
Like Gofer, Glasgow Haskell has a three-way comparison operation in the Ord class, _cmp :: a -> a -> _TAG where data _TAG = _LT | _EQ | _GT (The underbars are to avoid polluting the programmer's name space.) I'd be glad to add this to Haskell. Partial orderings are a separ

Re: Polymorphic recursion

1994-01-06 Thread Simon L Peyton Jones
| From: Sebastian Hunt <[EMAIL PROTECTED]> | Date: Thu, 9 Dec 1993 16:00:13 GMT | In the interests of keeping things (ie, the haskell type system) | as simple as possible, I would vote (if I had a vote) against this | proposal. Unless, of course, I was persuaded that the extension was | Really

Glasgow Haskell 0.19 released

1993-12-17 Thread Simon L Peyton Jones
The Glasgow Haskell Compiler -- version 0.19 "What a great system!" The third public release of the Glasgow Haskell Compiler is now available (GHC, version 0.19). Binaries and sources are freely avail

State in functional languages

1993-12-14 Thread Simon L Peyton Jones
The following four related papers, all on the topic of mutable state in non-strict functional languages, are available by FTP. The first two are as yet unpublised; the last two are published. I'm posting this to the types mailing list as well as the functional programming ones because there

Polymorphic recursion

1993-12-09 Thread Simon L Peyton Jones
Dear people interested in Haskell 1.3, One modest extension we could make to the Haskell type system is to permit polymorphic recursion if a type signature is provided The standard Hindley-Milner restriction is that a recursive function can only be called monomorphically in i

Re: Making argv a constant

1997-01-16 Thread Simon L Peyton Jones
Folks I agree with Sigbjorn about argv, rather strongly, though apparently nobody else does. The Glasgow Haskell Compiler used to deal with command-line arguments in the way mandated by Haskell 1.3; that is, we did a getArgs at the beginning and then passed the arguments everywhere. I recently

Re: stdin as a constant

1997-01-16 Thread Simon L Peyton Jones
| What you want is allowed. Although stdin *is* a constant, it's simply a | constant that refers to a handle. The handle information (file pointer, | attached device etc.) needn't be constant. It's entirely consistent to | provide, say: | | reconnect :: Handle -> Handle -> IO Handle |

Re: Making argv a constant

1997-01-16 Thread Simon L Peyton Jones
| Maybe the symbol table isn't passed around to all dark corners though. Dead right it ain't. There are plenty of places you don't need a symbol table. | Anyway, what it seems to me you lose by doing it the way you described | is that you are stuck again if some day you want to set those flags

Re: Making argv a constant

1997-01-17 Thread Simon L Peyton Jones
at code | runs. Give me the machinery to do that!" To: [EMAIL PROTECTED] (Kevin Hammond) cc: [EMAIL PROTECTED], simonpj Subject: Re: stdin as a constant Date: Thu, 16 Jan 1997 11:07:19 -0800 From: Simon L Peyton Jones Content-Type: text Content-Length: 1859 | What you want is allowed.

Re: Making argv a constant

1997-01-17 Thread Simon L Peyton Jones
My, what a firestorm! The Haskell mailing list springs to life. Frank writes | First, Simon, I think you're a little biased on this issue. I'm sure that | making argv a global constant would be a practical benefit for programs like | GHC. You're probably right. I am certainly biased towar

Re: Making argv a constant

1997-01-17 Thread Simon L Peyton Jones
Fergus | I would find Simon's arguments more convincing if he showed | a convenient idiom that did things properly, rather than a | convenient way to write broken programs. | | (Doing it properly is probably not too hard, but I'll leave it up to | the proponents of this proposal to demonstrate

Re: Making argv a constant

1997-01-28 Thread Simon L Peyton Jones
Claus writes: | Let me see if I understand the rules of this firestorm game: You have | to repeat your ideas some times to push them through the competition?-) Actually I think that is a poor way to proceed. That is why I have stopped sending on this topic --- I have already said what I think

Re: global type inference

1997-02-25 Thread Simon L Peyton Jones
| Why muddle implementation with language design? Pick a design that | we know everyone can implement -- e.g., exported functions must have | type declarations -- and stick to that. When the state of implementations | improve, the specification for Haskell 1.5 can change accordingly. -- P Act

Advance programme: ICFP'97 and PEPM'97

1997-02-27 Thread Simon L Peyton Jones
| | | International Conference on Functional Programming (ICFP97) | | Symposium on Partial Evaluation and Program Manipulation (PEPM97)| |

Re: polymorphic higher-order terms

1997-03-13 Thread Simon L Peyton Jones
| > data F = MkF t -> t -- did I get the syntax right? | Almost | data F = MkF (t -> t) | > | > foo :: (Int, String, F) -> (Int, String) | > foo (i, s, MkF f) = (f i, f s) | | In fact, this extension has been implemented in Hugs | and ghc as well as I understand it, but

Re: haskell operator precedence

1997-03-18 Thread Simon L Peyton Jones
| However, in return, perhaps somebody can supply me with parse trees for | the following: | | - - 1(accepted by nhc and hbc) | (- 1 `n6` 1) where infix 6 `n6` (accepted by nhc, hbc, ghc) | (- 1 `r6` 1) where infixr 6 `r6` (accepted by nhc, hb

Re: reading numbers

1997-03-20 Thread Simon L Peyton Jones
This is a bug in GHC 2.01 (and 0.29 I think). We'll fix it in 2.02. (But that means taking a few more hours to rebuild the 2.02 builds that are about to go out of the door :-). Simon | A couple of my colleagues are using Haskell to implement a simple desk | calculator but they have run into a

The Glasgow Haskell Compiler -- version 2.02

1997-03-26 Thread Simon L Peyton Jones
The Glasgow Haskell Compiler -- version 2.02 We are pleased to announce the first release of the Glasgow Haskell Compiler (GHC, version 2.02) for *Haskell 1.4*. Sources and binaries are freely available by anonymous FTP and

Jobs available at Glasgow

1996-05-30 Thread Simon L Peyton Jones
The Glasgow Computing Science Department is seeking two new members of academic (i.e. faculty) staff, one permanent (i.e. tenured) and the other temporary. I am very keen to attract excellent researchers to the department, especially ones interested in language design and implementation (and mos

Re: Adding attribute grammar syntax to Haskell

1996-07-11 Thread Simon L Peyton Jones
You've seen the Happy parser generator I assume? It's not a full attribute grammer extension, but it's moving in that direction. | Would it be possible to design a standard attribute grammar | extension to Haskell? This could then be added as an appendix to | the Report, or as a separate ext

Re: Debugging Haskell

1996-07-12 Thread Simon L Peyton Jones
| a feeling of frustration around here. So here is my question: | |How do people out there debug Haskell programs??? | | Please note that I am not talking about toy programs of a few dozen | lines. How do e.g. the people at Glasgow find the bugs in GHC (which is | a fairly large Haskell pro

ANNOUNCE: Glasgow Haskell 2.01 release (for Haskell 1.3)

1996-07-26 Thread Simon L Peyton Jones
The Glasgow Haskell Compiler -- version 2.01 We are pleased to announce the first release of the Glasgow Haskell Compiler (GHC, version 2.01) for *Haskell 1.3*. Sources and binaries are freely available by anonymous FTP and

Re: Type inference bug?

1996-10-21 Thread Simon L Peyton Jones
This type error comes up such a lot that I'm copying this message to the Haskell mailing list. | The following program does not typecheck under ghc-2.01 unless you | uncomment the type signature for test. (ghc-0.29 seems to propagate | the equality attribute correctly, and doesn't require the a

ICFP'97: update and final call for papers

1996-10-22 Thread Simon L Peyton Jones
International Conference on Functional Programming (ICFP'97) 9-11 June 1997, Amsterdam http://www.fwi.uva.nl/research/func/icfp97.html

Re: ICFP'97: update and final call for papers

1996-10-23 Thread Simon L Peyton Jones
Of course this should be 14 Feb '97! Simon | > Deadline [URLs below] | > ~ | | > Haskell workshop14 February 1996 | | '97? Or is this a Very Dead Line?

A pretty-printing library

1997-04-25 Thread Simon L Peyton Jones
Folks, Many of you will know of John Hughes pretty printing library [1]. I recently extended it with two new features: * An "empty document" which is a unit for all the composition operators. In practice this is tremendously useful. * A "paragraph fill" combinator.

A new view of guards

1997-04-28 Thread Simon L Peyton Jones
A new view of guards Simon Peyton Jones, April 1997 This note proposes an extension to the guards that form part of function definitions in Haskell. The increased expressive power is known (by me anyway!) to be useful. The ge

Type classes

1997-04-09 Thread Simon L Peyton Jones
Folks, There's often been quite a bit of discussion on the Haskell mailing list about extensions of type classes. Erik Meijer, Mark Jones and I have written a draft paper that explores the type-class design space, discussing the various design decisions one must make, and their consequences. (

The class Ix

1992-02-06 Thread Simon L Peyton Jones
RFC-822-HEADERS: Original-Via: == Folks, I have realised that the class Ix is under-documented in the Haskell Report. I propose to add the following: New section 6.9.1 "The Class Ix". (Renumber subsections in 6.9). ~ Arrays may be subscripted b

Re: Literate comments

1992-02-06 Thread Simon L Peyton Jones
I'd be happy with this, as an appendix, but I'd rather not change any of the report's presentation. To do so consistently would be difficult, and it adds little to the Prelude appendices which are basically all code anyway. Now, for Joe and Paul's tutorial, yes! I wonder if you could also work

Re: Modules again

1992-02-19 Thread Simon L Peyton Jones
| > This one is easy (I think) (for a change). The module above is quite legal, | > and exports the type T but not the constructor. If you wanted the | > constructor to go too, you can write | > | > module M( T(..) ) | > | > or | > | > module M( T(T) ) | But, but, but, how can you say

The last (sic) bug in the Prelude

1992-02-27 Thread Simon L Peyton Jones
I thought this message from Joe should have wider circulation. Someone out there must have good ideas about this! Simon --- Forwarded Message Date:Thu, 27 Feb 92 01:38:44 -0700 From:[EMAIL PROTECTED] (Joe Fasel) To: [EMAIL PROTECTED], [EMAIL PROTECTED], kh, [EMAIL PRO

Re: Modules one more time

1992-03-23 Thread Simon L Peyton Jones
Lennart You are absolutely right about this. It is a bug, but for the reason you describes, not a disastrous one. It should be cleaned up in Haskell 2 (ha!). Simon | From: Lennart Augustsson <[EMAIL PROTECTED]> | Date: Fri, 10 Jan 92 21:57:44 +0100 | | | I have some problems with modules aga

The Spineless Tagless G-machine: detailed paper

1992-04-15 Thread Simon L Peyton Jones
file PAPER_LIST. Simon PJ, University of Glasgow. Implementing lazy functional languages on stock hardware: the Spineless Tagless G-machine Version 2.4 Simon L Peyton Jones, University of Glasgow The Spineless Tagless G-machine is an a

Re: Pattern Binding

1992-05-29 Thread Simon L Peyton Jones
There are two issues going on here. 1. Should pattern variables be permitted in the guard? ^^ Haskell's reply: yes, but the result is always bottom. After all, - you need to evaluate the guard to discover which RHS to

Haskell status

1992-07-13 Thread Simon L Peyton Jones
Now that the Haskell report has appeared in SIGPLAN Notices, it seems like a good time to broadcast the current status of Haskell implementations. Below appears an up-to-date summary of implementations known to me. If there are other implementations about, please let me know! Simon Peyton Jon

Re: Semantics of Irrefutable Pattern Matching

1992-07-23 Thread Simon L Peyton Jones
Namrata asks... | So, when x1' + x2' is evaluated, | Is (1,2) pattern matched against (a,b) twice -- once for x1' and once | for x2' ?? The translation you give (correctly I think) expresses the required *semantics*. But the translation is not the required *implementation*. A compiler can do

Job available at Glasgow

1992-08-05 Thread Simon L Peyton Jones
Haskell implementor wanted ~~ Dept of Computing Science, Glasgow University We have a vacancy for a Research Assistant (USA, read "Research Associate") to work on implementations of the functional language Haskell for both s

Re: importing derived functions

1992-11-30 Thread Simon L Peyton Jones
| From: Stephen J Bevan <[EMAIL PROTECTED]> | Date: Fri, 27 Nov 92 12:07:04 GMT | | | Is it possible to import a type and the derived "show" function for it | without having to import all the type's constuctors? For example, in | the following I attempt to import just Lexeme into Token as th

Re: Another import question

1992-12-03 Thread Simon L Peyton Jones
Why do you need to drop the (..) when it turns into a "data" decl? You only need do so if you want it to be abstract! But "type" decls can't be abstract; the (..) reminds you of this. Some of us have been musing on how to provide an abstract version of "type" too, but that didn't get into the la

Re: Another import question

1992-12-18 Thread Simon L Peyton Jones
| For example, | | module F(S,T) where | type S a = (a,a) | data T a = C a a | | could have the interface: | | interface F where | type S a | data T a | | Are there any problems with this? The main difficulty is deciding whether the signatures in the int

Haskell implementation status summary

1993-02-23 Thread Simon L Peyton Jones
Here, for your interest, is a freshly-updated summary of the current state of Haskell implementations, at least those known to us. Simon Peyton Jones, Glasgow University. Haskell: Current status [Simon Peyton Jones wrote the original v

Re: general update notation

1993-04-27 Thread Simon L Peyton Jones
People reading the update-notation thread might also be interested in "Imperative functional programming" Peyton Jones & Wadler, POPL 93 which you can grab by ftp fromftp.dcs.glasgow.ac.uk in pub/glasgow-fp/papers/imperative.ps.Z The paper mainly deal

Re: Successor patterns in bindings and n+k patterns

1993-05-19 Thread Simon L Peyton Jones
I agree with everything Paul says, about translations, and about Norman's point. I'll record them in my things-to-improve-in-the-next-iteration-of the-Report file... Incidentally, I also do not like n+k patterns, but they don't seem to be a big issue to me, either from a semantic or implementa

Re: n+k patterns, etc.

1993-05-20 Thread Simon L Peyton Jones
|What if (the appropriate parts of) the standard prelude is | explicitly *not* imported: | | import Prelude () | or | import Prelude hiding(map) | | (see section 5.4.3). | |Are then the hidden parts of the standard prelude still available via | n+k patterns, list comprehen

Proposed change to Core

1993-07-26 Thread Simon L Peyton Jones
This message is directed specifically at people who are interested in the *internals* of the Glasgow Haskell compiler. If you aren't, then just delete this message. We don't have an exhaustive list of all ghc-internals users, which is why this message is going to the Haskell mailing list. Sim

Lifted products

1993-10-05 Thread Simon L Peyton Jones
I don't like Phil's suggestion to have non-lifted products: * It messes up the uniform semantics for algebraic data types (all lifted). For example a) You have to explain that f ~(z,a) = ... is the same as f (z,a) = ... but g ~(z:a) = ... is NOT the sam

ADTs and strictness

1993-10-05 Thread Simon L Peyton Jones
(This message assumes we head for the strictness-annotation-on-constructor-arg solution. I'll respond to Phil's comments in my next msg.) The problem with polymorphic strictness ~~~ John asks what the problem is with strict constructor args. As Lennart and K

ADTs in Haskell

1993-10-01 Thread Simon L Peyton Jones
Gentle Haskell-1.3 people, This message argues for a particular approach to abstract data types in Haskell. The problem ~~~ We have long been a bit unhappy with Haskell's treatment of abstract data types. It's easy to make a new algebraic data type abstract, just by not exporting its c

Type signatures

1993-10-05 Thread Simon L Peyton Jones
Folks, Warren Burton makes what appears to me to be a Jolly Sensible suggestion about the syntax of type signatures. Haskell already has many dual ways of doing things (let/where, case/pattern-matching). Warren proposes an alternative syntax for type signatures. Simon --- Forwarded Mess

Lifted functions

1993-11-04 Thread Simon L Peyton Jones
I think we should be pretty cautious about jumping in with lifed function spaces. I have come up with two distinct unintended effects. While neither is fatal to the idea, I don't think either obvious, and I am nervous that others may pop out of the woodwork somewhere down the road (to mix meta

Liftedness again

1993-11-05 Thread Simon L Peyton Jones
Warren makes an excellent point, though he doesn't highlight it: unlifted tuples are INCOMPATIBLE with seq By "incompatible" I mean that you need parallel specualative evaluation to implement it. So a truly polymorphic seq is out. That takes us back to an overloaded version, except t

Re: A new view of guards

1997-04-29 Thread Simon L Peyton Jones
| We can avoid both the case expressions and the helper function by Simon | Peyton Jones' guard syntax | | -- version 3 | simplify (Plus e e') | s <- simplify e , |s' <- simplify e', |(Val 0) <- s | = s' |

Re: pattern guards and guarded patterns

1997-04-30 Thread Simon L Peyton Jones
Thanks for feedback about pattern guards. Here are some quick responses. 1. Several people have suggested something along the lines of being able to backtrack half way through a pattern guard. I considered this but (a) I couldn't see a nice syntax for it and (b) it's against the spirit of

Re: Monads, Functors and typeclasses

1997-05-12 Thread Simon L Peyton Jones
Koen suggests: | The solution is real easy: To express the necessity of a Monad to be a | Functor, change the definition of the class Monad as follows: | | class Functor m => Monad m where | ... When to make one class into a superclass of another is a rather tricky matter of judgement:

Pattern guards

1997-05-13 Thread Simon L Peyton Jones
The discussion about pattern guards has raised two interesting and (I think) independent questions: - Nested guards - Maybes and monads Here are my thoughts on these things, typed 30,000 feet above Utah! Simon Nested guards ~~ Several people have pointed out that

Re: Deriving class instances

1997-05-14 Thread Simon L Peyton Jones
Olaf Noel Winstanley has a Haskell preprocessor that does more or less what you want. [EMAIL PROTECTED] Simon | From: Olaf Chitil <[EMAIL PROTECTED]> | Date: Wed, 14 May 1997 16:24:59 +0200 | Why is the automatic derivation of instances for some standard classes | linked to data and n

Re: Pattern guards

1997-05-14 Thread Simon L Peyton Jones
| > For example, in this case we could write (rather less elegantly) | > | > g2 a | (x:xs) <- h a, (y:ys) <- h x = if y<0 then e1 | >else if y>0 then e2 | >else e3 | > | > To avoid this difficulty with functions l

Re: Pattern guards

1997-05-15 Thread Simon L Peyton Jones
| > f c | (i,j) <- Just (toRect c) = ... | | I'm afraid this example suffers from the same problem as my "simplify" | example did: It does not perform a test and can thus be replaced by | | f c = ... | where (i,j) = toRect c True. I can think of two non-contrived ways in which this

Re: pattern guards + monads

1997-05-15 Thread Simon L Peyton Jones
| On pattern guards, Simon PJ writes: | > f (x:xs) | x<0 = e1 | > | x>0 = e2 | > | otherwise = e3 | | then | > g a | (x:xs) <- h a, x<0 = e1 | > | (x:xs) <- h a, x>0 = e1 | > | otherwise = e3 | | Am i right in thinking that f [] is bottom, whilst g [] is e3?

No Subject

1997-05-20 Thread Simon L Peyton Jones
| 1.- In the version 1.2 there is a restriction that a C-T instance declaration | may only appear either in the module where C or T are declared, but in | the version 1.3 this restriction does not appear. What is the reason for | the change? Why is the restriction in 1.2 at all?

Re: Working with newtype

1997-05-29 Thread Simon L Peyton Jones
| I have a small question about defining functions over types declared | with "newtype". Consider the following: | |newtype MyList a = MyList [a] | |myMap1 :: (a -> b) -> MyList a -> MyList b I would say myMap f (MyList xs) = MyList (map f xs) | Perhaps there is no elegant s

Re: Using `newtype' efficiently

1997-06-25 Thread Simon L Peyton Jones
| My question is: how much is this redundancy going to cost? Clearly the | lambda abstraction is just id, but less obviously (pEmbed (\x->LABEL | x))is now also id. Presumably none of the Haskell compilers can figure | this out though? It should cost you practically nothing with a compiler at

Re: Haskell 1.4 Prelude bug

1997-07-24 Thread Simon L Peyton Jones
There's a Haskell 1.4 report bug list at http://haskell.systemsz.cs.yale.edu/report/bugs.html John Peterson puts the entries in, but it's really up to others to write the entry. Would you like to document the bugs you've found along with the fixes and send an entry to John? It would

GHC status

1997-07-24 Thread Simon L Peyton Jones
[I originally sent this message to glasgow-haskell-users and glasgow-haskell-bugs, but it occurred to me that it might be of more general interest, so I'm sending it to the Haskell mailing list too.] Dear GHC users and co-implementors We are about to return from sabbatical in Oregon back to Gl

Re: what's wrong with instance C a => D a

1997-08-22 Thread Simon L Peyton Jones
> The report says explicit that instance declarations like > instance C (a,a) where ..., or for (Int,a) or for [[a]] are not > I now only would like to know why this design decission was made, > are there any problems with the instance declarations I have in mind? You might find "Type classes -

Re: Standard Haskell

1997-08-25 Thread Simon L Peyton Jones
> In fact, I would like to hear what all the major implementors have as their > picture of a final version of Haskell. You've all been pretty quiet. > I assume you've all already aired your opinions at the workshop, but it would > be nice to see them here as well. Reasonable request. I hope tha

Re: Evaluating Haskell

1997-08-27 Thread Simon L Peyton Jones
David > 1) JAVA -- Are there any plans to compile Haskell into byte codes for > execution on the Java Virtual Machine? The Java issue is very important. I know of a couple of prototypes of such a thing, one at Yale, and one at Nottingham. It is clearly do-able. It's pretty heavyweight, though

Re: Another question about monads and linearity

1997-09-04 Thread Simon L Peyton Jones
> There are few formal connections between monads and > single-threaded state... For any state-transformer monad... there > is a trivial operation... that will instantly destroy any hope for > single-threadedness: getState s = (s, s) > > In day-to-day Haskell 1.3 programming what

Re: Numeric conversions

1997-10-01 Thread Simon L Peyton Jones
> > real2frac :: (Real a, Fractional b) => a -> b > > real2frac = fromRational . toRational > > The composition of fromRational and toRational seems to be the > only way to convert a Double or an Int to a Double. > > There is a function in the prelude, fromRealFrac, with exactly > the same defi

Re: Deriving newtype ADTs from type ADTs

1997-10-01 Thread Simon L Peyton Jones
> However, if the transforming program took into account the information in the > type signature (for unionMany, it would notice that the user used the type > synonym for the inner list only), it could make pretty good guesses about which > arguments and results to unpack or pack. > Since the ad

Re: Importing Prelude

1997-10-14 Thread Simon L Peyton Jones
> The Prelude module is imported automatically into all modules as if > by the statement `import Prelude', if and only if it is not imported > with an explicit import declaration. This provision for explicit > import allows values defined in the Prelude to be hidden from the > unqualif

Re: evil laziness in iteration

1997-11-05 Thread Simon L Peyton Jones
Sergey Thanks for your various messages. I've explained your results below. You are right to say that it's hard to be sure what optimisations will happen when; arguably that's a bad shortcoming of functional programming (especially the lazy sort). Profiling tools help a bit. I think, though, tha

Re: Call for parsers

1997-11-13 Thread Simon L Peyton Jones
> So here is my call for contribution: > >Send an abstract syntax and/or a parser specification! > > It doesn't matter if a parser generator is used or recursive descent > techniques are applied. > > If there is enough echo, I'd like to setup a web page for this > project, containing thing

Re: Overlapping instance declarations.

1997-12-10 Thread Simon L Peyton Jones
> "A type may not be declared as an instance of a particular class more than > once in the program." > > Doesn't it really mean that a type _constructor_ may not appear in more > than one instance declaration for a particular class? That (stronger) > condition seems to be what ghc and hugs impl

Re: Xmas fun

1997-12-20 Thread Simon L Peyton Jones
> This bug could have been caught by a very simple static analysis that > is very popular in the logic programming community: singleton variable > warnings. In the code above, the variable `v2' occurs only once. > Singleton variables such as this are often bugs. For cases where the > programmer

Xmas fun

1997-12-19 Thread Simon L Peyton Jones
Folks, I thought you might find the following bug I've just found in GHC entertaining. In the strictness analyser we need to compare abstract values so that the fixpoint finder knows when to stop. In the middle of this code was the following: sameVal :: AbsVal -> AbsVal -> Bool

Re: Ambiguous Type Error

1998-01-05 Thread Simon L Peyton Jones
> I have enclosed below a test file that causes an error that puzzles > me. Both GHC and Hugs kick it out, so at least they agree; however, I > must admit that I don't understand it. Yes, it is a bit confusing, and it took me a few minutes to see what is going on. Here's your problem: > data (

Re: No field labels?

1998-02-04 Thread Simon L Peyton Jones
> Is there any reason for not allowing: > > > data Test = Test {} > > in Haskell? I can't think of one. Maybe Std Haskell should allow it. I'll put it on the Std-Haskell board. Simon

Re: Binary files in Haskell

1998-02-23 Thread Simon L Peyton Jones
> I would like to use Haskell for several larger scale projects, but I > can't figure out how to read and write binary data. It does not appear > that the language supports binary files. Am I missing something? Colin Runciman and his Merrie Men are working on writing Haskell values into binary

Want a job?

1998-02-24 Thread Simon L Peyton Jones
I'd be delighted if a programming-language-aware person applied for this (tenured) post. Deadline 13 March. Simon Lectureship in Computing Science University of Glasgow The University invites applications for a permanent lectureship in the Department of Computi

Re: Binary files in Haskell

1998-03-11 Thread Simon L Peyton Jones
> Real world example: development tools process a large geometric data set to > build a run-time optimized BSP tree with precalculated lighting and > collision information. The user application will not modify this data, but > it will have to load it dynamically without slowing down a 30Hz > gra

Multi-parameter type classes in GHC 3.01

1998-02-25 Thread Simon L Peyton Jones
> PS. Could somebody inform me what is the current status of > multi-parametric classes? GHC 3.01 supports multi-parameter type classes in more or less the form described in the last section of "Type classes: an exploration of the design space" (http://www.dcs.gl

Re: Multiple Parameter Class in Hugs -- Please!

1998-04-06 Thread Simon L Peyton Jones
> > infixl 7 *$ > > infixl 6 +$, -$ > > class Ring a where > > (+$), (-$), (*$) :: a -> a -> a > > negateR :: a -> a > > fromIntegerR :: Integer -> a > > zeroR, oneR :: a > > It's particularly irritating having to use many of the Num methods and > therefore having to give them different n

Re: binary search

1998-04-16 Thread Simon L Peyton Jones
> 2. how would I have found/fixed such an error in a more complex function > w/o assertions and w/o print statements? Good questions There was a proposal to put assertions into Std Haskell, which we have implemented in GHC. (I'm not sure we've yet put that version out though.) So assert

  1   2   >