Me again :)
Here's the offending code:
> module Foo where
> foo :: Int -> [((Int,Int), Int)]
> foo width = [((i,j),if i==j then 0 else 1) | i <- [1..50], j <-
> [1..width]]
largely arbitrary, the point is to make something that takes a while to
compute.
now, using ghci (5.04.1, sparc solaris, from binaries), we load Foo. now,
if we execute "foo 5" and then when it's done, type "it", it correctly
reproduces what it had. however, if we do something which will take a
while (say "foo 100") and then pound control-c to get it to be
"Interrupted!", then type "it", we get:
...43,4),1),((43,5),1),((43,6),1),((43,7),1),((43,8),1),((43,9),1),((43,10),Interrupted.
*Foo> it
ghc-5.04.1: panic! (the `impossible' happened, GHC version 5.04.1):
rdrNameModule it
Please report it as a compiler bug to [EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.
Should be pretty easy to reproduce. Happens on things other than lists,
too (for example, arrays -- which is where i noticed it).
--
Hal Daume III
"Computer science is no more about computers | [EMAIL PROTECTED]
than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs