"GHC as a library" stalls when nobody is consuming it's output

Mads Lindstrøm mads_lindstroem at yahoo.dk
Sun May 27 10:59:24 EDT 2007


Hi all

While trying to implement a GUI for GHCi, I have run into an annoying
concurrency problems. I think "GHC as a library" is at fault, as it
stalls (maybe some deadlock) when nobody is consuming it's output.

This message is a literate Haskell program, which illustrates the
problem.

This test-program starts a thread which prints an 'A' on stderr every
second. Then it wait three seconds (meanwhile the 'A's are printing),
and runs, via "GHC as a library", the following Haskell code "[1..]".

If I start the program as:

./IsGhcBlocking >/dev/null

everything works fine and the 'A' keeps coming out on stderr.

However, if I do:

./IsGhcBlocking | sleep 10

I only see three 'A's. I believe that is because the sleep-command, do
not consume any input.

The program was tested on Debian Etch running GHC 6.6.

> module Main where
> 

Compile with: ghc -threaded -package ghc-6.6 --make IsGhcBlocking.lhs

> import qualified GHC as GHC
> import qualified Outputable as GHC
> import qualified Packages as GHC
> import qualified DynFlags as GHC
> import qualified ErrUtils as GHC
> 
> import System.IO
> import Control.Concurrent

> -- the path of our GHC 6.6 installation
> path :: FilePath
> -- path = "c:\\ghc-6.6"
> path = "/usr/lib/ghc-6.6/"
> 
> main :: IO()
> main = do let printAs = do threadDelay (10^6)
>                            hPutStrLn stderr "A"
>                            printAs
>           forkOS printAs -- forkIO gives the same result
>           threadDelay (10^6 * 3)
>           session <- initializeSession
>           GHC.runStmt session "[1..]"
>           return ()
> 
> initializeSession =
>     do session <- GHC.newSession GHC.Interactive (Just path)
>        
>        -- initialize the default packages
>        dflags0 <- GHC.getSessionDynFlags session
>        let myLogAction _ locSpec style errMsg = hPutStrLn stderr showMsg where
>                showMsg = GHC.showSDoc $ GHC.withPprStyle style $ GHC.mkLocMessage locSpec errMsg
>            dflags1 = dflags0 { GHC.log_action = myLogAction }
>        (dflags2, packageIds) <- GHC.initPackages dflags1
>        GHC.setSessionDynFlags session dflags2{GHC.hscTarget=GHC.HscInterpreted}
>        GHC.setContext session [] []
>        return session

The stalling becomes a problem, when one wants to interrupt "GHC as a
library"'s runStmt function. One could interrupt "GHC as a library" with
Panic.interruptTargetThread (see
http://article.gmane.org/gmane.comp.lang.haskell.glasgow.user/12289). However,
as "GHC as a library" locks up (stalls, deadlocks) there is no way of
executing Panic.interruptTargetThread.

Some people may suggest that I should always consume the output from
"GHC as a library". But that is easier said than done. Many GUI
libraries (including WxHaskell, which I am using) only allows for one
active thread at a time (see
http://wxhaskell.sourceforge.net/faq.html). Thus my GUI cannot
simultaneously tell "GHC as a library" to interrupt it's execution and
read it's output.

For thus wondering how I can run both a GUI and "GHC as a library", if
WxHaskell is not happy about threading, the answer is that I run the
GUI and "GHC as a library" in separate processes.

Greetings,

Mads Lindstrøm




More information about the Glasgow-haskell-users mailing list