aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util/Run.hs
blob: 1f544f2b62e18bf0950cc58d75efe3b526c4fbd7 (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
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Util.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 "XMonad.Util.Dmenu" (by
-- Spencer Janssen), "XMonad.Util.Dzen" (by glasser\@mit.edu) and
-- XMonad.Util.RunInXTerm (by Andrea Rossato).
--
-----------------------------------------------------------------------------

module XMonad.Util.Run (
                          -- * Usage
                          -- $usage
                          runProcessWithInput,
                          runProcessWithInputAndWait,
                          safeSpawn,
                          unsafeSpawn,
                          runInTerm,
                          safeRunInTerm,
                          seconds,
                          spawnPipe
                         ) where

import System.Posix.IO
import System.Posix.Process (executeFile)
import Control.Concurrent (threadDelay)
import Control.Exception (try)
import System.IO
import System.Process (runInteractiveProcess, waitForProcess)
import XMonad
import Control.Monad

-- $usage
-- For an example usage of 'runInTerm' see "XMonad.Prompt.Ssh"
--
-- For an example usage of 'runProcessWithInput' see
-- "XMonad.Prompt.DirectoryPrompt", "XMonad.Util.Dmenu",
-- "XMonad.Prompt.ShellPrompt", "XMonad.Actions.WmiiActions",
-- "XMonad.Prompt.WorkspaceDir"
--
-- For an example usage of 'runProcessWithInputAndWait' see
-- "XMonad.Util.Dzen"

-- | Return output if the command succeeded, otherwise return @()@.
-- 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
    doubleFork $ do
        (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 ()

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

-- | safeSpawn bypasses XMonad's 'spawn' command, because 'spawn' passes
-- strings to \/bin\/sh to be interpreted as shell commands. This is
-- often what one wants, but in many cases the passed string will contain
-- shell metacharacters which one does not want interpreted as such (URLs
-- particularly often have shell metacharacters like \'&\' in them). In
-- this case, it is more useful to specify a file or program to be run
-- and a string to give it as an argument so as to bypass the shell and
-- be certain the program will receive the string as you typed it.
-- unsafeSpawn is an alias for XMonad's 'spawn', to remind one that use
-- of it can be, well, unsafe.
-- Examples:
--
-- >     , ((modMask, xK_Print), unsafeSpawn "import -window root png:$HOME/xwd-$(date +%s)$$.png")
-- >     , ((modMask, xK_d    ), safeSpawn "firefox" "")
--
-- Note that the unsafeSpawn example must be unsafe and not safe because
-- it makes use of shell interpretation by relying on @$HOME@ and
-- interpolation, whereas the safeSpawn example can be safe because
-- Firefox doesn't need any arguments if it is just being started.
safeSpawn :: MonadIO m => FilePath -> String -> m ()
safeSpawn prog arg = liftIO (try (doubleFork $ executeFile prog True [arg] Nothing) >> return ())

unsafeSpawn :: MonadIO m => String -> m ()
unsafeSpawn = spawn

-- | Run a given program in the preferred terminal emulator. This uses
-- 'safeSpawn'.
safeRunInTerm :: String -> String -> X ()
safeRunInTerm options command = asks (terminal . config) >>= \t -> safeSpawn t (options ++ " -e " ++ command)

unsafeRunInTerm, runInTerm :: String -> String -> X ()
unsafeRunInTerm options command = asks (terminal . config) >>= \t -> unsafeSpawn $ t ++ " " ++ options ++ " -e " ++ command
runInTerm = unsafeRunInTerm

-- | Launch an external application and return a 'Handle' to its standard input.
spawnPipe :: String -> IO Handle
spawnPipe x = do
    (rd, wr) <- createPipe
    setFdOption wr CloseOnExec True
    h <- fdToHandle wr
    hSetBuffering h LineBuffering
    doubleFork $ do
        dupTo rd stdInput
        executeFile "/bin/sh" False ["-c", x] Nothing
    return h