eval_thunk_selector: strange selectee 29

2004-03-08 Thread Greg Baker
For the Haskell program from hell (it kills ghc-6.01 on OpenBSD 3.4,
hugs on MacOS X and hugs on EPOC)
It's a translation of the (in)famous jpeg.gs script - but I'm yet to
see whether it works or not, and how fast. But it does compile cleanly.
I can send you a sample JPEG that causes the crash, but I think any
image will do.
Good luck, and thanks for making Haskell happen in the real world.
 module Jpeg where
 import Char
 type Table a  =  Int - a

Auxiliary functions:

 infixr 9 `o`
 o :: (c-d) - (a-b-c) - (a-b-d)
 (g `o` f) x y = g (f x y)

 ap :: (a-b) - a - b
 ap f x  = f x
 
 ap':: a - (a-b) - b
 ap' x f = f x


 subst :: Eq a = a - b - (a-b) - (a-b)
 subst i e t j  | i==j  =  e
| otherwise =  t j

 multi  :: Int - [a] - [a]
 multi n = concat . map (replicate n)

 ceilDiv:: Int - Int - Int
 --ceilDiv n d = (n+d-1)/d
 ceilDiv n d = (n+d-1) `div` d-- I think

Matrix manipulation

 type Dim   = (Int,Int)
 type Mat a = [[a]]

 matapply:: Num a  =  Mat a - [a] - [a]
 matapply m v = map (inprod v) m

 inprod :: Num a  =  [a] - [a] - a
 inprod  = sum `o` zipWith (*)

 matmap :: (a-b) - Mat a - Mat b
 matmap  = map . map

 matconcat :: Mat (Mat a) - Mat a
 matconcat  = concat . map (map concat . transpose)

 matzip :: [Mat a] - Mat [a]
 matzip  = map transpose . transpose

 transpose:: [[a]] - [[a]]  -- transpose list of lists
 transpose = foldr
   (\xs xss - zipWith (:) xs (xss ++ repeat []))
   []

 Bit Streams

 type Bits = [Bool]

 byte2bits  :: Int - Bits
 byte2bits x = zipWith (=) (map (rem x) powers) (tail powers)
  where powers = [256,128,64,32,16,8,4,2,1]

 string2bits :: String - Bits
 string2bits  = concat . map (byte2bits.ord)

 byte2nibs  :: Int - (Int,Int)
 --byte2nibs x = (x/16, x`rem`16)
 byte2nibs x = (x `div` 16, x `rem` 16) -- I think; maybe should be divMod?

Binary Trees

 data Tree a  =  Nil
  |  Tip a
  |  Bin (Tree a) (Tree a)


 instance Functor Tree where
 fmap f Nil   =  Nil
 fmap f (Tip a)   =  Tip (f a)
 fmap f (Bin x y) =  Bin (fmap f x) (fmap f y)

State Function (StFun) Monad

 data StFun s r = SF (s - (r,s))
 
 instance Functor (StFun s) where
