[Haskell-cafe] Re: On improving libraries: wanted list

Donald Bruce Stewart dons at cse.unsw.edu.au
Wed Dec 13 22:23:32 EST 2006


jgoerzen:
> On Wed, Dec 13, 2006 at 04:19:58PM +1100, Donald Bruce Stewart wrote:
> > > In particular, you seem to be wanting my pipeBoth function.
> > > 
> > > Note that your proposed String -> IO String function type is insufficient
> > > because it does not provide a way to evaluate the return value of the
> > > function.
> > 
> > this kind of functionality seems to be expected by new users (its one of
> > the more common questions on #haskell). 
> > 
> > Is System.Cmd.Utils in a position to be moved into base alongside
> > System.Cmd and System.Process? It seems quite fundamental for getting
> > work done quickly for script-like haskell programs.
> 
> It could go under System.Posix perhaps.  It relies quite heavily on
> functionality provided by the unix package and the System.Posix.* tree.

Can't we do something like this, on top of System.Process?
Do we need unix* stuff anymore?

(modulo getting rid of the non-portable stuff)

    module Lib.Process (popen) where

    import System.Exit
    import System.IO
    import System.Process
    import Control.Concurrent       (forkIO, newEmptyMVar, putMVar, takeMVar)

    import qualified Control.Exception

    popen :: FilePath -> [String] -> Maybe String -> IO (String,String,ExitCode)
    popen file args minput =
        Control.Exception.handle (\e -> return ([],show e,error (show e))) $ do

        (inp,out,err,pid) <- runInteractiveProcess file args Nothing Nothing

        case minput of
            Just input -> hPutStr inp input >> hClose inp -- importante!
            Nothing    -> return ()

        output <- hGetContents out
        errput <- hGetContents err

        forkIO (Control.Exception.evaluate (length output))
        forkIO (Control.Exception.evaluate (length errput))

        e <- Control.Exception.catch (waitForProcess pid) (\_ -> return ExitSuccess)

        return (output,errput,e)


More information about the Haskell-Cafe mailing list