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 ttimport/tt and tt fixity/tt

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 even

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

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

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

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 - [a]

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: 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 all. If anything, I'll have quite

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 cause

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 on

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 ambiguity error for s'.

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 straightforward

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

GHC 3.03

1998-07-10 Thread Simon L Peyton Jones
Folks, We've fixed a few bugs in GHC 3.02, thanks to useful bug reports from several of you. I'd rather not release an 'official' 3.03 because it takes half a day to do a full release, and meanwhile we have a substantial new compiler in the works (new RTS, CAF space leaks squashed, new GC, new

Re: type synonyms

1998-07-09 Thread Simon L Peyton Jones
Why does ghc allow to define instances of type synonyms? I did not find any remarks about that in the ghc docs. Due to the report this isn't allowed and hugs rejects it correctly. GHC allows arbitrary non-overlapping types in instance decls. Thus: instance C ([(Int,Bool)] where ..

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 to

Re: 3.02,multipar,overlaps

1998-07-08 Thread Simon L Peyton Jones
ghc-3.02-linux-i386-unknown... from ftp.dcs.gla.ac.uk.../3.02/ cannot link the program enclosed: ghc -c -fglasgow-exts -optC-fallow-overlapping-instances -v Main.hs log ghc -o run Main.o Main.o(.text+0x3a3): undefined reference to `Main_ZcMBConvertible_inregs_info'

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

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 that I use all of the type

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 constraint (Eq a)

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) searchList :: [key] -

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) searchList :: [key] -

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 given

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

Re: UnHappy 55 tuple [was: Re: PrelTup]

1998-06-16 Thread Simon L Peyton Jones
Hi Sigbjorn, I had another look at the 55 tuple problem. And this time, I could find a short program that produces the error. ... I had a look at `PrelTup.lhs' and it seems to define tuples up to 37 tuples or so. Maybe this is the problem. What shall I do? Hack `PrelTup.lhs'?

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 is

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

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

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

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) = Weirdest y x

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

Re: cycles in class definitions

1998-05-29 Thread Simon L Peyton Jones
class Fallible m where fail_ :: String - m a rethrow:: Fallible n = m a - n b GHC 2.10 (solaris) complains about this: Cycle.lhs:2: Cycle in class declarations ... `Fallible' Cycle.lhs:4 Whereas Hugs (jan98) is fine with it. I didn't see anything in the

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

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

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: Instance declaration superclasses

1998-04-27 Thread Simon L Peyton Jones
GHC complains about: class (Monad m, {-, Monad (t m)-}) = MonadT t m where lift :: m a - (t m) a instance (Monad m) = Monad (EnvT env m) where ... instance Monad m = MonadT (EnvT env) m where ... Even when I use the "decent" definition you suggest, GHC duplicates the

Re: Instance declaration superclasses

1998-04-27 Thread Simon L Peyton Jones
(This is related to my previous post concerning monad transformers.) GHC complains about: class (Monad m, {-, Monad (t m)-}) = MonadT t m where lift :: m a - (t m) a instance (Monad m) = Monad (EnvT env m) where ... instance (Monad (EnvT env m)) = MonadT (EnvT env) m where

Re: MPTC

1998-04-24 Thread Simon L Peyton Jones
There's no description of the multi-parameter type classes extension in the 3.01 user manual; are the extensions implemented as described in the link below? (I vaguely recollect Simon posting a message on this subject more recently, but I couldn't find it.)

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

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

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 names. Suggestion:

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

Re: type tags rejected

1998-03-02 Thread Simon L Peyton Jones
My problem is about tagging haskell expressions with the types I want them to have. What is the compiler error "Can't for-all tye type variable(s) `wef' in the inferred type `CONS ei f7t34 wef'" about? I mean, when I get it, how can I get more information about what went wrong? (I am

Re: Ambiguity

1998-02-25 Thread Simon L Peyton Jones
Except that this isn't actually allowed because happyReduce_1 appears in a restricted binding group, and hence can't have any context in its type. So, at this point, Hugs complains. GHC, I assume, just assigns hugsReduce_1 a monomorphic type, only to find at some later point that the list

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"

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

Ambiguity

