Hi all,

I am developing a test management GUI where processes are started and
their output (on stdout and stderr) are shown on corresponding console
windows. The process management worked quite OK with version 0.9.4 but
does no longer work in version 0.10.3 (using ghc 6.8.3 on Windows XP).

The attached small example application shows what happens: with
processExecAsync only garbage is shown on both the stdout and the stderr
console window, with processExecAsyncTimed the stdout console works
fine, but the stderr console shows nothing. Main.hs is the wxHaskell GUI
with two buttons, both calling the application compiled from
Testproc.hs, one using processExecAsync, one using the Timed variant.
The attached makefile builds everything.

If someone with understanding of the internals of wxHaskell could have a
look on this topic, I would be very grateful. Perhaps the (soon?) coming
new wxHaskell version 0.11 will do correctly?

Thanks,
Bernd

module Main where

import System.IO

main = do
  -- hSetBuffering stdout NoBuffering
  -- hSetBuffering stderr NoBuffering
  let loop 0 _ = return ()
      loop n cmd = do cmd n; loop (n-1) cmd
  loop 100 $ \n -> do
    if n `mod` 2 == 0
      then putStrLn $ show n ++ ": Info"
      else hPutStrLn stderr $ show n ++ ": Error"
module Main where

import Graphics.UI.WX
import Graphics.UI.WXCore

main = start $ do
  f <- frame [ text := "Test Process Handling in wxHaskell" ]
  p <- panel f []

  stdoutConsole <- textCtrlRich p [ font := fontFixed {_fontSize = 8} ]
  stderrConsole <- textCtrlRich p [ font := fontFixed {_fontSize = 8} ]

  let write console txt = textCtrlAppendText console txt
      clear c = set c [text := ""]
      clearAll = do clear stdoutConsole; clear stderrConsole
      onEndProcess exitcode = write stdoutConsole $ "\nprocess terminated with 
exitcode " ++ show exitcode
      onStdout txt _ = write stdoutConsole $ "Stdout: " ++ txt
      onStderr txt _ = write stderrConsole $ "Stderr: " ++ txt
      spawnTimed    = processExecAsyncTimed p "testproc" True onEndProcess 
onStdout onStderr
      spawnThreaded = processExecAsync      p "testproc" 100 onEndProcess 
onStdout onStderr

  startThreadedButton <- button p [ text := "processExecAsync"
                                  , on command := do clearAll; spawnThreaded; 
return ()]
  startTimedButton    <- button p [ text := "processExecAsyncTimed"
                                  , on command := do clearAll; spawnTimed; 
return ()]
  -- stopProcessButton  <- button p []

  set p [ layout := column 5
          [ row 5 [widget startThreadedButton, hglue]
          , row 5 [widget startTimedButton, hglue]
          , row 5 [ column 5 [hfill $ label "stdout", fill $ widget 
stdoutConsole]
                  , column 5 [hfill $ label "stderr", fill $ widget 
stderrConsole ]]]
        ]
  set f [ layout := margin 5 $ hfill $ widget p
        , clientSize := sz 860 550
        ]

all:    testproc.exe wxTest.exe

testproc.exe:   Testproc.hs
        ghc --make Testproc.hs -o testproc.exe

wxTest.exe:     Main.hs
        ghc --make -package wx Main.hs -o wxTest.exe

clean:
        rm -f *.exe *.exe.manifest *.o *.hi *~
-------------------------------------------------------------------------
This SF.Net email is sponsored by the Moblin Your Move Developer's challenge
Build the coolest Linux based applications with Moblin SDK & win great prizes
Grand prize is a trip for two to an Open Source event anywhere in the world
http://moblin-contest.org/redirect.php?banner_id=100&url=/
_______________________________________________
wxhaskell-devel mailing list
wxhaskell-devel@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/wxhaskell-devel

Reply via email to