RE: empty export in ghc-4.02

1999-02-15 Thread Sigbjorn Finne (Intl Vendor)
[EMAIL PROTECTED] writes: > > ghc-4.02 -c T.hsyields T.hs:1:11: parse error on input: ")" > > for > - > module T () where > > ng1 x y = negate y > > instance (Num a, Num b) => Num (a,b) > where > negate (a,b) = (ng 'c

RE: ghc-4.02 garbage collector problem and others

1999-02-15 Thread Sigbjorn Finne (Intl Vendor)
Thomas Hallgren <[EMAIL PROTECTED]> writes: > ... > I also encoutered another small problem resulting in > compilation errors like > > SizingF.hs:9: Could not find valid interface file `Sizing' > > which seems to happen whenever an imported module has a name > containing the letter 'z

GC bug

1999-02-15 Thread Simon Marlow
The following patch should fix 4.02's GC bug. I'll put up fixed distributions as soon as possible. diff -c -c -r1.30 GC.c *** GC.c1999/02/11 17:40:26 1.30 --- GC.c1999/02/15 14:21:50 *** *** 1932,1941 scavenge_mutable_list(generation *gen) { StgInfoTa

SPECIALIZE with = in ghc-4.02

1999-02-15 Thread S.D.Mechveliani
ghc-4.02 -c T.hs reports panic! (the `impossible' happened): Can't handle SPECIALISE with a '= g' part for module T where {-# SPECIALIZE f :: Int -> Int = g #-} f :: Num a => a -> a f x = x g = const 0 - tho

Re: Couldn't find isAlphaNum

1999-02-15 Thread David Barton
Sigbjorn writes: Weird - are you sure it was capitalised as Haskell now prescribes? Well, *that* makes me feel dumb. That was the problem, indeed. I ask pardon for my blindness. Dave Barton <*> [EMAIL PROTECTED

empty export in ghc-4.02

1999-02-15 Thread S.D.Mechveliani
ghc-4.02 -c T.hsyields T.hs:1:11: parse error on input: ")" for - module T () where ng1 x y = negate y instance (Num a, Num b) => Num (a,b) where negate (a,b) = (ng 'c' a, ng1 'c' b) where ng x y = negate y --

RE: Couldn't find isAlphaNum

1999-02-15 Thread Sigbjorn Finne (Intl Vendor)
Weird - are you sure it was capitalised as Haskell now prescribes? sar$ cat x.hs module X where { import Char (isAlphaNum) ; x = isAlphaNum } sar$ ghc --version The Glorious Glasgow Haskell Compilation System, version 4.02, patchlevel 0 sar$ ghc -noC x.hs sar$ --Sigbjorn > David Barton [mailt