replacement for popen
Uwe Schmidt
uwe at fh-wedel.de
Tue Apr 12 08:22:00 EDT 2005
in the ghc-6.4 release the posix module is deprecated.
I'm looking for a replacement and tried the
System.Process functions. the following first try
does not work for large files. it blocks if the
file "long.file" does not fit into one os-buffer.
then cat blocks and therefor waitForProcess blocks
------------------------------------
module Main where
import IO
import System
import System.Process
main :: IO ()
main = do
(inpH, outH, errH, pH) <- runInteractiveProcess "cat" ["long.file"] Nothing Nothing
hClose inpH
res <- hGetContents outH
errs <- hGetContents errH
rc <- waitForProcess pH
putStrLn ("rc: " ++ show rc)
putStrLn ("stdout: " ++ res)
putStrLn ("stderr: " ++ errs)
exitWith rc
----------------------
the following version works fine, but it looks very much like a hack
---------------------
module Main where
import IO
import System
import System.Process
main :: IO ()
main = do
(inpH, outH, errH, pH) <- runInteractiveProcess "cat" ["long.filel"] Nothing Nothing
hClose inpH
res <- hGetContents outH
errs <- hGetContents errH
if (length $! res) == 0 -- hack !!!
then return ()
else return ()
if (length $! errs) /= 0 -- hack !!!
then return ()
else return ()
rc <- waitForProcess pH
putStrLn ("rc: " ++ show rc)
putStrLn ("stdout: " ++ res)
putStrLn ("stderr: " ++ errs)
exitWith rc
-------------------------------------
is there a simple replacement for the popen using the System.Process module?
uwe
--
University of Applied Sciences, Wedel, Germany
http://www.fh-wedel.de/~si/index.html
mail:uwe at fh-wedel.de
tel:++49-4103-8048-45
More information about the Libraries
mailing list