I suspect that may previous bug report on interactive interpreter 
should be replaced with the following one, which is simple to 
analyse.
This is on

  ghc-6.0.1 
  installed from RPM on  Red Hat Linux release 7.3 (Valhalla),
  i-386 unknown.

Probably, you can reduce the example several times more.

  ghci Main +RTS -M1m -RTS

  ..> : Main
  ..> main
  ... 
  (<interactive>: internal error: thread_stack: 
  weird activation record found on stack: 1564
  Please report this as a bug to [EMAIL PROTECTED] ..

Probably, the interpreter manages memory in a wrong way.
Can you reproduce the effect?

Regards,

-----------------
Serge Mechveliani
[EMAIL PROTECTED]




-------------------------------------------------------------------
main = let xs = [1..9000]           -- change this number
                                    -- and see the message from ghc
           (x's, s1) = sortE compare xs
       in
       putStr $ shows s1 "\n"

type CompValue    = Ordering
type Comparison a = a -> a -> CompValue

mergeE :: Comparison a -> [a] -> [a] -> ([a],Char)
  -- Extended merge:
  -- the transposition sign '+' | '-' is also accumulated.

mergeE cp xs ys = m xs ys $ evenL xs
  where
  m []     ys     _  = (ys,'+')
  m xs     []     _  = (xs,'+')
  m (x:xs) (y:ys) ev = case  cp x y  of

    GT -> (y:zs, mulSign s ev)  where  (zs,s) = m (x:xs) ys ev
    _  -> (x:zs, s)         where  (zs,s) = m xs (y:ys) (invSign ev)

ortE :: Comparison a -> [a] -> ([a],Char)
                -- Extended sort:
                -- the permutation sign '+' | '-'  also accumulates.
sortE _  []  = ([] , '+')
sortE _  [x] = ([x], '+')
sortE cp xs  = let  (ys ,zs) = halve xs
                    (ys',s1) = sortE cp ys
                    (zs',s2) = sortE cp zs
                    (us ,s3) = mergeE cp ys' zs'
               in   (us, mulSign s3 $ mulSign s1 s2)

halve :: [a] -> ([a],[a])
halve    xs  = h [] xs xs  where
                           h ls (x:rs) (_:_:ys) = h (x:ls) rs ys
                           h ls rs     _        = (reverse ls, rs)

mulSign :: Char -> Char -> Char
mulSign    x       y    =  if  x==y  then '+'  else '-'

invSign :: Char -> Char
invSign    '+'  =  '-'
invSign    '-'  =  '+'

evenL :: [a] -> Char
evenL []     = '+'
evenL (_:xs) = invSign $ evenL xs
-------------------------------------------------------------------

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

Reply via email to