Re: some Standard Haskell issues

1998-08-19 Thread Simon L Peyton Jones
> Yes, I think it's a fine idea to loosen up the syntax and allow import and > infix anywhere. But could someone clarify what the intent is with regards to > the scoping of liberally sprinkled imports/infixes? I've added a clarification; my intent was that all import and fixity declarations wou

Standard Haskell

1998-08-04 Thread Simon L Peyton Jones
Folks, I'm writing to say how I hope to progress the Standard Haskell process. I have updated the 'State of play' page http://www.dcs.gla.ac.uk/~simonpj/std-haskell.html It now lists every change that I propose to make for Standard Haskell. I now propose the following plan: * Betwe

Re: Felleisen on Standard Haskell

1998-08-04 Thread Simon L Peyton Jones
> In any case, I hope that Simon will follow his urge to get Standard > Haskell done with Real Soon Now, even if there is no overwhelming > consensus on certain issues, so that we can then concentrate on Haskell > 2. That's just what I intend to do. I don't see Std Haskell as a big deal, but eve

Re: Rambling on numbers in Haskell

1998-08-04 Thread Simon L Peyton Jones
I think all this discussion about numerics in Haskell is great. I'm convinced that designing good libraries is a major creative act, not just an add-on to a language; and that the existence of good libraries has a big effect on how much use a language gets. ('Good' means both having a well-desig

Re: instances in Haskell-2

1998-07-29 Thread Simon L Peyton Jones
> I cannot find there the subject. Could you citate? Sorry, it turns out I missed your point entirely. class (Ring r,AddGroup (m r)) => RightModule m r where cMul :: m r -> r -> m r So here, m :: *->* What you really want is to say instance Ring r => RightModule (\t->t) r where

Re: suggestions for Haskell-2

1998-07-28 Thread Simon L Peyton Jones
> class (Ring r,AddGroup (m r)) => RightModule m r > where > cMul :: m r -> r -> m r > -- "vector" (m r) multiplied by "coefficient" r' > > Haskell rejects this (m r) in the context. Could Haskell-2 allow it? Yes. See http://www.dcs.gla.ac.uk/~simonpj/multi-p

International Symposium on Memory Management: call for participation

1998-07-26 Thread Simon L Peyton Jones
Dear colleague We'd like to invite you to join us at the International Symposium on Memory Management 1998, immediately preceding OOPSLA in Vacouver. Memory management is becomming more and more important these days, and the meeting should be a good chance to find out where it's at, and to meet

Re: Scoped typed variables.

1998-07-22 Thread Simon L Peyton Jones
> I think the way that Hugs 1.3c handles it would meet your goals. All that > it requires is a strict extension to the syntax for patterns to allow type > annotations. These can be useful in their own right, but also can be > applied > to problems like the one that you gave: > > f :: [a] -> a

Re: avoiding repeated use of show

1998-07-22 Thread Simon L Peyton Jones
> I would like to avoid using show all the time for printing strings e.g. > > > val = "the sum of 2 and 2 is "++(show $ 2 + 2)++" whenever." > > I would prefer to type something like: > > > val = "the sum of 2 and 2 is "./(2+2)./" whenever." > > -- i can' find a better haskell compatible opera

Re: instances of types

1998-07-22 Thread Simon L Peyton Jones
> Haskell doesn't seem to allow > > > instance Num (Int->Int) where ... > > or > > > instance Stringable String where ... Haskell requires you to write instances of the form instance context => T a1..an where ... where T is a type constructor and a1..an are type variables. This is

Re: Monomorphism

1998-07-21 Thread Simon L Peyton Jones
> > I'm going to ask a very stupid question. > > Why on earth is len computed twice in this example? I really don't > understand this! I have to confess that I mischievously hoped that someone would say this: it demonstates the point nicely that lifting the monomorphism restriction would ca

Re: GHC licence (was Could Haskell be taken over by Microsoft?)

1998-07-21 Thread Simon L Peyton Jones
> Simon L Peyton Jones wrote: > > So far as GHC is concerned, I wrote on this list a month ago: > > "More specifically, I plan to continue beavering away on GHC. > > GHC is public domain software, and Microsoft are happy for it to > > remain so, source code and al

