> If you have some code that triggers the bug, I'd be interested 
> so we can put it in the regression suite.

Hi Simon,

I've whittled it down to the following program. It triggers the
seg fault. The Foo data type is not necessary, but it does make
the program more self contained. You ought to be able to replace
Foo (..) with values from the Prelude.

-- begin Haskell code --
   
   module Main where
   import StablePtr (newStablePtr, freeStablePtr)
   
   data Foo = A | B | C | D
   
   main :: IO ()
   main = do aSPtr <- newStablePtr A
             bSPtr <- newStablePtr B
             cSPtr <- newStablePtr C
             cSPtr' <- newStablePtr C
             freeStablePtr aSPtr
             freeStablePtr bSPtr
             freeStablePtr cSPtr
             freeStablePtr cSPtr'
             aSPtr <- newStablePtr A
             bSPtr <- newStablePtr B
             cSPtr <- newStablePtr C
             dSPtr <- newStablePtr D
             print "Hello World"
      
-- end Haskell code --
   
Cheers,
Bernie.
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to