[Xmonad] Re: Remote Controlling XMonad: Cases and Materials
Andrea Rossato
mailing_list at istitutocolli.org
Tue Jul 31 05:37:30 EDT 2007
On Mon, Jul 30, 2007 at 08:47:11PM +0200, Tobias Hammerschmidt wrote:
> I like the idea too! Maybe this is a little bit off-topic but why don't
> use a standard like dbus? There are allready some haskell bindings out
> there (http://neugierig.org/software/hdbus/ -- ok they were not updated
> for about a year but maybe it could be a point to start from though).
well, we could have a look at dbus too, but the problem is finding a
way to listening for external commands without blocking XMonad (which
is already blocked, in the "forever" loop, by nextEvent).
I can send commands through a socket (very easy, see example below),
but how can I get XMonad to wait over a socket without blocking the
main thread? Concurrency is not going to give us an easy solution,
AFAIK.
Perhaps it's just me, but I find this problem quite difficult.
If you have any idea please let me know.
All the best,
Andrea
1. Save this as XMonadContrib/ServerMode.hs
-----
module XMonadContrib.ServerMode
import Network
import System.IO
import XMonadContrib.Commands
serverMode :: X ()
serverMode = do
com <- io $ serverMode'
runCommand' com
-- if I now add a line with "serverMode" XMonad is not very useful anymore...;-)
serverMode' :: IO String
serverMode' = do
s <- listenOn (PortNumber 6913)
(h, hn, pn) <- accept s
hSetBuffering h NoBuffering
sClose s
com <- hGetLine h
hClose h
return com
----
2. import it from Config.hs
3. add a key binding that calls serverMode
4. use this code to send commands (you can run one command then
serverMode must be restarted. XMonad will be blocked till a command is
recieved)
---
module Main where
import System.Environment
import System.Exit
import Network
usage :: String -> String
usage n = "Usage: " ++ n ++ " command\nSend a command 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)
sendTo "localhost" (PortNumber 6913) com
exitWith ExitSuccess
More information about the Xmonad
mailing list