fmap h (SF f)= SF g 
where g s = (h x,s')
where (x,s') = f s 

 instance Monad (StFun s) where
return x= SF g  
where g s = (x,s)
SF f = sfh = SF g 
where g s = h s'
where (x,s') = f s
  SF h   = sfh x

 st'apply :: StFun a b - a - b
 st'apply (SF f) s   = x 
where (x,_) = f s


--
-- Primitive State Functions
--

 empty  ::  StFun [a] Bool
 empty   =  SF f
 where  f [] = (True,  [])
f xs = (False, xs)

 item   ::  StFun [a] a
 item=  SF f
 where  f (x:xs) = (x,xs)

 peekitem   ::  StFun [a] a
 peekitem=  SF f
 where  f ys@(x:xs) = (x, ys)

 entropy :: StFun String String
 entropy =  SF f
 where  f ys@('\xFF':'\x00':xs)  = let (as,bs) = f xs in ('\xFF':as,bs) 
f ys@('\xFF': _   )  = ([],ys)
f( x   :xs)  = let (as,bs) = f xs in (x:as,bs) 


--
-- Auxiliary State Functions
--


The Gofer version here used monad comprehensions, which I think
aren't legitimate Haskell. I think the result still looks OK.

 byte :: StFun String Int
 byte = do
 c - item
 return (ord c)  

 word :: StFun String Int
 word = do
   a - byte
   b - byte 
   return (a*256+b)

 nibbles :: StFun String (Int,Int)
 nibbles  = do
  a - byte
  return (byte2nibs a)


--
-- State Function Combinators
--

 -- list::[StFun s r] - StFun s [r]
 list   :: Monad m = [m   a] - m   [a]
 list [] = return []
 list (f:fs) = do
 x-f
 xs-list fs
 return (x:xs)

 exactly :: Monad m = Int - m a - m [a]
 exactly 0 f  = return []
 exactly (n+1) f  = do
  x-f
  xs-exactly n f 
  return (x:xs)

 matrix  :: Monad m = Dim - m a - m (Mat a)
 matrix (y,x) = exactly y . exactly x

 -- many   :: Monad (StFun [a]) = StFun [a] b - StFun [a] [b]
 many f  = do  b  - empty
   y  - f
   ys - many f
   return (if b then [] else y:ys)
 
 sf'uncur  :: (b - StFun a (b,c)) - StFun (a,b) c
 sf'uncur f = SF h
   where h (a,b) = (c, (a',b'))
 where SF g = f b
   ((b',c),a')  = g a

 sf'curry   :: StFun (a,b) c - b - StFun a (b,c)
 sf'curry (SF h) = f
   where f b = SF g
 

RE: eval_thunk_selector: strange selectee 29

2004-03-08 Thread Simon Marlow
 
 For the Haskell program from hell (it kills ghc-6.01 on OpenBSD 3.4,
 hugs on MacOS X and hugs on EPOC)
 
 It's a translation of the (in)famous jpeg.gs script - but I'm yet to
 see whether it works or not, and how fast. But it does 
 compile cleanly.
 
 I can send you a sample JPEG that causes the crash, but I think any
 image will do.

I believe this bug was fixed in GHC 6.2.  Could you try that version and
let us know if it helps?

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


RE: eval_thunk_selector: strange selectee 29

2003-11-11 Thread Josef Svenningsson
On Mon, 10 Nov 2003, Simon Marlow wrote:


  I can confirm that this happens on my solaris machine as
  well. Moreover it
  crashes my computer! I have seen the same crash when working
  with the ffi
  on solaris but haven't been able to reproduce it. What
  happens is this:
  In the window I'm running ghci/my ffi application gets filled with
  prompts. I'm guessing something has started forking like crazy. Anyway
  this eats up all the computer resources and all I can do is
  restart the
  computer.
 
  It would be Very Nice if you could fix the crashing bug as
  this sometimes
  crashes programs running for example wxHaskell. I get very
  uneasy as soon
  as I start to program with the ffi.

 We've fixed the strange selectee 29 bug, but I doubt that could be the
 cause of your infinite forking behaviour.  If you manage to get a
 repeatable example, we can look into it.

Well, if the infinite forking behaviour doesn't depend on the strange
selectee 29 bug then you should be able to use the same program to
provoke ghci to start forking.

Apart from that I attach a small program which exibits the forking
behaviour. It's a wxHaskell application which might make things a little
tricky, but the program itself is just hello world where I forget to
supply the start function in the beginning.

I perhaps should repeat again that the bug is not wxHaskell specific but
the problem seems to be with the ffi as we've encountered the problem
before when using the ffi.

 To prevent it crashing your machine, you should set a limit on the
 number of processes creatable by each user.  To do it locally for
 yourself, use the 'ulimit' shell command.  Most OSs have a way to set
 this globally or on a user-by-user basis too (can't remember exactly how
 Solaris does it, sorry).

Hmmm, the problem is that I don't know either. ulimit doesn't do the job
anyway. I've managed to close the window by pressing Ctrl-D in it now,
which is nice because I don't have to restart my computer :)

/Josef
module Bug where

import Graphics.UI.WX

main = -- start $
 do win - frame [text := Hello World!]
qbutton - button win [text := Quit, on command := close win]
set win [layout := widget qbutton]
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: eval_thunk_selector: strange selectee 29

2003-11-10 Thread Simon Marlow
 
 I can confirm that this happens on my solaris machine as 
 well. Moreover it
 crashes my computer! I have seen the same crash when working 
 with the ffi
 on solaris but haven't been able to reproduce it. What 
 happens is this:
 In the window I'm running ghci/my ffi application gets filled with
 prompts. I'm guessing something has started forking like crazy. Anyway
 this eats up all the computer resources and all I can do is 
 restart the
 computer.
 
 It would be Very Nice if you could fix the crashing bug as 
 this sometimes
 crashes programs running for example wxHaskell. I get very 
 uneasy as soon
 as I start to program with the ffi.

We've fixed the strange selectee 29 bug, but I doubt that could be the
cause of your infinite forking behaviour.  If you manage to get a
repeatable example, we can look into it.

To prevent it crashing your machine, you should set a limit on the
number of processes creatable by each user.  To do it locally for
yourself, use the 'ulimit' shell command.  Most OSs have a way to set
this globally or on a user-by-user basis too (can't remember exactly how
Solaris does it, sorry).

Cheers,
Simon

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


Re: eval_thunk_selector: strange selectee 29

2003-11-07 Thread Josef Svenningsson

I can confirm that this happens on my solaris machine as well. Moreover it
crashes my computer! I have seen the same crash when working with the ffi
on solaris but haven't been able to reproduce it. What happens is this:
In the window I'm running ghci/my ffi application gets filled with
prompts. I'm guessing something has started forking like crazy. Anyway
this eats up all the computer resources and all I can do is restart the
computer.

It would be Very Nice if you could fix the crashing bug as this sometimes
crashes programs running for example wxHaskell. I get very uneasy as soon
as I start to program with the ffi.

Cheers,

/Josef

On Wed, 5 Nov 2003, Yitzchak Gale wrote:

 Hi,

 As requested, I am reporting the following bug that appeared
 during a ghci session on a Debian testing box.

 Regards,
 Yitz
___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version 6.0.1, for Haskell 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.

 Loading package base ... linking ... done.
 Prelude replicate 5 foo
 [foo,foo,foo,foo,foo]
 Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom
 (System.Random.randomR (1::Int, 5; print a}
 [2,1,1,4,3,3,2,4,4,3]
 Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom
 (System.Random.randomR (1::Int, 5; print a}
 [1,2,2,2,1,4,2,1,4,3]
 Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom
 (System.Random.randomR (1::Int, 5; print a}
 [4,1,3,4,2,4,4,2,4,2]
 Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom
 (System.Random.randomR (1::Int, 5; print a}
 [3,4,4,1,5,1,4,2,1,1]
 Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom
 (System.Random.randomR (1::Int, 5; print a}
 [2,4,3,2,2,4,1,4,4,2]
 Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom
 (System.Random.randomR (1::Int, 5; print a}
 [5,4,2,3,4,1,5,3,3,1]
 Prelude do {a - sequence (repeat (System.Random.getStdRandom
 (System.Random.randomR (1::Int, 5; print (take 10 a)}
 Interrupted.
 Prelude do {a - sequence (replicate 10 (System.Random.randomRIO
 (1::Int, 5))); print a}
 [*** Exception: stack overflow
 Prelude do {a - sequence (replicate 10 (System.Random.randomRIO
 (1::Int, 5))); print a}
 interactive: internal error: eval_thunk_selector: strange selectee 29
 Please report this as a bug to [EMAIL PROTECTED],
 or http://www.sourceforge.net/projects/ghc/

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


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


eval_thunk_selector: strange selectee 29

2003-11-06 Thread Yitzchak Gale
Hi,

As requested, I am reporting the following bug that appeared
during a ghci session on a Debian testing box.
Regards,
Yitz
  ___ ___ _
 / _ \ /\  /\/ __(_)
/ /_\// /_/ / /  | |  GHC Interactive, version 6.0.1, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.
Loading package base ... linking ... done.
Prelude replicate 5 foo
[foo,foo,foo,foo,foo]
Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom 
(System.Random.randomR (1::Int, 5; print a}
[2,1,1,4,3,3,2,4,4,3]
Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom 
(System.Random.randomR (1::Int, 5; print a}
[1,2,2,2,1,4,2,1,4,3]
Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom 
(System.Random.randomR (1::Int, 5; print a}
[4,1,3,4,2,4,4,2,4,2]
Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom 
(System.Random.randomR (1::Int, 5; print a}
[3,4,4,1,5,1,4,2,1,1]
Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom 
(System.Random.randomR (1::Int, 5; print a}
[2,4,3,2,2,4,1,4,4,2]
Prelude do {a - sequence (replicate 10 (System.Random.getStdRandom 
(System.Random.randomR (1::Int, 5; print a}
[5,4,2,3,4,1,5,3,3,1]
Prelude do {a - sequence (repeat (System.Random.getStdRandom 
(System.Random.randomR (1::Int, 5; print (take 10 a)}
Interrupted.
Prelude do {a - sequence (replicate 10 (System.Random.randomRIO 
(1::Int, 5))); print a}
[*** Exception: stack overflow
Prelude do {a - sequence (replicate 10 (System.Random.randomRIO 
(1::Int, 5))); print a}
interactive: internal error: eval_thunk_selector: strange selectee 29
   Please report this as a bug to [EMAIL PROTECTED],
   or http://www.sourceforge.net/projects/ghc/

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


RE: eval_thunk_selector: strange selectee 29

2003-11-06 Thread Simon Marlow
 
 interactive: internal error: eval_thunk_selector: strange 
 selectee 29
 Please report this as a bug to [EMAIL PROTECTED],
 or http://www.sourceforge.net/projects/ghc/

This bug has been fixed, the fix will be in 6.2.  Thanks for the report.

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


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
 Please report this as a bug to [EMAIL PROTECTED],
 or http://www.sourceforge.net/projects/ghc/
   Command exited with non-zero status 254

Can you send the code, or is it too large?

Cheers,
Simon


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


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 the directory at that point.
Then make clean, build from scratch again, and if that works then send
us the original snapshot.

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


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 isn't deterministic though, because heap samples happen
based on a timer interrupt, so you might get different results if you
run it multiple times.

 I'm not quite sure what kind of confusion that led to the error (or
 the fact that my run times suddenly were tripled); possibly some old
 .o or .hi file got copied in by mistake?

Possibly, or possibly a recompilation bug (are you using --make?).

 Compiling with -optl-static should only affect the linking stage,
 shouldn't it?  (I.e. the *.o etc. files should be identical?)

Right.

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


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 on a timer interrupt, so you might get different results if you
 run it multiple times.

 I'm not quite sure what kind of confusion that led to the error (or
 the fact that my run times suddenly were tripled); possibly some old
 .o or .hi file got copied in by mistake?

 Possibly, or possibly a recompilation bug (are you using --make?).

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 stumble
over it again, I'll make a copy first.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs