summaryrefslogtreecommitdiffstats
path: root/src/XMonad/Local/Util.hs
blob: 0b754ceed5d459a63fa608d950c26634a211fd2e (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
{-# LANGUAGE DoAndIfThenElse #-}
{-# LANGUAGE UnicodeSyntax   #-}

module XMonad.Local.Util where

import Codec.Binary.UTF8.String
import Control.Monad
import System.IO
import System.Process           (runInteractiveProcess)

import XMonad

-- utilities ******************************************************************
runProcessAndGetOutputs ∷ MonadIO m ⇒ FilePath → [String] → String → m (String, String)
runProcessAndGetOutputs cmd args input = io $ do
    (pin, pout, perr, _) <- runInteractiveProcess (encodeString cmd) (map encodeString args) Nothing Nothing
    hPutStr pin input
    hClose pin
    output <- hGetContents pout
    when (output == output) $ return ()
    err <- hGetContents perr
    when (err == err) $ return ()
    hClose pout
    hClose perr
    -- no need to waitForProcess, we ignore SIGCHLD
    return (output, err)

runProcessAndLogError ∷ MonadIO m ⇒ FilePath → [String] → String → m (Maybe String)
runProcessAndLogError cmd args input = do
    (out, err) <- runProcessAndGetOutputs cmd args input
    if null err then
        return (Just out)
    else do
        io $ hPrint stderr $ "failed to run " ++ cmd ++ ": " ++ err
        return Nothing