1998-02-23 Thread Simon L Peyton Jones
[Comment to Simon Marlow: Does happyReduce_1 really need *eight* type parameters? Why not output type signatures? ] I respectfully suggest that the enclosed is a bug in Hugs. GHC gets the following type for happyReduce_1, which I think is the correct type: happyReduce_1 _:_

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: Confusing error message

1998-02-17 Thread Simon L Peyton Jones
I encountered a confusing error message, which you can reproduce with type P a = Maybe a instance Monad P where (=) = error "foo" return = error "bar" I get bug.hs:5: `P' should have 1 argument, but has been given 0 . Would it be better if it said

Re: ghc-3.00-linux bug in linking

1998-02-11 Thread Simon L Peyton Jones
Sergey, Marc I've had a look at your Docon thing. It's very impressive. But I'm amazed it compiles at all! When I fixed the makefile it showed up *all sorts* of loops. For example, IParse_ imports DPrelude, and DPrelude imports IParse_ Getting these mutually recursive modules to work

Re: GHC 3.00 Error when introducing an ErrorMonad

1998-02-06 Thread Simon L Peyton Jones
While experimenting with multiple parameter type classes, I introduced an ErrorMonad. Compiling this with GHC 3.00, the following happened: Computation.hs:16: Warning: `ErrorMonad' mentioned twice in export list I'll look into this. panic! (the `impossible' happened):

Re: bug report 3.00

1998-02-06 Thread Simon L Peyton Jones
panic! (the `impossible' happened): fun_result_ty: 6 GHC.Int#{-3e-} - GHC.Int#{-3e-} - b_trKC - PolyParse.HappyState{-rq9-} b_trKC c_trKD - [PolyParse.HappyState{-rq9-} b_trKC c_trKD] -

Re: Another panic

1998-02-06 Thread Simon L Peyton Jones
The following works fine with GHC 3.00: class Variable v where updVar :: v a - (a - IO (a,b)) - IO b applyVar :: Variable v = v a - (a - a) - IO a applyVar v f = updVar' v (\x - let x' = f x in (x',x')) By changing the definition of applyVar

Re: MPC Problem --- II

1998-02-06 Thread Simon L Peyton Jones
Nice point! For the class decl class (C a, D a) = E a where {...} we use to generate superclass selectors: scsel_E_C :: E a - C a scsel_E_D :: E a - D a But now there can be class decls like yours: class (C a, C b) = E a b where {...} and our naming

Re: MPC Feature/Error ?

1998-02-05 Thread Simon L Peyton Jones
My first attempt to define a MPC and some instances failed partially. I am not sure, if it is a bug or a feature. The class OMSObjAttrAppC should restrict the possible combinations of objects and attributes, so that attributes can only be read from objects to which they belong. Every

Re: bug report

1998-02-05 Thread Simon L Peyton Jones
Mark says: data Blah = Blah type Tuple = (Blah,Int) instance Show Tuple where showsPrec _ _ _ = error [] No instance for: `Show Blah' arising from use of `PrelBase.$mshowList', at tmp.lhs:8 I know that instances of classes shouldn't be types, but that's

Re: MPC dunce question.

1998-02-04 Thread Simon L Peyton Jones
While hacking around with MPCs, trying to define a variant of the Collection class, mutated to suit my own fiendish ends, I ran into this: Intervals.hs:345: Class type variable `e' does not appear in method signature union2 :: s - s - s What's the significance of this

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: Query on multi-param type classes

1998-01-30 Thread Simon L Peyton Jones
I decided to try and get my old multi-param. parser to work, and got told-off by Haskell's parser: Please tell me what I am doing wrong. The following program: module A where class (Monad m, Monad (t m)) = AMonadT t m where lift :: m a - t m a Gives me: (lambda o) ghc

Re: Strange module exportation behavior

1998-01-29 Thread Simon L Peyton Jones
Conal: great bug report; thanks. Meanwhile a workaround is to use qualified names in the export list for Test2: module Test2( Test1.foo, module Test2 ) import Test1 hiding(main) main = ... Inconvenient, but it should get you rolling. Simon,

Re: Fun with 3.00

1998-01-29 Thread Simon L Peyton Jones
One can play funny games with GHC-3.00 and the following program (a small fragment of a Happy-generated parser): -- module Foo ( happyParse ) where action_0 1 = \j tk _ - action_1 j j tk (HappyState action_1)

Re: Pattern-matching strings.

1998-01-28 Thread Simon L Peyton Jones
Is pattern-matching short strings (one or two characters) likely to be _vastly_ less efficient than matching against a single level of constructor? (Order of magnitude, plus.) Trying to make sense of some profiling numbers, here... I believe it is. Currently I think we call the

Re: building ghc on new platform

1998-01-27 Thread Simon L Peyton Jones
Richard Is it true that one must have a working version of ghc on a new in order to port it to that platform or is there a "starters-kit" with which one can start such a port? You can port by starting from the ".hc" files; that is, files that have been compiled to C but not to machine

Re: The impossible, again...

1998-01-27 Thread Simon L Peyton Jones
panic! (the `impossible' happened): lookupBindC:no info! for: showsPrec_a7AK Alex tickled a genuine, long-standing bug in the simplifier. Congratulation! Here's the patch, to simplCore/Simplify.lhs Simon == diff -c

