blob: 12be81c02e059f282df4179727aff0c52156da43 (
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
|
-----------------------------------------------------------------------------
-- |
-- Module : XMonadContrib.Dzen
-- Copyright : (c) glasser@mit.edu
-- License : BSD
--
-- Maintainer : glasser@mit.edu
-- Stability : unstable
-- Portability : unportable
--
-- Handy wrapper for dzen.
--
-----------------------------------------------------------------------------
module XMonadContrib.Dzen (dzen, dzenScreen) where
import System.Posix.Process (forkProcess, getProcessStatus, createSession)
import System.IO
import System.Process
import System.Exit
import Control.Concurrent (threadDelay)
import Control.Monad.State
import qualified StackSet as W
import XMonad
-- 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
-- output <- hGetContents pout
-- when (output==output) $ return ()
hClose pout
hClose perr
waitForProcess ph
return ()
exitWith ExitSuccess
return ()
getProcessStatus True False pid
return ()
curScreen :: X ScreenId
curScreen = (W.screen . W.current) `liftM` gets windowset
toXineramaArg :: ScreenId -> String
toXineramaArg n = show ( ((fromIntegral n)+1)::Int )
-- Requires dzen >= 0.2.4.
dzen :: String -> X ()
dzen str = curScreen >>= \sc -> dzenScreen sc str
dzenScreen :: ScreenId -> String -> X()
dzenScreen sc str = io $ (runProcessWithInputAndWait "dzen2" ["-xs", screen] str 5000000)
where screen = toXineramaArg sc
|