xmonad-contrib-0.14: Third party extensions for xmonad

Copyright(c) Peter Olson 2013 and Andrea Rossato and David Roundy 2007
LicenseBSD-style (see xmonad/LICENSE)
Maintainerpolson2@hawk.iit.edu
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell98

XMonad.Hooks.ServerMode

Contents

Description

This is an EventHook that will receive commands from an external client. Also consider XMonad.Hooks.EwmhDesktops together with wmctrl.

This is the example of a client:

import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import System.Environment
import System.IO
import Data.Char

main :: IO ()
main = parse True "XMONAD_COMMAND" =<< getArgs

parse :: Bool -> String -> [String] -> IO ()
parse input addr args = case args of
        ["--"] | input -> repl addr
               | otherwise -> return ()
        ("--":xs) -> sendAll addr xs
        ("-a":a:xs) -> parse input a xs
        ("-h":_) -> showHelp
        ("--help":_) -> showHelp
        ("-?":_) -> showHelp
        (a@('-':_):_) -> hPutStrLn stderr ("Unknown option " ++ a)

        (x:xs) -> sendCommand addr x >> parse False addr xs
        [] | input -> repl addr
           | otherwise -> return ()


repl :: String -> IO ()
repl addr = do e <- isEOF
               case e of
                True -> return ()
                False -> do l <- getLine
                            sendCommand addr l
                            repl addr

sendAll :: String -> [String] -> IO ()
sendAll addr ss = foldr (\a b -> sendCommand addr a >> b) (return ()) ss

sendCommand :: String -> String -> IO ()
sendCommand addr s = do
  d   <- openDisplay ""
  rw  <- rootWindow d $ defaultScreen d
  a <- internAtom d addr False
  m <- internAtom d s False
  allocaXEvent $ \e -> do
                  setEventType e clientMessage
                  setClientMessageEvent e rw a 32 m currentTime
                  sendEvent d rw False structureNotifyMask e
                  sync d False

showHelp :: IO ()
showHelp = do pn <- getProgName
              putStrLn ("Send commands to a running instance of xmonad. xmonad.hs must be configured with XMonad.Hooks.ServerMode to work.\n-a atomname can be used at any point in the command line arguments to change which atom it is sending on.\nIf sent with no arguments or only -a atom arguments, it will read commands from stdin.\nEx:\n" ++ pn ++ " cmd1 cmd2\n" ++ pn ++ " -a XMONAD_COMMAND cmd1 cmd2 cmd3 -a XMONAD_PRINT hello world\n" ++ pn ++ " -a XMONAD_PRINT # will read data from stdin.\nThe atom defaults to XMONAD_COMMAND.")

compile with: ghc --make xmonadctl.hs

run with

xmonadctl command

or with

$ xmonadctl
command1
command2
.
.
.
^D

Usage will change depending on which event hook(s) you use. More examples are shown below.

Synopsis

Usage

You can use this module with the following in your ~/.xmonad/xmonad.hs:

import XMonad.Hooks.ServerMode

Then edit your handleEventHook by adding the appropriate event hook from below

serverModeEventHook :: Event -> X All Source #

Executes a command of the list when receiving its index via a special ClientMessageEvent (indexing starts at 1). Sending index 0 will ask xmonad to print the list of command numbers in stderr (so that you can read it in ~/.xsession-errors). Uses XMonad.Actions.Commands as the default.

main = xmonad def { handleEventHook = serverModeEventHook }
xmonadctl 0 # tells xmonad to output command list
xmonadctl 1 # tells xmonad to switch to workspace 1

serverModeEventHook' :: X [(String, X ())] -> Event -> X All Source #

serverModeEventHook' additionally takes an action to generate the list of commands.

serverModeEventHookCmd :: Event -> X All Source #

Executes a command of the list when receiving its name via a special ClientMessageEvent. Uses XMonad.Actions.Commands as the default.

main = xmonad def { handleEventHook = serverModeEventHookCmd }
xmonadctl run # Tells xmonad to generate a run prompt

serverModeEventHookCmd' :: X [(String, X ())] -> Event -> X All Source #

Additionally takes an action to generate the list of commands

serverModeEventHookF :: String -> (String -> X ()) -> Event -> X All Source #

Listens for an atom, then executes a callback function whenever it hears it. A trivial example that prints everything supplied to it on xmonad's standard out:

main = xmonad def { handleEventHook = serverModeEventHookF "XMONAD_PRINT" (io . putStrLn) }
xmonadctl -a XMONAD_PRINT "hello world"