[Haskell-beginners] gtk2hs, inputAdd and forked process

Johann Giwer johanngiwer at web.de
Thu Jan 15 17:26:25 EST 2009


Some times ago I wrote a frontend for mpg123 using python and gtk2. Now
I'm trying to do the same in haskell, but my attempt failed in a very
early stage. 

I like to start a subprocess and read its output via 'inputAdd'. The
(simplified) code looks like this:

module Main (Main.main) where
import System.IO.UTF8 hiding (putStr, putStrLn, print)
import qualified Control.Exception as E
import System.Glib.MainLoop
import System.Environment
import System.Posix.Process
import System.Posix.IO
import System.Posix.Types
import Graphics.UI.Gtk


main :: IO ()
main = do
    name <- getProgName
    argv <- getArgs
    case argv of
        [file] -> play file
        _      -> putStrLn $ "Usage: " ++ name ++ " MP3 FILE"

play :: FilePath -> IO ()
play file = do
    initGUI
    (r0,w0) <- createPipe
    (r1,w1) <- createPipe
    pid <- forkProcess $ do
        closeFd w0
        closeFd r1
        dupTo r0 stdInput
        dupTo w1 stdOutput
        executeFile "mpg123" True ["--output", "alsa", "--remote"] Nothing
    closeFd w1
    closeFd r0

    window <- windowNew
    onDestroy window mainQuit
    button <- buttonNew
    set button [ buttonLabel := "Play" ]
    onClicked button $ do
        w <- fdToHandle w0
        E.handle ( \e -> print e ) $ do
            hPutStrLn w ( "L " ++ file )
        return ()
    set window [ containerChild := button ]
    widgetShowAll window

    inputAdd (fromIntegral r1) [ IOIn,IOPri ] priorityHigh ( readData r1 ) 

    mainGUI

readData :: Fd -> IO Bool
readData h = do
    E.handle ( \e ->  print e >> return True ) $ do
        (s,_) <- fdRead h 1
        putStr s 
        return False

When loading the file in ghci, I get half a second of sound and a couple of
status message lines. Compiled with ghc, this program gives absolute no output
(So threading seams to be the problem?). 

In a next step, I wrapped every IO action in the main process in a call
of 'forkIO' and used MVars for the file name and descriptors, but that
doesn't help. 

Does anybody have experience with 'inputAdd' and forked processes?

Thanks in advance

-Johann




More information about the Beginners mailing list