How do you get the process id out of the ProcessHandle in Win XP?
John Vogel
jpvogel1 at gmail.com
Wed Dec 19 21:59:58 EST 2007
Here is what I have tried:
module Main where
import System.Process -- using runInteractiveProcess
import System.Posix.Types
import System.Process.Internals
import Control.Concurrent.MVar
main = do
(input,output,err,ph) <- runInteractiveProcess calc.exe" ([]) Nothing
Nothing
p <- Main.getPID ph
putStrLn $ show p --- The output
getPID :: ProcessHandle -> IO CPid
getPID (ProcessHandle p) = do
(OpenHandle pp) <- takeMVar p
return (toPID pp)
toPID :: PHANDLE -> CPid
toPID ph = toEnum $ fromEnum ph
---------------------------------------------------------------------------------------------------------------------------
But the CPid always returns some const value (like 1904 in cygwin; 1916 in
cmd.exe)
I think, I saw that CPid was a newtype of Ptr ()
So, currently I need to get the process id from CPid or something else.
All help is appreciated.
John
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20071219/d4d33b0d/attachment.htm
More information about the Glasgow-haskell-users
mailing list