RE: ghc 5.04 bug

2003-09-03 Thread Simon Marlow
ghc -c Ghcbug.hs c:\ghc\ghc-5.04\bin\ghc.exe: panic! (the `impossible' happened, GHC version 5.04): expectJust tyConDataCons Please report it as a compiler bug to [EMAIL PROTECTED], or http://sourceforge.net/projects/ghc/. Ghcbug.hs: -- module O where

RE: ghci failed to load static archive

2003-09-01 Thread Simon Marlow
Loading package base ... linking ... done. Loading package lang ... linking ... done. Loading object (static) /home/pimlott/local/fudgets/lib/GhcFudgets/FudgetsXlib.o ... done Loading object (static) /home/pimlott/local/fudgets/lib/GhcFudgets/Fudgets.o ... done Loading

RE: Segmentation fault with GHCi 6.0

2003-08-28 Thread Simon Marlow
What is going on here? Is it already fixed in 6.1? # uname -a Linux denebola 2.4.19-4GB #2 Mon Mar 31 10:57:24 CEST 2003 i686 unknown # ghc DynExcep.hs -c -fglasgow-exts # ghci ___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 6.0, for

RE: Run-time error

2003-08-26 Thread Simon Marlow
You're not gonna like this one. In ghci, Ctr-C within a loop, and: ghc-6.0.1: internal error: eval_thunk_selector: strange selectee 29 Please report this as a bug to [EMAIL PROTECTED], or http://www.sourceforge.net/projects/ghc/ Can't repeat. Undoubtedly a bug, but since you

RE: Run-time error

2003-08-26 Thread Simon Marlow
You're not gonna like this one. In ghci, Ctr-C within a loop, and: ghc-6.0.1: internal error: eval_thunk_selector: strange selectee 29 Please report this as a bug to [EMAIL PROTECTED], or http://www.sourceforge.net/projects/ghc/ Can't repeat. Undoubtedly a bug,

RE: Odd GHCi behavior

2003-08-26 Thread Simon Marlow
ketil: Andy Moran [EMAIL PROTECTED] writes: Skipping Util.List( ../../libraries/Util/List.hs, ../../libraries/Util/List.o ) ... Failed to load interface for `Util.List': Doing a big old clean, --make, and then GHCi solved the problem. But what could

RE: interactive co-recursion

2003-08-26 Thread Simon Marlow
I've no idea if the following is supposed to work, but the message tells me to report it, so here it is. Happens for all attempts to define co-recursive functions, this is just the simplest example. Prelude let { f = g ; g = f} ghc-6.0: panic! (the `impossible' happened, GHC version

RE: missing mk/config.h.in in the HEAD branch

2003-08-26 Thread Simon Marlow
I don't know if it is really a bug. When I try to configure the HEAD branch of the CVS, the script complains about a missing config.h.in . What do I have to do? You need to run autoreconf rather than autoconf these days. Also, if you're running the HEAD, it's a good idea to keep an

RE: forkProcess + stdin issue

2003-08-15 Thread Simon Marlow
After using forkProcess the child cannot read from stdin (except for data already in the buffer). Using forkProcessAll or foreign importing C's fork makes the problem go away. This applies to Solaris and GHC 6.0, I have not tested other platforms. Thanks for the report. It's a bug in

RE: GHC CVS compiling problem

2003-08-15 Thread Simon Marlow
i'm experiencing a problem when trying to compile the CVS tree of ghc. i've COed from the cvs the modules fpconfig, ghc and libraries. after having created a fptools-working directory with the lndir tool and set up mk/build.mk (taken from mk/build.mk.sample) , i run make -f

RE: internal error: eval_thunk_selector: strange selectee 29

2003-08-14 Thread Simon Marlow
(Apologies for the repeated message, the moderator seems to be out at the moment, so I just subscribed to the list and resent it, this time with a bit more information) Trying to run profiling (+RTS -p -RTS), I get: xsactp: internal error: eval_thunk_selector: strange selectee 29

RE: internal error: eval_thunk_selector: strange selectee 29

2003-08-14 Thread Simon Marlow
--make is just too pleasant not to be used. I can always clean out things in case of weird errors. Would you like me to submit subsequent reports if I encounter further problems? If you get into a state where --make produces a crashing program, then it's a good idea to take a snapshot of

RE: internal error: eval_thunk_selector: strange selectee 29

2003-08-14 Thread Simon Marlow
Simon Marlow [EMAIL PROTECTED] writes: Can you send the code, or is it too large? Both of the above. :-) There is something really fishy going on; I checked out the same code in a different directory, and built it in the same way, without getting the same behaviour. Hmm. Profiling

