aboutsummaryrefslogtreecommitdiffstats
path: root/Run.hs
blob: 2eb16d4ee533c0dce636b737e35a245f13ca74d9 (plain) (blame)
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
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonadContrib.Run
-- Copyright   :  (C) 2007 Spencer Janssen, Andrea Rossato, glasser@mit.edu
-- License     :  BSD-style (see LICENSE)
--
-- Maintainer  :  Christian Thiemann <mail@christian-thiemann.de>
-- Stability   :  unstable
-- Portability :  unportable
--
-- This modules provides several commands to run an external process.
-- It is composed of functions formerly defined in XMonadContrib.Dmenu (by
-- Spenver Jannsen), XMonadContrib.Dzen (by glasser@mit.edu) and
-- XMonadContrib.RunInXTerm (by Andrea Rossato).
--
-----------------------------------------------------------------------------

module XMonadContrib.Run (
                          -- * Usage
                          -- $usage
                          runProcessWithInput,
                          runProcessWithInputAndWait,
                          seconds
                         ) where

import Control.Monad.State (Monad((>>), return), when)
import System.Posix.Process (createSession, forkProcess, executeFile,
			    getProcessStatus)
import Control.Concurrent (threadDelay)
import Control.Exception (try)
import System.Exit (ExitCode(ExitSuccess), exitWith)
import System.IO (IO, FilePath, hPutStr, hGetContents, hFlush, hClose)
import System.Process (runInteractiveProcess, waitForProcess)
import XMonad (X, io, spawn)

-- $usage
-- For an example usage of runInXTerm see XMonadContrib.SshPrompt
--
-- For an example usage of runProcessWithInput see
-- XMonadContrib.{DirectoryPrompt,Dmenu,ShellPrompt,WmiiActions,WorkspaceDir}
--
-- For an example usage of runProcessWithInputAndWait see XMonadContrib.Dzen

-- | Returns Just output if the command succeeded, and Nothing if it didn't.
-- This corresponds to dmenu's notion of exit code 1 for a cancelled invocation.
runProcessWithInput :: FilePath -> [String] -> String -> IO String
runProcessWithInput cmd args input = do
    (pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing
    hPutStr pin input
    hClose pin
    output <- hGetContents pout
    when (output==output) $ return ()
    hClose pout
    hClose perr
    waitForProcess ph
    return output

-- wait is in us
runProcessWithInputAndWait :: FilePath -> [String] -> String -> Int -> IO ()
runProcessWithInputAndWait cmd args input timeout = do
    pid <- forkProcess $ do
       forkProcess $ do -- double fork it over to init
         createSession
         (pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing
         hPutStr pin input
         hFlush pin
         threadDelay timeout
         hClose pin
         hClose pout
         hClose perr
         waitForProcess ph
         return ()
       exitWith ExitSuccess
       return ()
    getProcessStatus True False pid
    return ()

{- | Multiplies by ONE MILLION, for use with runProcessWithInputAndWait.
     Use like:
     > (5.5 `seconds`)
-}
seconds :: Rational -> Int
seconds = fromEnum . (* 1000000)