Bug with -h and -c together

2001-10-19 Thread Ian Lynagh


Here's another one, using GHC 5.02

[ian@urchin current]$ cat W.lhs 

> module Main where

> main :: IO()
> main = putStrLn $ show $ last [1..10]

[ian@urchin current]$ ghc W.lhs -prof -auto-all -o W
[ian@urchin current]$ ./W +RTS -h   
10
[ian@urchin current]$ ./W +RTS -c
10
[ian@urchin current]$ ./W +RTS -h -c
Segmentation fault (core dumped)
[ian@urchin current]$ 

In a rather larger piece of code I get

[ian@urchin current]$ ./Project -d +RTS -M350M -h -c < PP.lhs
Project: fatal error: scavenge_mark_stack: unimplemented/strange closure
type 29 @ 0x500c22a0

which is hopefully caused by the same bug.


Thanks
Ian


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



forall for all places

2001-10-19 Thread Ralf Hinze

GHC 5.02 accepts forall types only at some sensible places:

this works

data CPS a = CPS { unCPS :: forall ans . (a -> ans) -> ans }

this doesn't work

newtype CPS a = CPS { unCPS :: forall ans . (a -> ans) -> ans }

this works

newtype CPS a = CPS (forall ans . (a -> ans) -> ans)

Needless to say that I prefer the second variant (which Hugs happily
accepts).

Cheers, Ralf


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



nativeGen/MachCode.lhs

2001-10-19 Thread Josef Svenningsson

Hi again!

In order to compile the module nativeGen/MachCode.lhs I have to add
isAsmTemp to the import list of module CLabel. Currently it says:

import CLabel   ( CLabel, labelDynamic )

but I change it to:

import CLabel   ( CLabel, labelDynamic, isAsmTemp )

isAsmTemp is only used when compiling for sparc and alpha, which I guess
is the reason why this omission has gone unnoticed.

Cheers,

/Josef


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Non-exhaustive patterns in function coreAltsType

2001-10-19 Thread Josef Svenningsson

Hi!

While bootstrapping a ghc checked out from cvs from yesterday I ran into a
problem. While compiling PrelBase.lhs I got the following error message:

ghc-5.03: panic! (the `impossible' happened, GHC version 5.03):
coreSyn/CoreUtils.lhs:97: Non-exhaustive patterns in function
coreAltsType

I'm on a sparc running solaris 2.7

/Josef


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs