-O2 == crash

2000-03-09 Thread Marcin 'Qrczak' Kowalczyk
The following code crashes when compiled with -O2. With -O it does not crash. Some trivial modifications make the crash go away. import Array(Array, array, (!)) import Random (StdGen, newStdGen) import MonadRWS

RE: _ is not always small (syntactically :-)

2000-03-09 Thread Simon Marlow
GHC's lexer (function Lex.mk_var_token) treats names starting with an underscore followed by an uppercase letter as a constructor (conid) and not as a variable (varid): module Foo where data T = _ThisWorksAlthoughItShouldNot _ThisShouldWorkButItDoesNot = '?' A comment in the

RE: -O2 == crash

2000-03-09 Thread Simon Marlow
The following code crashes when compiled with -O2. With -O it does not crash. Some trivial modifications make the crash go away. Sorry, I can't repeat this one. As far as I can tell, using -O2 does three things - it forces -fvia-C (on by default anyway) - it passes -O2 to

Re: -O2 == crash

2000-03-09 Thread Marc van Dongen
Marcin 'Qrczak' Kowalczyk ([EMAIL PROTECTED]) wrote: : Thu, 9 Mar 2000 01:58:02 -0800, Simon Marlow [EMAIL PROTECTED] pisze: : : So the likely candidate would appear to be your gcc - which version : do you have installed? : : 2.95.1 : : With -O -O2-for-C it still crashes. With -O it does

RE: -O2 == crash

2000-03-09 Thread Simon Marlow
2.95.1 With -O -O2-for-C it still crashes. With -O it does not. With -O2-for-C it does not. (gdb) bt #0 0x804932a in Main_zn_fast2 () #1 0x500c0444 in ?? () #2 0x500c1fa4 in ?? () #3 0x468bfc45 in ?? () Cannot access memory at address 0x8908468b. We could investigate further,

RE: hslibs/tools/DtdToHaskll

2000-03-09 Thread Simon Marlow
(when doing gmake in the fptools directory.) ../../../ghc/driver/ghc-inplace -o DtdToHaskell -cpp -fglasgow-exts -syslib text-H40m -OnotDtdToHaskell.o DtdToTypeDefPP.o /usr/local/pub-bkb/ghc/fptools/hslibs/data/libHSdata.a(FiniteM ap__1.o)(.text+0x38): undefined reference to