Re: The impossible, again...

1998-01-26 Thread Simon L Peyton Jones
Hi everybody-peeps. I stumbled across the following panic, which occurs when I compile the given module with either -O2 or -O. If it proves necessary I'll try to produce a small instance, ship the whole lot off to Glasgow, or otherwise poke around in search of illumination. Try with

Re: Profiling, again.

1998-01-26 Thread Simon L Peyton Jones
Another non-killing, but rather annoying error message: this one is provoked by duplicate _scc_ labels. I don't see the sense in this restriction, myself, but at any rate this wouldn't seem to be the handiest way of detecting same... Cheers, Alex. Thanks -- this is another of the

Re: Profiling again.

1998-01-26 Thread Simon L Peyton Jones
Doing a time-profiling of my current hackery tells me the worst offender in my program is: Intervals/$d11 This raises and question or two in my mind... This represents the encoding of a dictionary (or a single method?) for some class with an instance declared in the given

Re: Simple usage of GHC

1998-01-12 Thread Simon L Peyton Jones
year ago I had the pleasure of using a compiler (for BETA I think) where the basic usage for a novice was Just What You Wanted: % compiler Main.source From there it figured out which other modules it needed, which required recompiling, which object files and libraries where needed

Re: Mysterious 2.09 message.

1998-01-09 Thread Simon L Peyton Jones
Alex Ferguson writes: Struct.hs:1: Failed to find interface decl for `Maybe' Compilation had errors make: *** [Struct.o] Error 1 I'm guessing it has to do with out of date interface files (from ghc-2.07, to be exact), but it's not the most helpful way of finding out about

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: panic! (the `impossible' happened) (2.09, patchlevel 0)