RE: DLL problem with GHC 6.0.1

2003-08-04 Thread Simon Marlow
I have run into something in GHC that looks like a bug (GHC 6.0.1 under Win2k). A DLL with several exported FFI functions reports (and then terminates): ghcDll: internal error: schedule: invalid what_next field Please report this as a bug to [EMAIL PROTECTED], or

RE: hp2ps: MARKs wrongly placed unless x-axis starts at zero

2003-07-30 Thread Simon Marlow
The following seems to do the trick. N *** Marks.bad.c 2003-07-30 18:00:12.0 +0100 --- Marks.c 2003-07-30 18:00:15.0 +0100 *** *** 16,22 floatish m; for (i = 0; i nmarks; i++) { ! m = (markmap[i] / xrange) * graphwidth;

RE: Panic report in ghci

2003-07-25 Thread Simon Marlow
___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 6.0, for Haskell 98. / /_\\/ __ / /___| | http://www.haskell.org/ghc/ \/\/ /_/\/|_| Type :? for help. Loading package base ... linking ... done. Prelude let f n | n 5 =

RE: The Errno Story

2003-07-25 Thread Simon Marlow
I therefore propose that we make the RTS save restore the value of errno in the TSO, thus making errno Haskell-Thread-Local-State, and solving all of the above problems. Actually this has been on my ToDo list for a long time, I just never got around to doing it (it has been mentioned on

RE: -fno-implicit-prelude -prof bug on x86

2003-07-21 Thread Simon Marlow
In article [EMAIL PROTECTED], I wrote: $ ghc -fno-implicit-prelude -prof -c M.hs /tmp/ghc4124.hc:5: `NULL' undeclared here (not in a function) /tmp/ghc4124.hc:5: initializer element is not constant /tmp/ghc4124.hc:5: (near initialization for `M_CAFs_cc_ccs[0].prevStack')

RE: stack overflow triggered by profiling in ghc 6

2003-07-18 Thread Simon Marlow
Not sure if this counts as a bug or not, but I've got the following program: import GHC.Exts import Data.List wrapper_sum xs = ub_acc_sum xs 0# ub_acc_sum :: [Int] - Int# - Int ub_acc_sum [] v = I# v ub_acc_sum ((I# x):xs) v = ub_acc_sum xs (v +#

RE: GHC 6.0: warning!

2003-07-18 Thread Simon Marlow
On Mon, Jul 07, 2003 at 03:49:38PM +0100, Simon Peyton-Jones wrote: Some of you have already discovered that GHC 6.0 has a nasty bug: if you go ghci foo\Baz.hs and there is any error at all in Baz.hs, then GHC deletes the source file! This seems like excessive punishment for a

RE: nightly build nofib failures

2003-07-16 Thread Simon Marlow
There is a bug in the nightly build scripts for running the nofib suite. Nofib programs can fail, yet the build output will still be ok.. In fact, every single nofib program can fail to compile, but it will still be ok. in the nightly mail. In a normal nightly build, we get this kind of

RE: Problems installing ghc 6.0 on freebsd

2003-06-23 Thread Simon Marlow
We've been trying to install ghc 6.0 on our freebsd boxes using the port at freshports: http://www.freshports.org/lang/ghc6/ And following the advice on the ghc download page (http://www.haskell.org/ghc/download_ghc_600.html). Sadly, it dies when it tries to build the libraries

RE: Trouble installing ghc 6.0 on Solaris

2003-06-23 Thread Simon Marlow
I've tried installing ghc 6.0 on Solaris under /opt/ghc. The files that get created include a bunch with references to Hal Daume's home directory (e.g., /opt/ghc/bin/ghci-6.0 needed to be changed). We have some problems with the Solaris binary tarball at the moment. Hopefully we'll get

RE: GHC running out of memory, surprisingly.

2003-06-19 Thread Simon Marlow
Yes, I know functional languages are memory hogs, but really! The following is on linux # ghci ___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 6.0, for Hask / /_\\/ __ / /___| | http://www.haskell.org/ghc/ \/\/ /_/\/|_|

RE: GHC bug on MacOSX 10.2.6

2003-06-13 Thread Simon Marlow
Question to the bosses: should I rename HsReadline.c to HsReadline_cbits.c by cvs-removing it and then cvs-adding it? Do I just have to do that separately for the HEAD and STABLE branches? Yes, and yes. Cheers, Simon ___

RE: Problem when compiling with -prof -fasm

2003-06-12 Thread Simon Marlow
when compiling anything with -prof -fasm, I get the following response: ghc-6.0: panic! (the `impossible' happened, GHC version 6.0): AbsCStixGen.gencode CC_DECLARE(CGI_CAFs_cc,CAF,CGI,CC_IS_CAF,); Please report it as a compiler bug to [EMAIL PROTECTED], or

RE: Strange ghci :def failure

2003-06-09 Thread Simon Marlow
This is an embarrassing bug in 6.0. Alas. We need more regression tests for ghci. Workaround: do not write expressions in ghci with pattern matches that may fail. There's a slightly less intrusive workaround: Prelude :t GHC.Err.error GHC.Err.error :: forall a. [Char] - a Prelude let

RE: ghc --make and missing interface files

2003-06-04 Thread Simon Marlow
Hello all, I have a file BinaryIO. This used to import a module HGetCharHack to work around an annoying problem with ghc5.04 which meant that hGetChar was blocking unexpectedly. However I see that this problem has now been fixed in ghc6 (ta very much, Simon) so I deleted the files

RE: problem compiling OpenGL/.../Extensions.hs with GHC version 6.0

2003-06-03 Thread Simon Marlow
But in any case, just removing the double quotes from your -D option should be enough to fix it. Well, fixing my humble Makefile is not the point, I'm more concerned about this gratuitous change in the handling of quoting which breaks other people's Makefiles. Regardless of the

RE: GHC *is* resource hungry

2003-05-29 Thread Simon Marlow
As far as I know, Hugs doesn't hash-cons types, yet it manages to typecheck these pathalogical examples in reasonable time/space. I vaguely recall there being a specific modification to Hugs's typechecker to handle this, but I can't remember what it was. Cheers, Simon -Original

RE: Removing greencard from project list

2003-05-29 Thread Simon Marlow
I'd like to remove greencard from the list of projects that can get built if you 'make' in fptools. I see a list AllProjects which include 'green-card' in fptools/mk/config.mk.in Is this the bit I need to edit? It looks plausible but I'm not certain. Yes, that should work. Why

RE: build of GHCi 5.04.3 fails to work (libgcc.a)

2003-03-31 Thread Simon Marlow
Downloaded, unpacked GHC release 5.04.3, ./configure echo GhcWithInterpreter=YES mk/build.mk make make install ghci ___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 5.04.3, for Haskell 98. / /_\\/ __ / /___| |

RE: Uninformative error message from getModificationTime

2003-03-31 Thread Simon Marlow
If I run the program main = print = readFile god and god doesn't exist, I get the following informative error message Fail: does not exist Action: openFile Reason: No such file or directory File: god However, if I run the program import Directory

RE: build of GHCi 5.04.3 fails to work (libgcc.a)

2003-03-31 Thread Simon Marlow
On Mon, Mar 31, 2003 at 11:43:46AM +0100, Simon Marlow wrote: The boxes I have access to all have __umoddi3 in libc That's rather odd; AIUI it really shouldn't be in libc. It's part of how gcc implements 64 bit division, and pollutes the namespace for other compilers (including other

RE: changing configure --prefix later?

2003-03-26 Thread Simon Marlow
OK, I'm building ghc-5.04.3 freshly from source, but when running ./configure initially, I forgot to use the --prefix= option to set the final installation location. Now, after fourteen hours of building, I use `make install' and discover the mistake. :-( How can I recover the situation?

RE: bug with splitPS in Data.PackedString

2003-03-25 Thread Simon Marlow
there's a bug in Data.PackedString that doesn't exist in PackedString: Prelude :m PackedString Prelude PackedString splitPS ('\t') (packString Foo\tBar) [Foo,Bar] Prelude PackedString :m Data.PackedString Prelude Data.PackedString splitPS ('\t') (packString Foo\tBar) [Foo*** Exception:

RE: unused import not always reported

2003-03-24 Thread Simon Marlow
How is it possible that an unused import warning is not always emitted? Below I get a warning when I recompile everything, but no warning when I only recompile the Main module (that contains the unused import). In fact Main.hi changes. It could be a bug, but we'll need to reproduce it

RE: Symbol referencing problem in GHC HEAD.

2003-03-21 Thread Simon Marlow
I recently had some trouble trying to compile a simple Template Haskell program main = putStrLn (show ($[| 20 |])) The following output was generated: /home/sseefried/local/lib/ghc-5.05/HSbase_cbits.o: unknown symbol `__umoddi3' Loading package base ... linking ... ghc-5.05: panic!

RE: HEAD: the `impossible' happened, MacOS X

2003-03-20 Thread Simon Marlow
This is yesterdays HEAD: ../../ghc/compiler/ghc-inplace -H32m -O0 -W -fno-warn-unused-matches -fwarn-unused-imports -L/sw/lib -fglasgow-exts -cpp -Iinclude -#include HsBase.h -funbox-strict-fields -package-name base -dcore-lint -W -fno-warn-unused-matches -fwarn-unused-imports

RE: floating point literals

2003-03-19 Thread Simon Marlow
Simon Marlow wrote: On Mon, Mar 17, 2003 at 10:33:47AM +, Ross Paterson wrote: GHC doesn't recognize literals like 9e2, and nor does lex. Correction: GHC doesn't recognize 9e2 lex is confused by 0xy, 0oy, 9e+y and 9.0e+y Fixed GHC, I'll leave lex to someone more

RE: building 5.04.3 on sparc-solaris-2.6

2003-03-19 Thread Simon Marlow
I'm trying to build ghc-5.04.3 from source on a sparc-solaris-2.6 machine, using 5.02.3. It throws up the following build error. Any ideas what might be going wrong? /tmp/ghc11170.hc: In function `SystemziTime_zdLrpHVeta_entry': /tmp/ghc11170.hc:10508: called object is not a function

RE: building 5.04.3 on sparc-solaris-2.6

2003-03-18 Thread Simon Marlow
I'm trying to build ghc-5.04.3 from source on a sparc-solaris-2.6 machine, using 5.02.3. It throws up the following build error. Any ideas what might be going wrong? I'm not sure, and I'm afraid our one and only Sparc box has just died, probably permanently :-( The 5.04.3 build *did* go

RE: building 5.04.3 on sparc-solaris-2.6

2003-03-18 Thread Simon Marlow
Simon Marlow [EMAIL PROTECTED] writes: I'm trying to build ghc-5.04.3 from source on a sparc-solaris-2.6 machine, using 5.02.3. It throws up the following build error. Any ideas what might be going wrong? I'm not sure, and I'm afraid our one and only Sparc box has just died

RE: floating point literals

2003-03-17 Thread Simon Marlow
On Mon, Mar 17, 2003 at 10:33:47AM +, Ross Paterson wrote: GHC doesn't recognize literals like 9e2, and nor does lex. Correction: GHC doesn't recognize 9e2 lex is confused by 0xy, 0oy, 9e+y and 9.0e+y Fixed GHC, I'll leave lex to someone more familiar with the code... Cheers,

RE: 5.04.2: hp2ps -c no longer works

2003-03-05 Thread Simon Marlow
The colours in postscript generated by 5.04.2's hp2ps are stuffed. I suspect the attached complaints are related, but I haven't followed this up. Is this a known bug? Is there any patch available for it? It's been reported before, and 5.04.3 (due to be released momentarily) will have the

RE: Posix.getFileStatus

2003-02-28 Thread Simon Marlow
(1) I think Posix.getFileStatus should respond to a file which isn't there with something rather more helpful than system error. For example, a No such file or directory message. With today's CVS sources: Prelude System.Posix.getFileStatus /tmp/foo Loading package unix ... linking ...

RE: thread blocked indefinitely

2003-02-26 Thread Simon Marlow
I'm now `GHC.Conc.forkProcess`ing only from the initial thread, and all seems well. Thanks for the suggestion! Any idea when `forkProcess` might get fixed? Don't hurry on my account; I'm just curious. There's a comment in the code from Sigbjorn who tried to fix it and was

RE: no input files

2003-02-26 Thread Simon Marlow
buzzard(150)% cat Two-part.hs main = return () buzzard(151)% ghc --make Two-part.hs ghc-5.04.2: chasing modules from: Two-part.hs Compiling Main ( Two-part.hs, ./Two-part.o ) ghc: linking ... buzzard(152)% ghc --make Two-part ghc-5.04.2: no input files Usage: For basic

RE: profiling problems

2003-02-26 Thread Simon Marlow
I have this code which compiles and runs normally, but gives bus errors or segfaults at run time when compiled with -prof -auto-all. ghc-5.04 SunOS cownose.cs.indiana.edu 5.8 Generic_108528-18 sun4u sparc SUNW,Ultra-5_10 If that's really 5.04, and not 5.04.2, you should upgrade and try

RE: thread blocked indefinitely

2003-02-25 Thread Simon Marlow
Something like the following seems to be occurring. The program `Concurrent.forkIO`s several threads. Two of these auxiliary threads each fork a process (with `GHC.Conc.forkProcess`). Just as the second forked process is about to `Posix.executeFile`, it appears that the ghost of

RE: unexpected thread blocking

2003-02-24 Thread Simon Marlow
Actually I am not sure if this is really a bug, but anyway the following program behaves in different manners between with and without -O. Interestingly, ghci provides the same (expected) behavior as -O. \begin{code} import Control.Concurrent import Control.Concurrent.MVar import

RE: Build error

2003-02-11 Thread Simon Marlow
Could you try with EXTRA_HC_OPTS=-v, and send us the output? Thanks. Also, what compiler are you building GHC with? Installed from where? The compiler was ghc 5.04.1, installed from the rpm on haskell.org; I've updated to 5.04.2 (same source): no change. In the example below,

RE: bug with -O -ffi and multiple module

2003-01-29 Thread Simon Marlow
Okay, here's a weird one. There's something wrong with the ffi when using -O and the foreign imports are from another module. For example, our foreign module, foo.c contains functions: void* openFile(char*fn); void closeFile(void*f); float readFloat(void*f); which are

RE: Bizarre Haskell Problem

2003-01-29 Thread Simon Marlow
I am having a bizarre Haskell problem that I am having difficulty debugging. I am not positive this is a compiler problem, but my results are not making any sense. I have attached a few source files which compiled with ghc-5.04.2 running under Win95. The files were compiled as: ghc

RE: evaluation fault in ghci.

2003-01-24 Thread Simon Marlow
The interactive loop of ghci displays an interesting evaluation fault to do with derived equality. In the attached source file, there is a simple guard which tests some equalities, and basically the same value is given on the left and right of the (==). Yet, it evaluates to False in

RE: foreign import label with polymorphic type

2003-01-23 Thread Simon Marlow
GHC (5.04 and CVS) rejects the following, saying Unacceptable type: foreign import ccall unsafe stdlib.h free pFree :: FunPtr (Ptr a - IO ()) Fixed, thanks. Simon ___ Glasgow-haskell-bugs mailing list [EMAIL PROTECTED]

RE: bug report

2003-01-22 Thread Simon Marlow
I am reporting a bug in the GHCi Haskell interpreter as requested by the program itself. GHC is 5.04.2 running on SunOS 5.8. The interpreter encountered a panic condition when trying to load a parser produced by Happy the parser generator. Yes, this is a known bug in 5.04.2 (although I

RE: Compile problems

2003-01-22 Thread Simon Marlow
I'm still trying to compile ghc, but it's getting worse: Running make results in the following error message: Do you have GHC installed? It looks like you either don't have GHC, or configure didn't detect it. Could you send the output of ./configure at the top of the tree? Cheers,

RE: ghc 5.04.2 and seg fault

2003-01-22 Thread Simon Marlow
I have a bug which I'm having trouble reproducing on a small scale, so I'm not sure how to proceed to get more information to you. When I use ghc --make to recompile a group of files, I sometimes get a segfault when running the target program. If I remove all of the .o files and compile

RE: Small bug in Data.PackedString.splitWithPS

2003-01-13 Thread Simon Marlow
In GHC 5.04.2 this fails: wordsPS (packString a) Cause: typical off-by-one error in libraries/base/Data/PackedString.hs line 289 first_pos_that_satisfies pred ps len n = case [ m | m - [n..len], pred (ps ! m) ] of ^ here

RE: Error messages when mixing profiled and unprofiled code

2003-01-08 Thread Simon Marlow
I just went through an interesting (== painful) remote debugging session with one of my clients which could be avoided by improving an error message. If you compile a program for profiling but don't have profiling versions of the standard libraries, then the linker generates reports

RE: BCO entry code - parameter passing on RISC

2003-01-06 Thread Simon Marlow
After a day of running gdb in parallel on my MacOS X and Linux [quite annoying because of different keyboard layouts ;-) ], I've come to the following conclusion: The entry code for BCOs expects all parameters to be on the stack, but on non-x86 machines, the stg_ap_*_ret pass

RE: bug

2003-01-06 Thread Simon Marlow
it only happens when i try to compile with profiling enabled. Profiling (-prof) is incompatible with the native code generator (-fasm). Leave out -fasm if you want profiling. (Compiling will be slower without -fasm) It is only a tiny bug: GHC should complain about incompatible options

RE: Strict Word64 Compiler Panic

2002-12-12 Thread Simon Marlow
Let Crash.hs be: module Crash where import Data.Word (Word64) data S = S { a :: ! Word64 } s :: S s = S { a = 0 } Then: (mbs@emae) ghci-5.04 -fglasgow-exts ___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 5.04, for Haskell 98. /

RE: ghci and unboxed types

2002-12-12 Thread Simon Marlow
ralf/tmp ghci -fglasgow-exts Arr.lhs ___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 5.04, for Haskell 98. / /_\\/ __ / /___| | http://www.haskell.org/ghc/ \/\/ /_/\/|_| Type :? for help. Loading package base ... linking

RE: Bug#171518: ghc --make does not play nice with FFI wrapper

2002-12-06 Thread Simon Marlow
Package: ghc5 Version: 5.04-1 Severity: normal I have a module SDL.Bare.Audio with this declaration: foreign import ccall safe wrapper mkSDL_AudioSpec_Callback :: SDL_AudioSpec_Callback u - IO (FunPtr (SDL_AudioSpec_Callback u)) When compiling

RE: RULES/SPECIALIZE not parsing:

2002-12-04 Thread Simon Marlow
Rules.hs: module Rules where my_id :: a - a my_id a = a my_int_id :: Int - Int my_int_id a = a {-# RULES my_id = my_int_id #-} Each rule should begin with a string, like: {-# RULES my_id my_id = my_int_id #-} {-# SPECIALIZE my_id :: Int - Int = my_int_id #-} These kind of

RE: build of ghc-5.05.20021118 fails

2002-11-27 Thread Simon Marlow
From time to time I try out one of the development snapshots. Does it make sense to report errors? Anyway, the the build of ghc-5.05.20021118 fails with the following error message ... -- -- ==fptools== make html -

RE: Running make

2002-11-26 Thread Simon Marlow
Simon Marlow [EMAIL PROTECTED] writes: You also need libreadline.so, which here is just a link to libreadline.so.4.2. The right way to get this, if you're on an RPM-based Linux system, is to install the appropriate readline-devel RPM. Thanks, it worked, but now a longer error

RE: Running make

2002-11-19 Thread Simon Marlow
While running make, following error occurred: -- -- ==fptools== make boot - --no-print-directory -r; in /home/sonja/uni/work/e8/ghc-5.04.1Mod/ghc/utils/ghc-pkg

RE: Can't load package 'util'

2002-11-05 Thread Simon Marlow
Typing 'ghci -package util' caused an error. Error message: ... panic!(...)can't load package 'util' What version of the readline library do you have installed? I suspect you need version 4.2 (that's what is installed on the machine used to build the binaries). Could you do 'rpm -qa | grep

RE: additional to earlier mail Can't load package util

2002-11-04 Thread Simon Marlow
I forgot to say which version und operating system: ghc 5.04.1 linux Suse Could you please post the full error report? Preferably also add the -v flag to ghci. I have seen a problem with loading package util before, and I think it was also on a SuSE system. Anyone else on SuSE get an error

RE: interrupted system calls

2002-10-28 Thread Simon Marlow
Does anyone know what might be causing the following error from a program that uses System.system? Fail: interrupted Action: system Reason: Interrupted system call The shell command given to System.system runs and terminates with a non-zero exit code (actually 8). I

RE: mod 0 results in core dump

2002-10-24 Thread Simon Marlow
Prelude 4 `mod` 0 Floating exception (core dumped) 'nuf said. ghc 5.04.1, solaris. It now raises an exception, and the fix is scheduled to be merged into 5.04.2. Cheers, Simon ___ Glasgow-haskell-bugs mailing list [EMAIL PROTECTED]

RE: glibc 2.3.1

2002-10-24 Thread Simon Marlow
some days ago I upgraded the GNU libc6 (also called glibc2) C library to version 2.3.1. It's only now that I notice that this wasn't a very good idea as it breaks GHC (version 5.04.1). basilisk Software/Haskell ghc --make Hello.hs ghc-5.04.1: chasing modules from: Hello.hs Compiling Main

RE: GetMBlock

2002-10-23 Thread Simon Marlow
Hello, I am getting the the folowing error message with ghc-5.04 meegpar: fatal error: GetMBlock: misaligned block 0x401d1000 returned when allocating 1 megablock(s) at 0x5080 I saw on the mailing list that the problem exists since long time. I would think that trying

RE: System.Cmd.system tries to execve(n/sh, ...)

2002-10-18 Thread Simon Marlow
I find it hard to see how a bug like this could get into a GHC release, since it appears to break the build. But, I don't know of anything wrong with the platform I'm running it on, and in general my setup looks okay (rpm --verify, etc). So, does anyone reproduce this? I'm running GHC

RE: Object Splitting and the Base Package Makefile

2002-10-18 Thread Simon Marlow
In a related issue, it seems that in ghc-5.04 libraries *_hsc.o files are left out when linking with SplitObjs=YES. Yes. Actually it's better to not use #def in .hsc files at all, so that the *_hsc.o files are empty, and rather put auxiliary definitions in the appropriate header files. I've

RE: [GHCi 5.04.1] the `impossible' happened

2002-10-14 Thread Simon Marlow
[Indented text is me; unindented text is GHCi] Initial experience with the bug: *Autoexi let x e = do putStrLn hmm...; return 'c' *Autoexi y - catch (getChar) (x) here, I hit ^C several times, hoping to catch that as an exception. This didn't seem to happen, and GHCi appeared

RE: bug/feature/? of ghci with concurrency

2002-10-01 Thread Simon Marlow
Maybe this is by design, but in case it isn't: I was a little suprprised when I came across this behavior of ghci: ghci ... GHC Interactive, version 5.04.1, for Haskell 98. ... Prelude :m Concurrent Prelude Concurrent let loop c = putChar c loop c

RE: Newbie building GHC

2002-09-27 Thread Simon Marlow
May I suggest the GHC downloads page drops the claim that the 5.04.1 RPMs will work under RH7.2? Ok, will do. Thanks for looking into this one. Does anyone have a set of RedHat 7.2 RPMs we can make available? Cheers, Simon ___

RE: typo in unboxed types section + feature request

2002-09-27 Thread Simon Marlow
First off, in section 7.2.7 Primitive-Double and Float operations there's a typo. It says minux instead of minux on the line reading: {plus,minux,times,divide}Float# :: For the feature request, could we get the rest of the trig functions, namely: asinhFloat#, acoshFloat#,

RE: typo in unboxed types section + feature request

2002-09-27 Thread Simon Marlow
You can use the FFI for all these operations, just import the C versions. You can even use unboxed types if you really want (mostly it shouldn't be necessary, though). Ah, yes, that works too :). I only suggested it because all the other Float# functions seem to be exactly what is

RE: typo in unboxed types section + feature request

2002-09-27 Thread Simon Marlow
There shouldn't be any difference, as far as I can tell. The two types have the same representation. But strange things do happen. If you have an example where it makes a difference, we can take a look. If I can manage to get a small example, I'll let you know (adds this to his

RE: Generating docs

2002-09-25 Thread Simon Marlow
What is the approved way of generating and installing docs? I tried (from source) ./configure ... make all make install make html make dvi make ps make install-docs The latter command fails with (as usual with a bit of German :-) Do you have Haddock installed? Did the configure

RE: Generating docs

2002-09-25 Thread Simon Marlow
BTW, why did you separate Haddock from GHC? I love these vicious circles: to build GHC with docs you need Haddock, to build Haddock you need GHC ... You can either use an installed Haddock, or use Haddock from the same tree (./configure --enable-src-tree-haddock). It's not really a cyclic

RE: Main Thread Evacuated

2002-09-25 Thread Simon Marlow
I've found a bug in the scheduler: When a main thread finishes (e.g. returning from a ffi callback), the GC might be run before it is removed from the main_threads list. If a major collection happens, the thread will be garbage collected and the GC barfs when it updates the pointers

RE: uh oh, another bug report :) (it and big computations)

2002-09-25 Thread Simon Marlow
*Foo it ghc-5.04.1: panic! (the `impossible' happened, GHC version 5.04.1): rdrNameModule it Fixed, thanks. Simon ___ Glasgow-haskell-bugs mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

RE: -xc and stack overflow

2002-09-24 Thread Simon Marlow
I'm suffering stack overflow in a program that uses both multiple processes and multiple threads. Can anyone help me interpret the following -xc output? In particular, which ... reports relate to the stack overflow? (I've added a newline following each '' to increase readability.) I

RE: Bus Error when profiled

2002-09-20 Thread Simon Marlow
I compiled a program with ghc --make -prof -auto-all -H100M -fglasgow-exts -i.. -iHUnit -package data -package util -package posix -syslib concurrent When I run it, it evokes a Bus Error (with or without +RTS -p). Any ideas what's wrong? I'm using GHC 5.02.3 on Sparc/Solaris. Try

RE: ghc --make

2002-09-19 Thread Simon Marlow
We are having a problem with ghc --make. We have a standard set of libraries that we build and install in a shared area and then use with ghc --make. The problem is that ghc then (sometimes) tries to rebuild the libraries: something that is doomed to fail for a variety of reasons.

RE: Division by 0 exits ghci

2002-09-18 Thread Simon Marlow
George Russell [EMAIL PROTECTED] wrote, In fact the problem is more drastic than I mentioned in my last message; division by 0 doesn't seem to be catchable at all. From this program --- cut here --- import Exception main = do excep -

RE: ghc5.04.1 deriving Read/Show broken

2002-09-17 Thread Simon Marlow
Luckily, there is a workaround (discovered by Tom Moertel on #haskell). If you include field names in the data definition for which you derive Show and Read, it seems to work fine. So, in George's example module GHCBug where data Command = NewLocation | Commit

RE: Posix.executeFile having problems with unevaluated argumnets

2002-09-17 Thread Simon Marlow
Sorry, I haven't got time to narrow this down to a test case, but here are what I hope are the key factors: (1) We start up applications in a child process (forked with Posix.forkProcess) by calling Posix.executeFile, wrapped in an Exception.catch handler (to detect errors). (2) Both

RE: GetMBlock: misaligned block

2002-09-12 Thread Simon Marlow
Simon Marlow [EMAIL PROTECTED] writes: The problem is that GHC is asking for memory at a particular address (0x5000) and the kernel is returning memory elsewhere that doesn't satisfy our aligment constraints (1M aligned). We don't particularly care where we get memory from

RE: docs bug

2002-09-09 Thread Simon Marlow
In local.glasgow-haskell-bugs, you wrote: http://www.mirror.ac.uk/sites/www.haskell.org/ghc/docs/latest/ html/base/Data.Bits.html The description of each method of the Bits class seems to be attached to the signature of a different method. The documentation generated by haddock 0.4

RE: FFI: passing 6 FD arguments doesn't work

2002-09-09 Thread Simon Marlow
This was a bug in GHC's native code generator for SPARC, which sometimes misaligned the stack pointer. This has already been fixed in CVS (HEAD and branch), but it didn't make it into 5.04, see: http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/nativeGen

RE: Bug in ghc-pkg on SunOS

2002-09-09 Thread Simon Marlow
I am using ghc-pkg on SunOS4 and get the following behavior when using 'ghc-pkg -g': ld: illegal option -- x ld: illegal option -- - ld: illegal option -- w ld: illegal option -- x ld: illegal option -- - ld: illegal option -- w The relevant line from ghc-pkg is: system(ld -r -x

RE: GetMBlock: misaligned block

2002-09-06 Thread Simon Marlow
after baking a new kernel for my Linux box I got this funny error message: basilisk /home/ralf ghci ghc-5.04: fatal error: GetMBlock: misaligned block 0x15745000 returned when allocating 1 megablock(s) at 0x5000 (There is a 4 year old entry on the mailing list reporting the same

RE: ghc-5.02.3: fatal error: getStablePtr: too light

2002-09-05 Thread Simon Marlow
I'm sporadically seeing the following error: ghc-5.02.3: fatal error: getStablePtr: too light Any ideas what it means or how to avoid it? I'm running on Linux. This is fixed in 5.04. I believe it was triggered by making too many stable pointers to the same object. Cheers,

<    1   2   3   4   5   6   7   8   9   10   >