Concurrency issue with dynamic linker in GHC

Vyacheslav Akhmechet coffeemug at gmail.com
Fri Oct 20 23:37:19 EDT 2006


I am running ghc 6.4.2 on a Win32 machine. I'm using hs-plugins in one
thread and a simple getLine loop in another. It appears that getLine
blocks the hs-plugins thread on Win32 (this has been verified to work
fine on freeBSD). I've tried various combinations of -threaded flag
and forkIO/forkOS and always get the undesireable result. Below is the
minimal test case.

module Main where

import Control.Concurrent
import System.Plugins
import System.IO

-- Main loop
main = do
  hSetBuffering stdout NoBuffering
  forkIO blah
  test <- getLine
  putStrLn test

blah = do
  contents <- loadPlugin "Hello"
  putStrLn contents

loadPlugin path = do
  status <- pdynload (path ++ ".o") [] [] "Prelude.String" "myTestSym"
  case status of
    (LoadSuccess _ res) -> return res
    (LoadFailure errors) -> return $ concat errors

--------------------- Hello.hs --------------------

module Hello where

myTestSym :: String
myTestSym = "Hello 2!"


Thanks!


More information about the Glasgow-haskell-users mailing list