convering Fds to Handles
Sebastien Carlier
sebc@wise-language.org
Fri, 17 May 2002 11:07:38 +0200
--Apple-Mail-3-369586141
Content-Transfer-Encoding: 7bit
Content-Type: text/plain;
charset=US-ASCII;
format=flowed
> I meant do you have an example of your working code.
Sure.
--Apple-Mail-3-369586141
Content-Disposition: attachment;
filename=SubProcess.lhs
Content-Transfer-Encoding: 7bit
Content-Type: application/octet-stream;
x-unix-mode=0755;
name="SubProcess.lhs"
\begin{code}
module SubProcess ( subprocess ) where
import IO
import Posix
import System
\end{code}
``subprocess cmd args input'' executes the command ``cmd'' (searching in
the path) with arguments ``args''. The string ``input'' is fed to this
process on its standard input.
The return value contains the text output be the process on its standard
output.
\begin{code}
subprocess :: FilePath -> [String] -> Maybe String -> IO String
subprocess cmd args minput =
do (cfdi, pfdi, pprei) <- prepareInput minput
(cfdo, pfdo, pposto) <- prepareOutput
let cex = do executeFile cmd True args Nothing
fail ("Cannot execute " ++ cmd)
mpid <- forkProcess
case mpid of
Nothing -> do cfdi ; cfdo ; cex
Just pid -> do pfdi ; pfdo ; pprei ; pposto
prepareInput (Just input) =
do (ri,wi) <- createPipe
let cfdi = do dupTo ri (intToFd 0) ; fdClose wi
pfdi = fdClose ri
pprei = do wih <- fdToHandle wi ; hPutStr wih input ; hClose wih
return (cfdi, pfdi, pprei)
prepareInput Nothing =
return (return (), return (), return ())
prepareOutput =
do (ro,wo) <- createPipe
let cfdo = do dupTo wo (intToFd 1) ; fdClose ro
pfdo = fdClose wo
pposto = do roh <- fdToHandle ro ; hGetContents roh
return (cfdo, pfdo, pposto)
\end{code}
Example:
main =
do cs <- subprocess "/bin/cat" [] (Just $ replicate 10000 a)
putStrLn $ show $ length cs
--Apple-Mail-3-369586141
Content-Transfer-Encoding: quoted-printable
Content-Type: text/plain;
charset=ISO-8859-1;
format=flowed
> localhost% cat Main.hs
>
> module Main where
>
> import SubProcess
>
> main =3D
> do cs <- subprocess "/bin/cat" [] (Just $ replicate 10000 $ 'a')
> putStrLn $ show $ length cs
>
> localhost% ghc -package posix --make -o foo Main.hs
> ghc-5.03: chasing modules from: Main.hs
> Compiling SubProcess ( SubProcess.lhs, SubProcess.o )
> Compiling Main ( Main.hs, ./Main.o )
> ghc: linking ...
> localhost% ./foo
> 10000
> localhost%
Note that is does leave zombie processes, since getProcessStatus is
never called. I think, maybe appending something like the following
to the ouput would work:
output ++ (seq (unsafePerformIO childStatus) [])
where childStatus =3D hClose roh ; getProcessStatus True False pid
You would return childStatus along with the ouput.
If the end of the string is reached, the zombie child will be reaped
automatically.
If you prematurely decide to stop reading the ouput, you have to call
childStatus manually.
I didn't bother to test it, because I didn't care about zombie =
processes.
--
S=E9bastien
--Apple-Mail-3-369586141--