1997-12-19 Thread Simon L Peyton Jones
{- Hi, Compiling the following module results in the following error message (with GHC 2.09, patchlevel 0, i386-linux -- panic! (the `impossible' happened): getWorkerIdAndCons

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: panic! (the `impossible' happened) in ghc-2.09

1997-12-04 Thread Simon L Peyton Jones
ran into this bug when compiling with the optimization flags: -H10M -O -fvia-C -O2-for-C " NOTE: Simplifier still going after 4 iterations; bailing out. NOTE: Simplifier still going after 4 iterations; bailing out. panic! (the `impossible' happened): getWorkerIdAndCons

Re: Again: The impossible happened, this time in 2.08

1997-11-27 Thread Simon L Peyton Jones
Great bug report, thanks. I've fixed it in the upcoming 2.09 S As a by-product of hacking Fudgets to death, a bug in ghc-2.08 showed up. Compiling the fragment from Fudgets below (the real names made as much sense to me as the ones below :-), ghc fails ungracefully:

Re: Dinesh Vadhia: Haskell in the Real World ...

1997-11-21 Thread Simon L Peyton Jones
Hi! Before raising my questions please point me in the appropriate direction if these questions have been asked before. I have also just requested to join the various Haskell mail lists. My questions are really concerned with the commercial viability of Haskell especially in the face

Re: `panic' at `Integer i' in ghc-2.08

1997-11-19 Thread Simon L Peyton Jones
This is definitely a bug. Will be fixed! Simon Compiling f :: Integer i = i f = 0 ghc-2.08 reports: panic! (the `impossible' happened): tcLookupClass: PrelBase.Integer Please report it as a compiler bug to ... Probably,

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

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,

Re: Building ghc-0.29 for on sunos4 and linux

1997-10-23 Thread Simon L Peyton Jones
What is happening is this. - there's a SPECIALISE pragma involving data type Reg in FiniteMap - SpecTyFuns imports FiniteMap - Haskell 1.2 required closure on import, so Reg therefore had to be imported even though it's not used. Haskell 1.4 doesn't have this silly restriction. Solution:

Re: Optimizing Haskell programs is hard

1997-10-17 Thread Simon L Peyton Jones
You are right to be "bugged" (see your last para). Fortunately, ghc 2.09 (i.e. our current working copy) gives identical runtimes for all three. (Might be true of 2.08; I haven't tried.) Simon I'm benchmarking MVar's and other shared memory abstractions, e.g. by accessing a variable a

Re: -O in ghc-2.08-linux-i386

1997-10-17 Thread Simon L Peyton Jones
Joining these modules into *one* module Main (main) where ... and compiling with -O gives 6.1 sec. This is the *only* situation, I found -O working. Thus, if we set then `Main (main,test) where' - just for curiosity - we return to 70 sec. GHC 2.08

Re: -O in ghc-2.08-linux

1997-10-16 Thread Simon L Peyton Jones
A small program Main.hs compiled with -O runs 10 times faster or slower depending on the export list module Main (main) or module Main (main,test) Is this a bug? I don't know without seeing the program. It's certainly extreme. Can you send the

Re: profiling

1997-10-14 Thread Simon L Peyton Jones
Marc I strongly suspect that the names are simply truncated before they get into a .hp file. Doubtless this could be fixed. However, we're now embarking on building a new RTS, designed to support both GHC and Hugs, so I'd rather just make sure that the new system doesn't truncate names.

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 unqualified

Re: Universal quantification

1997-10-13 Thread Simon L Peyton Jones
ghc -c -fglasgow-exts Test.lhs Test.lhs:11: Context `{Ord taDr}' required by inferred type, but missing on a type signature `Ord taDr' arising from use of `q' at Test.lhs:11 In a polymorphic function argument `q' In the first argument of

Re: pattern match

1997-10-10 Thread Simon L Peyton Jones
I am using GHC 2.06 for Win32 and why does GHC complain about "possibly incomplete patterns"? It does so because it uses a brain-dead and incorrect way to detect incomplete patterns. (I can say this because I did it myself.) As we speak Juan Quintela is doing a Better Job. It'll appear

Re: Compiler bug pops up when compiling ghc-2.07 with 2.02

1997-10-09 Thread Simon L Peyton Jones
I tried, but it seems to complete successfully. Nevertheless, later make all fails with the same message. Probably the dependencies generated by make boot (or make depend, for that matter) _are_ circular (citing from ghc/compiler/.depend): utils/FastString.o : basicTypes/Unique.hi

Re: 100 MB of heap exhausted when compiling Happy

1997-09-22 Thread Simon L Peyton Jones
When compiling Happy-1.3's Main.lhs with optimization turned on, 100 MB of heap space aren't enough for the compiler. It crashes after several hours of compilation. When optimization is turned off, it finishes after some minutes. I would consider this a bug. I consider it a bug too! We

Re: profiling optimised code

1997-09-08 Thread Simon L Peyton Jones
Main.o(.text+0x9c): undefined reference to `PrelBase_Z36g3J_fast3' That's odd. It's usually a sign that PrelBase.hi and PrelBase.o weren't generated by the same run of GHC. You could try doing "make clean; make depend; make" in your ghc/lib directory. If that doesn't work we'll need to

Re: building with ghc-2.03

1997-09-08 Thread Simon L Peyton Jones
Hi ! I am trying to build ghc-2.05 libraries with ghc-2.03 on RS6000 and get the following problem: That's a very curious thing to do! You should only compile the ghc-2.05 libraries with ghc-2.05. The format of interface files has changed often. The complaint you are getting is that ghc-2.03

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 is

Re: Compiler Crash: ghc-2.05:panic! lookupBindC:no info!

1997-09-03 Thread Simon L Peyton Jones
The following program (rather condensed as it comes from something much larger), crashes the compiler. I am using ghc-2.05 on a Solaris box, with one or two patches(including the WwLib one which Simon gave me, but this error occured before applying this patch). Thanks for this bug report,

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 that

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 -

  1   2   >