aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions
diff options
context:
space:
mode:
authorJan Vornberger <jan.vornberger@informatik.uni-oldenburg.de>2009-12-09 00:44:31 +0100
committerJan Vornberger <jan.vornberger@informatik.uni-oldenburg.de>2009-12-09 00:44:31 +0100
commitf0dd99edb3c66d80a41a443059cbeb85665a22db (patch)
tree67523ffa4945ba91e996bfd544a027d87ba2c29d /XMonad/Actions
parenta1ac655c911f97c3a7bb455ad601426012eeb673 (diff)
downloadXMonadContrib-f0dd99edb3c66d80a41a443059cbeb85665a22db.tar.gz
XMonadContrib-f0dd99edb3c66d80a41a443059cbeb85665a22db.tar.xz
XMonadContrib-f0dd99edb3c66d80a41a443059cbeb85665a22db.zip
BluetileCommands - a list of commands that Bluetile uses to communicate with its dock
Ignore-this: 1a5a5e69c7c37d3ffe8d8e09496568de darcs-hash:20091208234431-594c5-d2e921046b8e3a5af12cb94ab681fcf4c7b45d67.gz
Diffstat (limited to 'XMonad/Actions')
-rw-r--r--XMonad/Actions/BluetileCommands.hs83
1 files changed, 83 insertions, 0 deletions
diff --git a/XMonad/Actions/BluetileCommands.hs b/XMonad/Actions/BluetileCommands.hs
new file mode 100644
index 0000000..a8e0f2b
--- /dev/null
+++ b/XMonad/Actions/BluetileCommands.hs
@@ -0,0 +1,83 @@
+----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Actions.BluetileCommands
+-- Copyright : (c) Jan Vornberger 2009
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : jan.vornberger@informatik.uni-oldenburg.de
+-- Stability : unstable
+-- Portability : not portable
+--
+-- This is a list of selected commands that can be made available using
+-- "XMonad.Hooks.ServerMode" to allow external programs to control
+-- the window manager. Bluetile (<http://projects.haskell.org/bluetile/>)
+-- uses this to enable its dock application to do things like changing
+-- workspaces and layouts.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Actions.BluetileCommands (
+ -- * Usage
+ -- $usage
+ bluetileCommands
+ ) where
+
+import XMonad
+import qualified XMonad.StackSet as W
+import XMonad.Layout.LayoutCombinators
+import System.Exit
+
+-- $usage
+--
+-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Hooks.ServerMode
+-- > import XMonad.Actions.BluetileCommands
+--
+-- Then edit your @handleEventHook@:
+--
+-- > main = xmonad defaultConfig { handleEventHook = serverModeEventHook' bluetileCommands }
+--
+-- See the documentation of "XMonad.Hooks.ServerMode" for details on
+-- how to actually invoke the commands from external programs.
+
+workspaceCommands :: Int -> X [(String, X ())]
+workspaceCommands sid = asks (workspaces . config) >>= \spaces -> return
+ [(("greedyView" ++ show i),
+ activateScreen sid >> windows (W.greedyView i))
+ | i <- spaces ]
+
+layoutCommands :: Int -> [(String, X ())]
+layoutCommands sid = [ ("layout floating" , activateScreen sid >>
+ sendMessage (JumpToLayout "Floating"))
+ , ("layout tiled1" , activateScreen sid >>
+ sendMessage (JumpToLayout "Tiled1"))
+ , ("layout tiled2" , activateScreen sid >>
+ sendMessage (JumpToLayout "Tiled2"))
+ , ("layout fullscreen" , activateScreen sid >>
+ sendMessage (JumpToLayout "Fullscreen"))
+ ]
+
+masterAreaCommands :: Int -> [(String, X ())]
+masterAreaCommands sid = [ ("increase master n", activateScreen sid >>
+ sendMessage (IncMasterN 1))
+ , ("decrease master n", activateScreen sid >>
+ sendMessage (IncMasterN (-1)))
+ ]
+
+quitCommands :: [(String, X ())]
+quitCommands = [ ("quit bluetile", io (exitWith ExitSuccess))
+ , ("quit bluetile and start metacity", restart "metacity" False)
+ ]
+
+bluetileCommands :: X [(String, X ())]
+bluetileCommands = do
+ let restartCommand = [ ("restart bluetile", restart "bluetile" True) ]
+ wscmds0 <- workspaceCommands 0
+ wscmds1 <- workspaceCommands 1
+ return $ restartCommand
+ ++ wscmds0 ++ layoutCommands 0 ++ masterAreaCommands 0 ++ quitCommands
+ ++ wscmds1 ++ layoutCommands 1 ++ masterAreaCommands 1 ++ quitCommands
+
+activateScreen :: Int -> X ()
+activateScreen sid = screenWorkspace (S sid) >>= flip whenJust (windows . W.view)