panic! (the `impossible' happened): again

2000-03-09 Thread George Russell
Glasgow Haskell seems to be good at doing the impossible . . . panic! (the `impossible' happened): mkWWcpr: not a product w{-rIZ-} - e{-rJ1-} - Listener.DispatchMode{-rgO,i-} - ExternalEvent.IA{-rgh,i-} GUIEvent.EventInfo{-rsx,i-} Let me know if you want the source file

Re: panic! (the `impossible' happened): again

2000-03-09 Thread George Russell
George Russell wrote: Glasgow Haskell seems to be good at doing the impossible . . . panic! (the `impossible' happened): mkWWcpr: not a product w{-rIZ-} - e{-rJ1-} - Listener.DispatchMode{-rgO,i-} - ExternalEvent.IA{-rgh,i-} GUIEvent.EventInfo{-rsx,i-} Let

RE: panic! (the `impossible' happened): again

2000-03-09 Thread Simon Peyton-Jones
Yes, this is a known bug. It doesn't happen in my private copy, which I'm eternally just about to commit. I keep not doing it because I'm busy doing ICFP papers. I think I'll just commit it anyway by the end of this week. Simon | -Original Message- | From: George Russell

PrelList.badHead - has GHC got a hangover?

2000-03-09 Thread George Russell
Sadly my shiny new GHC (downloaded and compiled from CVS last night) seems to have produced an inconsistent .hi file (attached) when compiling the basis. The problem is that badHead is mentioned in a inline bit of gunk, but the type for it isn't specified anywhere. (It's an internal value which

Re: Enum instance for Ratio

2000-03-09 Thread George Russell
Marc van Dongen wrote: Wouldn't that make Enum depend on Ord? Doesn't seem to make sense if classes are enumerable but not comparable. What examples are there of types for which it would be sensible to implement Enum but not Ord? The concept rather puzzles me. In particular, suppose you

Enum instance for Ratio

2000-03-09 Thread Sven Panne
Both GHC and Hugs have a bug in their Prelude for Ratio's Enum instance. The following program import Ratio main = print [ 1, 4%(3::Int) .. 2 ] should print [1 % 1,4 % 3,5 % 3,2 % 1] but instead an infinite list of 1%1s is generated. The reason for this is that the default method for

Re: Enum instance for Ratio

2000-03-09 Thread Marc van Dongen
George Russell ([EMAIL PROTECTED]) wrote: : Marc van Dongen wrote: : Wouldn't that make Enum depend on Ord? : Doesn't seem to make sense if classes are : enumerable but not comparable. Of course above I should have said orderable in stead of comparable. : What examples are there of types

Re: Enum instance for Ratio

2000-03-09 Thread Malcolm Wallace
Sven writes: Both GHC and Hugs have a bug in their Prelude for Ratio's Enum instance. ... The reason for this is that the default method for enumFromThenTo is used, which truncates 4%3 to 1 (same for enumFromTo). I'd say that this is a bug in the Library

Re: Enum instance for Ratio

2000-03-09 Thread George Russell
A logical definition of Enum (to me wearing a mathematical hat) would be succ x = min { y | y x} For Ratio this makes no sense, ergo Ratio should not be an instance of Enum. For Float and Doubles it makes a lot of sense (giving nextAfter, which is a commonly used IEEE function not otherwise

Re: Enum instance for Ratio

2000-03-09 Thread Marc van Dongen
George Russell ([EMAIL PROTECTED]) wrote: : A logical definition of Enum (to me wearing a mathematical hat) : would be : : succ x = min { y | y x} : Wouldn't that make Enum depend on Ord? Doesn't seem to make sense if classes are enumerable but not comparable. Regards, Marc

RE: binary IO

2000-03-09 Thread Simon Peyton-Jones
| But Haskell *really* needs some standard way of reading values in the | native format on a platform: What about this specification? hReadByteArray :: Handle - MutableByteArray a - Int - IO Int -- Read the specified number of *bytes* into the byte array. -- Return the

Re: binary IO

2000-03-09 Thread Sven Panne
Simon Peyton-Jones wrote: What about this specification? hReadByteArray :: Handle - MutableByteArray a - Int - IO Int [...] hWriteByteArray :: Handle - MutableByteArray a - Int - IO () [...] Both may block. Would that do what you want? If so we can add it to IOExts.

scanr1 [], scanl1 []

2000-03-09 Thread Marcin 'Qrczak' Kowalczyk
Why are they undefined? IMHO [] would be a perfect answer. Consistent with scanr1 f . drop n = drop n . scanr1 f scanl1 f . take n = take n . scanl1 f and everything else I can imagine. -- __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/ \__/ GCS/M

No Subject

2000-03-09 Thread Chris Angus
Does anyone know where I can get some information on Lambada. I tried http://windows.st-lab.cs.uu.nl/Lambada/ but got a 403 (not authorised to view page) Cheers Chris

RE: fixity declarations in where clauses?

2000-03-09 Thread Simon Peyton-Jones
Good point. My fault, I think, and now fixed in the head of the CVS tree. Workaround: put the fixity decls at top level. Sorry about this Simon | -Original Message- | From: Michael Hudson [mailto:[EMAIL PROTECTED]] | Sent: 08 March 2000 13:31 | To: [EMAIL PROTECTED] | Subject: fixity

Re: Lambada

2000-03-09 Thread John Atwood
Try Erik Meijer's home page: http://www.cs.ruu.nl/~erik/ John Atwood - Chris Angus wrote: Does anyone know where I can get some information on Lambada. I tried http://windows.st-lab.cs.uu.nl/Lambada/ but got a 403 (not authorised to view page) Cheers

Re: fixity declarations in where clauses?

2000-03-09 Thread Michael Hudson
Simon Peyton-Jones [EMAIL PROTECTED] writes: Good point. My fault, I think, and now fixed in the head of the CVS tree. Ah, the wonders of open source! Workaround: put the fixity decls at top level. Not a help sadly; there was a reason my original operators were local. val = 3 +! 4 *! 2

Re: Combinators for data flow / Laws of Form

2000-03-09 Thread Hannah Schroeter
Hello! On Wed, Mar 08, 2000 at 12:59:23PM +0100, Arne Bayer wrote: 1.) Does anybody know of (a set of) combinators describing the data flow through functions? The most prominent representative in this resepct is probably composition ('.' in Haskell). Do you already know the SK(I) calculus?

FYI: ghc to be dropped from potato (debian)

2000-03-09 Thread Sengan
http://www.debian.org/Lists-Archives/debian-devel-announce-0003/msg7.html Sorry if this has already been mentionned. It's not in http://www.dcs.gla.ac.uk/mail-www/haskell/ Sengan

cfp: ICFP Wkshp on Program Generation

2000-03-09 Thread Walid Taha
PRELIMINARY CALL FOR PAPERS Semantics, Applications and Implementation of Program Generation (SAIG) ICFP Workshop, Montreal, September 20th, 2000. (Deadline: May 22, 2000)