module System.Plugins.Process (exec, popen) where
import System.Exit
#if __GLASGOW_HASKELL__ >= 604
import System.IO
import System.Process
import Control.Concurrent (forkIO)
#else
import qualified Posix as P
#endif
import qualified Control.Exception as E
exec :: String -> [String] -> IO ([String],[String])
exec f as = do
(a,b,_) <- popen f as (Just [])
return (lines a, lines b)
#if __GLASGOW_HASKELL__ >= 604
type ProcessID = ProcessHandle
popen :: FilePath -> [String] -> Maybe String -> IO (String,String,ProcessID)
popen file args minput =
E.handle (\e -> return ([],show (e::E.IOException), error (show e))) $ do
(inp,out,err,pid) <- runInteractiveProcess file args Nothing Nothing
case minput of
Just input -> hPutStr inp input >> hClose inp
Nothing -> return ()
output <- hGetContents out
errput <- hGetContents err
_ <- forkIO (E.evaluate (length output) >> return ())
_ <- forkIO (E.evaluate (length errput) >> return ())
exitCode <- waitForProcess pid
case exitCode of
ExitFailure code
| null errput -> let errMsg = file ++ ": failed with error code " ++ show code
in return ([],errMsg,error errMsg)
_ -> return (output,errput,pid)
#else
popen :: FilePath -> [String] -> Maybe String -> IO (String,String,P.ProcessID)
popen f s m =
E.handle (\e -> return ([], show (e::IOException), error $ show e )) $ do
x@(_,_,pid) <- P.popen f s m
b <- P.getProcessStatus True False pid
return $ case b of
Nothing -> ([], "process has disappeared", pid)
_ -> x
#endif