blob: db70c6b9f3d16b0fb029ceb24c656f72109f6c14 (
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
|
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Hooks.ServerMode
-- Copyright : (c) Andrea Rossato and David Roundy 2007
-- License : BSD-style (see xmonad/LICENSE)
--
-- Maintainer : andrea.rossato@unibz.it
-- Stability : unstable
-- Portability : unportable
--
-- This is an 'EventHook' that will receive commands from an external
-- client.
--
-- This is the example of a client:
--
-- > import Graphics.X11.Xlib
-- > import Graphics.X11.Xlib.Extras
-- > import System.Environment
-- > import Data.Char
-- >
-- > usage :: String -> String
-- > usage n = "Usage: " ++ n ++ " command number\nSend a command number to a running instance of XMonad"
-- >
-- > main :: IO ()
-- > main = do
-- > args <- getArgs
-- > pn <- getProgName
-- > let com = case args of
-- > [] -> error $ usage pn
-- > w -> (w !! 0)
-- > sendCommand com
-- >
-- > sendCommand :: String -> IO ()
-- > sendCommand s = do
-- > d <- openDisplay ""
-- > rw <- rootWindow d $ defaultScreen d
-- > a <- internAtom d "XMONAD_COMMAND" False
-- > allocaXEvent $ \e -> do
-- > setEventType e clientMessage
-- > setClientMessageEvent e rw a 32 (fromIntegral (read s)) currentTime
-- > sendEvent d rw False structureNotifyMask e
-- > sync d False
--
-- compile with: @ghc --make sendCommand.hs@
--
-- run with
--
-- > sendCommand command number
--
-- For instance:
--
-- > sendCommand 0
--
-- will ask to xmonad to print the list of command numbers in
-- stderr (so you can read it in @~\/.xsession-errors@).
-----------------------------------------------------------------------------
module XMonad.Hooks.ServerMode
( -- * Usage
-- $usage
ServerMode (..)
, serverModeEventHook
, serverModeEventHook'
) where
import Control.Monad (when)
import Data.List
import Data.Monoid
import System.IO
import XMonad
import XMonad.Actions.Commands
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Hooks.ServerMode
-- > import XMonad.Actions.Commands
--
-- Then edit your @handleEventHook@ by adding the 'serverModeEventHook':
--
-- > main = xmonad defaultConfig { handleEventHook = serverModeEventHook }
--
data ServerMode = ServerMode deriving ( Show, Read )
-- | Executes a command of the list when receiving its index via a special ClientMessageEvent
-- (indexing starts at 1)
serverModeEventHook :: Event -> X All
serverModeEventHook = serverModeEventHook' defaultCommands
-- | serverModeEventHook' additionally takes an action to generate the list of
-- commands.
serverModeEventHook' :: X [(String,X ())] -> Event -> X All
serverModeEventHook' cmdAction (ClientMessageEvent {ev_message_type = mt, ev_data = dt}) = do
d <- asks display
a <- io $ internAtom d "XMONAD_COMMAND" False
when (mt == a && dt /= []) $ do
cl <- cmdAction
let listOfCommands = map (uncurry (++)) . zip (map show ([1..] :: [Int])) . map ((++) " - " . fst)
case lookup (fromIntegral (head dt) :: Int) (zip [1..] cl) of
Just (_,action) -> action
Nothing -> mapM_ (io . hPutStrLn stderr) . listOfCommands $ cl
return (All True)
serverModeEventHook' _ _ = return (All True)
|