Re: Monomorphism

1998-07-21 Thread Simon L Peyton Jones
Olaf suggests > Hence I suggest that part (b) of rule 1 of the MR should > be deleted, i.e. simple > pattern bindings are just treated as function bindings. As I have said in a > previous email, the recomputation issue could be handled by warnings from the > compiler. That would indeed not fall

Re: Could Haskell be taken over by Microsoft?

1998-07-21 Thread Simon L Peyton Jones
> It seems that many prominent Haskell people are more or less associated > with Microsoft. It has just been announced that Hugs may go into > Microsoft Developers Studio and Simon Peyton-Jones is about to move to > Microsoft. Is there a risk (or change, if you like) that Microsoft will > eventual

Re: GHC/Hugs Status (was Re: simple interface to web?)

1998-07-17 Thread Simon L Peyton Jones
> But if there are too many things missing, no one will use Standard > Haskell - it already seems as if most of the people on this list are > going to go straight to Haskell 2, which would mean that Standard > Haskell might only be used for teaching. Indeed, I do expect that most of the people o

Re: Monomorphism

1998-07-16 Thread Simon L Peyton Jones
> > read :: Read a => String -> a > > read s = let [(r,s')] = reads s in r > > > > This *won't compile* if you don't treat the let binding definition > > monomorphicly. Without monomorphism, the types of r and s' are > > > > r :: Read a => a > > s' :: Read a => String > > > > This leads to an a

Re: GHC/Hugs Status (was Re: simple interface to web?)

1998-07-15 Thread Simon L Peyton Jones
> More generally, regardless of the standards process, it feels like the > GHC, Hugs define the de facto Haskell standard (it doesn't look like HBC > is still in progress but I could be wrong). As such, it seems tough to > write libraries right now as the upcoming GHC/Hugs release will contain >

Re: GHC/Hugs Status (was Re: simple interface to web?)

1998-07-15 Thread Simon L Peyton Jones
> etc... all seem to be things that are waiting 'till Haskell 2. My > point was that _something_ should be in Standard Haskell. The features > you mention are likely to help when writing a better network library, > but let's not get distracted from the option of including something > straightfor

Re: Instance contexts.

1998-07-13 Thread Simon L Peyton Jones
[I'm taking the liberty of broadening this to the Haskell mailing list. I doubt anyone is on glasgow-haskell-users, where it started, but not on the haskell list.] > > I think this has been discussed before, but I've just run into it myself. > > I have a MPC 'Set', in the usual bog-standard fas

Re: type synonyms

1998-07-09 Thread Simon L Peyton Jones
> That's basically newtype with the data constructor omitted (I would > prefer data to record). Unfortunately, this seems to be incompatible > with the class system. (There was a long discussion on the Standard > Haskell discussion list, unfortunately the entry vanished). No, it just moved over

Re: MPTC: class type variables

1998-07-08 Thread Simon L Peyton Jones
> Well, I have a convincing example (at least it convinces me ;-). > There are several ways to define a type class for finite maps (aka > dictionaries, aka lookup tables). Here is one taken from Chris Okasaki's > book on purely functional data structures (p. 204): I saw Mark yesterday, and have m

Standard Haskell

1998-07-08 Thread Simon L Peyton Jones
Folks This message is to update you on the state of play so far as Standard Haskell is concerned. I'm circulating to three Haskell-related mailing lists; in future I'll mail only the "haskell" list, so pls subscribe to it if you want to see anything more. You may remember that John Hughes has

Re: Multi-parameter type classes

1998-07-01 Thread Simon L Peyton Jones
> |5. In the signature of a class operation, every constraint must > | mention at least one type variable that is not a class type > | variable. Thus: > ... > | > class C a where > | >op :: Eq a => (a,b) -> (a,b) > | > | is not OK because the constrain

Re: type errors

1998-07-01 Thread Simon L Peyton Jones
> | > > class (Eq key, Ord key) => Dictionary dict key dat where > | > > delete :: key -> dict -> dict > | ... > | > the first error: > | > > | > Class type variable `dat' does not appear in method signature > | > delete :: key -> dict -> dict > | > > | > Why does ghc expect tha

Re: type errors

1998-07-01 Thread Simon L Peyton Jones
> > Actually I think you would be better off with a class like > > this: > > > > class (Eq key, Ord key) => Dictionary dict key where > > delete :: key -> dict dat -> dict dat > > search :: key -> dict dat -> (key, SearchResult dat, dict dat) > > searchList :: [key] -> dict dat -

Multi-parameter type classes

1998-06-30 Thread Simon L Peyton Jones
Folks, GHC 3.02 supports multi-parameter type classes, but I have been guilty of not documenting precisely what that means. I've now summarised the extensions, informally but I hope precisely, at http://www.dcs.gla.ac.uk/multi-param.html This includes some changes that aren't in 3.02,

Re: type errors

1998-06-30 Thread Simon L Peyton Jones
> The ghc compiler complains about 2 type errors in the following code: > > > data SearchResult a = Found a | Fail > > > > class (Eq key, Ord key) => Dictionary dict key dat where > > delete :: key -> dict -> dict > > search :: key -> dict -> (key,SearchResult dat,dict) > > searchL

Re: laziness and functional middleware

1998-06-19 Thread Simon L Peyton Jones
> The paper says: > "We are working on a distributed implementation of Concurrent Haskell. > Once nice property of MVars is that they seem relatively easy to implement > in a distributed setting..." > I assume that they are not referring to GPH here. > (I was surprised that at this statement giv

Re: Garbage Collection in GreenCard/RedCard/HaskellCOM

1998-06-17 Thread Simon L Peyton Jones
> I just reread Dima's answer to my query about the database access in > particular and am confused. Dima says that he can't allow queries > outside the IOMonad because he has to worry about freeing memory (query > output). > > However, Haskell/Com (built on top of Greencard?) seems to be able

Re: laziness and functional middleware

1998-06-17 Thread Simon L Peyton Jones
Alex, > > main = do input <- getContents > > putStr $ addTwo $ makeLines input > > > addTwo lines = ask1++(ask2 (Strict x)) ++ (result (Strict y)) > > where x:y:xs = map read lines > > ask1 = "Enter an Integer: " > > ask2 _ = "Enter another Integer: " >

Re: FW: Exceptions are too return values!

1998-06-16 Thread Simon L Peyton Jones
> Simon, I'm sure that a really thorough programmer such as yourself > would never forget to insert such a test. But, as was recently > demonstrated on this mailing list ;-), I'm quite fallible. > I'm sure there are many other fallible Haskell programmers around. Don't worry, I'm fallible all r

Re: FW: Exceptions are too return values!

1998-06-16 Thread Simon L Peyton Jones
> I thought about this problem some more, and I have realized that the > problem of nondeterminacy for Haskell exceptions would in fact be > considerably worse that I had previously considered. The trouble is > that in the general case the problem is not just that the choice of > which exception

Re: FW: Exceptions are too return values!

1998-06-11 Thread Simon L Peyton Jones
> I was keeping quiet myself, because I am planning to write > a paper touching on this topic. But the cat seems to be > mostly out of the bag now, so I might as well pipe up. I'm glad you did. That's a neat idea. I'm familiar with the NDSet idea -- that's in the Hughes/O'Donnell paper that Ke

Re: FW: Exceptions are too return values!

1998-06-11 Thread Simon L Peyton Jones
> Just to reiterate. I strongly urge you to ensure consistent exception > behavior. As a matter of course, two different compiles should not result > in two different programs. One of the wonderful things about functional languages is that they do not prescribe the order of evaluation. To ac

Re: FW: Exceptions are too return values!

1998-06-11 Thread Simon L Peyton Jones
> Another question: Is "handle" strict in the following argument: > > handle :: (IOError -> IO a) -> IO a -> IO a > ^ > (meaning: will "handle f (return bottom)" be bottom?) Good question. No, it's not strict in that sense. Simon

Re: FW: Exceptions are too return values!

1998-06-10 Thread Simon L Peyton Jones
Alastair Reid has been very quiet, so I'll pipe up for him. Here's a reasonable design for exceptions in Haskell: * A value of Haskell type T can be EITHER one of the values we know and love (bottom, or constructor, or function, depending on T),

Re: circular module imports

1998-06-09 Thread Simon L Peyton Jones
Alex, If I were you I'd dispense with "deriving(Read,Show)" in module Publisher, and add an explicit instance for Read/Show on Publisher in PublisherDB. That would solve your circularity problem. Haskell does permit mutually recursive modules, but Hugs does not support them, and GHC requires so

Re: classes and instances

1998-06-08 Thread Simon L Peyton Jones
> data Weirder a b = Weirdest a b > > class Weird c where > f1 :: c -> c > f2 :: Weirder a b -> c -> Weirder a b > f3 :: Weirder a c -> Weirder c a > f4 :: c -> c -> Bool > > instance Weird (d,e) where > f1 (x,y) = (x,y) > f2 w (x,y) = Weirdest x y > f3 (Weirdest x y

Re: data or class inheritance

1998-06-05 Thread Simon L Peyton Jones
> I have a base class,Organization, with name and address functions. > I want classes Buyer and Seller from Organization. > > Now if I want to create an 2 instances of Seller > > data Yahoo = Yahoo > > instance Organization Yahoo where > > name _= "Yahoo" > > addreess = ... > > > data DoubleC

Re: order of evalutation of ||

1998-05-29 Thread Simon L Peyton Jones
> > If you have a statement like: > > result= a || b || c > > does Haskell guarantee that a gets evaluated before b? > If it does then I only have to protect against pattern match failure in > one place, a. Yes; if a is true, b and c won't be evaluated. That's part of the defn of || Simon

Re: SLPJ Moving to Microsoft

1998-05-22 Thread Simon L Peyton Jones
> I was a little surprised to read this too. You make it sound as if GHC's > free status was in jeopardy. Should we all go running for the hills if > Microsoft decides to crook its little finger in our direction? I'm glad > that you will continue to contribute to GHC, but it scares me to think

Moving to Microsoft

1998-05-21 Thread Simon L Peyton Jones
Folks, As some of you will by now know, I am leaving Glasgow. I'm going to move to the Microsoft Research lab in Cambridge (England), in September 1998. This is a big upheaval for me, but it's one I'm pretty excited about. [Lest you should wonder, my reasons for moving are personal and famil

Re: doubles-troubles

1998-05-12 Thread Simon L Peyton Jones
> rigid and I belong to the small legion of amateurs who implemented their > own math. domain system, Rings, Fields, Modules, etc. This apparently > has no chance to be included into the Haskell standard, nobody cares. Standards develop because people who care about particular aspects of them pu

Re: C to Haskell

1998-05-12 Thread Simon L Peyton Jones
> Greencard allows Haskell to call C (or Corba). Is there a way to give C > code access to Haskell functions? GHC does not yet allow this, but we are working hard on H/Direct, a successor to Greencard, that will. It'll also allow you to seal up Haskell programs inside COM objects. Timescale: a

Re: Pattern Match Success Changes Types

1998-05-11 Thread Simon L Peyton Jones
Yes, GHC does some CSE stuff, but not very much. I don't think it has a large performance impact, but (as luck would have it) but I plan to work on it a bit in the newt few months. My advice would be: write clear code, and let the compiler do the CSE. If it doesn't, complain to the compiler wri

Re: Binary, Conversions, and CGI

1998-05-06 Thread Simon L Peyton Jones
> To the newcomer who is not part of the FP academic community, this all > makes life sort of difficult. These differences seem larger than the > differences among C compilers and are MUCH larger than the differences > among Java compilers. I have been trying to learn Haskell and have been >

Re: binary search

1998-04-17 Thread Simon L Peyton Jones
> Not to reject assertions (they would be welcome), but I think that you > need something slightly different in a functional programming language. > > Assertions in procedural languages typically define system state before > and after a particular function gets executed. > > State assertions ar

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

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

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

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

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

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

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: 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?

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

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

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: 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' |

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

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.

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

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

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

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

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: 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-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-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: 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
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: 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?

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

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

  1   2   >