RE: very strange behavior (crashes!) with Dynamics

2003-08-14 Thread Hal Daume
Okay, I know I promised that was the last one, but you can actually get it simpler. Remove all the dynamic map stuff. Just have two files, Range.hs and Coref.hs, with: module Range where import Data.Dynamic data Range = Single Int | Range Int Int deriving (Eq, Ord, Show)

RE: very strange behavior (crashes!) with Dynamics

2003-08-14 Thread Hal Daume
Okay, this is the last spam from me. Here's exactly what you need to do to get the bug. Create three modules, DynamicMap.hs, Range.hs and Coref.hs, containing the following: DynamicMap.hs module DynamicMap ( DynamicMap, emptyDM, addToDM, foldDM

RE: very strange behavior (crashes!) with Dynamics

2003-08-14 Thread Hal Daume
This hasn't yet been posted, but I've actually whittled it down quite a bit. All we need is to import the Util.DynamicMap and do: > dm1 = addToDM emptyDM (Range 1 2) > showDM :: DShow -> DynamicMap -> ShowS > showDM sd = foldDM (\d b -> case sd d of { Nothing -> b ; Just s -> s . b }) id and do

GHC CVS compiling problem

2003-08-14 Thread djrom
helo 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 Makefil

Re: internal error: eval_thunk_selector: strange selectee 29

2003-08-14 Thread Ketil Z. Malde
"Simon Marlow" <[EMAIL PROTECTED]> writes: > We know of two recompilation bugs in 5.04.x & 6.0.x, both of which can > result a broken binary after making a change to a module in the program > and recompiling with --make (or in GHCi). > The first is when you switch from using -O to compiling witho

internal error: eval_thunk_selector: strange selectee 29

2003-08-14 Thread Ketil Z. Malde
(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 Please re

RE: segmentation fault with -prof -auto-all

2003-08-14 Thread Simon Marlow
Hi Simon, Forget about this one! It's as with the dentist: If you go there, the ache vanishes. I tried to assemble a distribution for you, everything worked fine. When I compiles the stuff yesterday, I only "touched" the .hs-source. Perhaps some old .hi-files caused the problem. In case the err

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 2

Re: internal error: eval_thunk_selector: strange selectee 29

2003-08-14 Thread Ketil Z. Malde
"Simon Marlow" <[EMAIL PROTECTED]> writes: >> 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 isn't deterministic though, because heap samples happen > based o

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. Hm

segmentation fault with -prof -auto-all

2003-08-14 Thread Elke Kasimir
Hi! My program runs fine when compiled with: ghc -O2 -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instanc es under debian-linux: Linux version 2.4.19 ([EMAIL PROTECTED]) (gcc version 2.95.4 200 11002 (Debian prerelease)) #6 Thu Feb 13 17:43:04 CET 2003 But it stops in the m

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

non-intuitive error message in ghci

2003-08-14 Thread Hal Daume
When we'd try to evaluate a finite map at the prompt, we get an error about there not being a show instance: Prelude> :m Data.FiniteMap Prelude Data.FiniteMap> emptyFM No instance for (Show (FiniteMap key elt)) arising from use of `print' at In a 'do' expression pattern binding: print it Howev

Bad eta expand

2003-08-14 Thread Donald Bruce Stewart
Hey all. >From a larger program I pruned down the following code which generates this error message: $ ghc-6.0 -O -package unix bug.hs Bad eta expand __coerce (# GHCziPrim.Statezh {- tc 32q -} GHCziPrim.RealWorld {- tc 31E -}, a {- tv a29a -} #) zdwzdj {- v s2dV -} (#

Re: ghc 6.0.1 and Mac OS X 10.2.6 build

2003-08-14 Thread Gregory Wright
Hi Wolfgang, Thanks again for the prompt reply. I did exactly as you noted below (removed the framework support check from configure.in, ran autoconf and ./configure, then built. Everything works appears to work correctly but ghci. (For example, I can build a network test program that queries

Re: internal error: eval_thunk_selector: strange selectee 29

2003-08-14 Thread Ketil Z. Malde
"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. I'm not quite sure wha

Re: ghc 6.0.1 and Mac OS X 10.2.6 build

2003-08-14 Thread Donald Bruce Stewart
gwright: > > Hi, > > I've built ghc 6.0.1 under OS X 10.2.6 and have a curious > problem with ghci. ghc seems to work fine, but ghci give me an > error. I should note that I've done the build without > Wolfgang's HaskellSupportFramework, by setting the include and > library paths in build.mk. Th

Re: ghc 6.0.1 and Mac OS X 10.2.6 build

2003-08-14 Thread Wolfgang Thaller
I should note that I've done the build without Wolfgang's HaskellSupportFramework, by setting the include and library paths in build.mk. This is more compatible with the automated packing scheme of DarwinPorts. Of course. The HaskellSupport.framework isn't necessary when the user already has Dar

RE: compiler (simplifier) loops

2003-08-14 Thread Simon Peyton-Jones
A known infelicity; see the bottom of http://www.haskell.org/ghc/docs/latest/html/users_guide/bugs.html My hypothesis is that this only happens if you try to make it happen. I've never found it happen in a real program. Let me know if that's not the case. Simon | -Original Message

RE: internal error: eval_thunk_selector: strange selectee 29

2003-08-14 Thread Simon Marlow
> Yes, I am. I got the error several times, but when I cleaned > everything up, it seems to have gone away -- as did the tripled > running times (and yes, they were user/system times, not just wall > clock). Very puzzling. > > Unfortunately, a 'make clean' removed all the evidence -- if I stum