Difference between revisions of "Xmonad/Config archive/adamvo's xmonad.hs"

From HaskellWiki
Jump to navigation Jump to search
(Remove NamedAction stuff, it is too ugly)
(updates for gridselect changes)
 
(20 intermediate revisions by the same user not shown)
Line 1: Line 1:
  +
[[Category:XMonad configuration]]
  +
[[../adamvo's xmobarrc]] (0.9.2)
  +
  +
[[../obtoxmd]] -- script called to temporarily run another wm
  +
 
<haskell>
 
<haskell>
  +
-- current darcs as of 2010-12-31
{-# OPTIONS_GHC -Wall -fno-warn-missing-signatures #-}
 
{-# LANGUAGE ImplicitParams, NoMonomorphismRestriction #-}
+
{-# LANGUAGE
  +
DeriveDataTypeable,
module Main where
 
  +
FlexibleContexts,
  +
FlexibleInstances,
  +
MultiParamTypeClasses,
  +
NoMonomorphismRestriction,
  +
PatternGuards,
  +
ScopedTypeVariables,
  +
TypeSynonymInstances,
  +
UndecidableInstances
  +
#-}
  +
{-# OPTIONS_GHC -W -fwarn-unused-imports -fno-warn-missing-signatures #-}
   
import XMonad
+
import Control.Applicative
import qualified XMonad.StackSet as W
+
import Control.Monad
  +
import Control.Monad.Instances ()
  +
import Control.Monad.Writer
  +
import Data.List
  +
import Data.Maybe
  +
import Data.Traversable(traverse)
  +
import Graphics.X11.Xinerama
 
import qualified Data.Map as M
 
import qualified Data.Map as M
  +
import qualified XMonad.StackSet as W
 
  +
import qualified XMonad.Util.ExtensibleState as XS
-- Update these with: ghc -ddump-minimal-imports
 
  +
import System.IO
import XMonad.Actions.CycleWS(WSType(NonEmptyWS), WSDirection(..),
 
  +
import XMonad
moveTo)
 
import XMonad.Actions.DwmPromote(dwmpromote)
+
import XMonad.Actions.DwmPromote
import XMonad.Actions.FloatSnap(Direction(..), snapGrow, snapMove,
+
import XMonad.Actions.FloatSnap
  +
import XMonad.Actions.GridSelect
snapShrink)
 
import XMonad.Actions.GridSelect(defaultGSConfig, goToSelected)
+
import XMonad.Actions.Search
import XMonad.Actions.Search(mathworld, wikipedia, multi,
+
import XMonad.Actions.SpawnOn
  +
import XMonad.Actions.Submap
promptSearch)
 
import XMonad.Actions.SpawnOn(spawnOn, Spawner, manageSpawn,
+
import XMonad.Actions.TopicSpace
  +
import XMonad.Actions.UpdatePointer
mkSpawner, spawnHere)
 
import XMonad.Actions.Submap(submap)
+
import XMonad.Actions.Warp
import XMonad.Actions.TopicSpace(TopicConfig(..), Topic, (>*>),
+
import XMonad.Hooks.DynamicLog
  +
import XMonad.Hooks.EwmhDesktops
checkTopicConfig, currentTopicAction, currentTopicDir,
 
  +
import XMonad.Hooks.ManageDocks
pprWindowSet, switchNthLastFocused, switchTopic)
 
import XMonad.Hooks.DynamicLog(PP(ppSep, ppCurrent, ppHidden,
+
import XMonad.Hooks.ManageHelpers
  +
import XMonad.Hooks.UrgencyHook
ppVisible, ppLayout, ppTitle, ppUrgent),
 
  +
import XMonad.Layout.BoringWindows
dynamicLogString, defaultPP, xmobarColor, wrap)
 
import XMonad.Hooks.EwmhDesktops(ewmhDesktopsEventHook,
+
import XMonad.Layout.Drawer
  +
import XMonad.Layout.Grid
ewmhDesktopsLogHook)
 
import XMonad.Hooks.ManageDocks(ToggleStruts(ToggleStruts),
+
import XMonad.Layout.IM
  +
import XMonad.Layout.LayoutHints
avoidStruts, manageDocks)
 
import XMonad.Hooks.UrgencyHook(NoUrgencyHook(..), withUrgencyHook)
+
import XMonad.Layout.LayoutModifier
import XMonad.Layout.BoringWindows(boringAuto, focusDown, focusUp)
+
import XMonad.Layout.Magnifier
import XMonad.Layout.LayoutHints(layoutHintsToCentre)
+
import XMonad.Layout.Master
import XMonad.Layout.Mosaic(Aspect(Wider, Taller), mosaic)
+
import XMonad.Layout.Mosaic
import XMonad.Layout.Named(named)
+
import XMonad.Layout.MosaicAlt
import XMonad.Layout.NoBorders(Ambiguity(Screen), lessBorders,
+
import XMonad.Layout.MouseResizableTile
  +
import XMonad.Layout.Named
noBorders)
 
import XMonad.Layout.Simplest(Simplest(..))
+
import XMonad.Layout.NoBorders
import XMonad.Layout.SubLayouts(GroupMsg(UnMergeAll, UnMerge,
+
import XMonad.Layout.PerWorkspace
  +
import XMonad.Layout.Simplest
MergeAll),
 
  +
import XMonad.Layout.SimplestFloat
defaultSublMap, onGroup, pullGroup, subLayout)
 
import XMonad.Layout.Tabbed(defaultTheme, addTabs, shrinkText)
+
import XMonad.Layout.SubLayouts
import XMonad.Layout.WindowNavigation(Navigate(Swap, Go),
+
import XMonad.Layout.Tabbed
  +
import XMonad.Layout.TrackFloating
configurableNavigation, navigateColor)
 
import XMonad.Layout.WorkspaceDir(changeDir, workspaceDir)
+
import XMonad.Layout.WindowNavigation
import XMonad.Prompt(XPConfig(font), XPrompt(showXPrompt),
+
import XMonad.Prompt
  +
import XMonad.Prompt.RunOrRaise
greenXPConfig, mkXPrompt)
 
import XMonad.Prompt.RunOrRaise(runOrRaisePrompt)
+
import XMonad.Prompt.Ssh
import XMonad.Prompt.Shell(shellPrompt)
+
import XMonad.Prompt.Window
import XMonad.Prompt.Ssh(sshPrompt)
+
import XMonad.Prompt.XMonad
import XMonad.Prompt.Window(windowPromptGoto)
 
import XMonad.Prompt.Workspace(workspacePrompt)
 
import XMonad.Prompt.XMonad(xmonadPrompt)
 
import XMonad.Util.Run(spawnPipe)
 
import Graphics.X11.Xinerama(getScreenInfo)
 
import Graphics.X11.ExtraTypes.XF86(xF86XK_AudioLowerVolume,
 
xF86XK_AudioMute, xF86XK_AudioNext, xF86XK_AudioPlay,
 
xF86XK_AudioPrev, xF86XK_AudioRaiseVolume, xF86XK_AudioStop,
 
xF86XK_Sleep)
 
import Data.Map(fromList)
 
import Control.Monad(Monad(return, (>>=), (>>)), Functor(..),
 
(=<<), mapM, sequence, zipWithM_)
 
import Data.IORef(newIORef, readIORef, writeIORef)
 
import Data.List((++), zip, map, concatMap, repeat, zipWith, nub,
 
isPrefixOf, intercalate, isInfixOf)
 
import Data.Maybe(catMaybes)
 
import Data.Ratio((%))
 
import System.IO(IO, Handle, hPutStrLn)
 
 
import XMonad.Util.EZConfig
 
import XMonad.Util.EZConfig
  +
import XMonad.Util.Replace
  +
import XMonad.Util.Run
  +
   
 
main :: IO ()
 
main :: IO ()
 
main = do
 
main = do
sp <- mkSpawner
+
replace
mpdHost <- newIORef "localhost"
 
let ?spawner = sp
 
?mpdHost = mpdHost
 
 
checkTopicConfig myTopics myTopicConfig
 
checkTopicConfig myTopics myTopicConfig
  +
let urgency
xmonad . withUrgencyHook NoUrgencyHook . myConfig
 
=<< mapM xmobarScreen
+
| True = withUrgencyHook FocusHook
  +
| True = withUrgencyHook NoUrgencyHook
=<< getScreens
 
  +
xmonad . ewmh . urgency . myConfig
  +
=<< mapM xmobarScreen =<< getScreens
  +
  +
sofficeToolbox = className =? "OpenOffice.org 3.1"
  +
<&&> isInProperty "WM_PROTOCOLS" "WM_TAKE_FOCUS"
   
 
myConfig hs = let c = defaultConfig {
 
myConfig hs = let c = defaultConfig {
 
layoutHook = myLayout
 
layoutHook = myLayout
, focusedBorderColor = "#ff0000"
+
, focusFollowsMouse = False
  +
, focusedBorderColor = "red"
  +
, startupHook = do
  +
return () -- supposedly to avoid inf. loops with checkKeymap
  +
checkKeymap (myConfig []) (myKeys c)
 
, terminal = "urxvt"
 
, terminal = "urxvt"
 
, modMask = mod4Mask
 
, modMask = mod4Mask
, logHook = ewmhDesktopsLogHook >> myLogHook hs
+
, logHook = do
  +
multiPP'
, handleEventHook = ewmhDesktopsEventHook
 
  +
(mergePPOutputs [XMonad.Actions.TopicSpace.pprWindowSet myTopicConfig,
  +
dynamicLogString . onlyTitle])
  +
myPP
  +
myPP{ ppTitle = const "" }
  +
hs
  +
updatePointer (TowardsCentre 0.2 0.2)
  +
, handleEventHook = ewmhDesktopsEventHook <+> fullscreenEventHook <+> focusFollow <+>
  +
(\e -> case e of
  +
PropertyEvent{ ev_window = w } -> do
  +
isURXVT <- runQuery (className =? "URxvt") w
  +
if not isURXVT then hintsEventHook e else return (All True)
  +
_ -> return (All True))
 
, workspaces = myTopics
 
, workspaces = myTopics
, manageHook = composeAll
+
, manageHook = mconcat
[ manageSpawn ?spawner
+
[manageSpawn
, manageDocks
+
,isFullscreen --> doFullFloat
, fmap (isInfixOf "Gran Paradiso") className --> doShift "web"
+
-- ,className =? "MPlayer" --> doFullFloat
  +
,className =? "XTerm" --> queryMerge (className =? "XTerm")
]
 
  +
,manageDocks
} in additionalKeys c (myKeys c)
 
  +
]
  +
} in additionalKeysP c (myKeys c)
   
 
myXPConfig :: XPConfig
 
myXPConfig :: XPConfig
 
myXPConfig = greenXPConfig { font = "xft:Profont:pixelsize=15:autohint=true" }
 
myXPConfig = greenXPConfig { font = "xft:Profont:pixelsize=15:autohint=true" }
  +
  +
gsConfig = defaultGSConfig { gs_navigate = fix $ \self ->
  +
let navKeyMap = M.mapKeys ((,) 0) $ M.fromList $
  +
[(xK_Escape, cancel)
  +
,(xK_Return, select)
  +
,(xK_slash , substringSearch self)]
  +
++
  +
map (\(k,a) -> (k,a >> self))
  +
[(xK_Left , move (-1,0 ))
  +
,(xK_h , move (-1,0 ))
  +
,(xK_n , move (-1,0 ))
  +
,(xK_Right , move (1,0 ))
  +
,(xK_l , move (1,0 ))
  +
,(xK_i , move (1,0 ))
  +
,(xK_Down , move (0,1 ))
  +
,(xK_j , move (0,1 ))
  +
,(xK_e , move (0,1 ))
  +
,(xK_Up , move (0,-1 ))
  +
,(xK_u , move (0,-1 ))
  +
,(xK_y , move (-1,-1))
  +
,(xK_m , move (1,-1 ))
  +
,(xK_space , setPos (0,0))
  +
]
  +
in makeXEventhandler $ shadowWithKeymap navKeyMap (const self) }
  +
  +
data ExpandEdges a = ExpandEdges Int deriving (Read,Show)
  +
  +
instance LayoutModifier ExpandEdges Window where
  +
modifyLayout (ExpandEdges n) ws (Rectangle x y w h) = let
  +
bigRect = Rectangle (x - fromIntegral n) (y - fromIntegral n)
  +
(w + 2*fromIntegral n) (h + 2*fromIntegral n)
  +
in
  +
runLayout ws bigRect
  +
  +
-- | push edges off-screen
  +
expandEdges n layout = ModifiedLayout (ExpandEdges n) layout
  +
  +
   
 
-------------------- Layout ----------------------------------
 
-------------------- Layout ----------------------------------
myLayout = workspaceDir "~" $ avoidStruts
+
myLayout =
  +
trackFloating . smartBorders
$ named "M" mos ||| named "F" (noBorders Full)
 
  +
. onWorkspace "movie" (magnifier m ||| layoutHints Full)
where mos = lessBorders Screen
 
$ addTabs shrinkText defaultTheme
+
. avoidStruts
  +
. onWorkspace "test" (multimastered 2 (1/100) (1/2) Grid)
$ configurableNavigation (navigateColor "#ffff00")
 
$ boringAuto
+
. onWorkspace "gimp" (named "G" gimp)
$ subLayout [] (Simplest ||| Tall 1 (1%6) 0.5)
+
. onWorkspace "xm-conf" ((nav $ ModifiedLayout (ExpandEdges 1) (Tall 1 0.3 0.5)) ||| Full)
$ layoutHintsToCentre
+
$ m ||| named "F" (noBorders Full)
  +
where nav = configurableNavigation (navigateColor "#ffff00")
$ mosaic 1.5 [5,4,2]
 
  +
m = named "M"
  +
. lessBorders Screen
  +
. layoutHintsToCenter
  +
. addTabs shrinkText defaultTheme
  +
. nav
  +
. boringAuto
  +
. subLayout [] (Simplest ||| simplestFloat)
  +
$ mosaic 1.5 [7,5,2]
  +
gimp = nav
  +
. onLeft (simpleDrawer 0.01 0.3 $ Role "gimp-toolbox")
  +
. withIM 0.15 (Role "gimp-dock")
  +
. addTabs shrinkText defaultTheme
  +
. nav
  +
. boringAuto
  +
. subLayout [] Simplest
  +
$ mouseResizableTile ||| Full
 
--------------------------------------------------------------
 
--------------------------------------------------------------
 
 
-------------------- Keys ------------------------------------
 
-------------------- Keys ------------------------------------
myKeys c@(XConfig { modMask = modm }) =
+
myKeys c =
[ ((modm, xK_Left), withFocused $ snapMove L Nothing)
+
[("M-<Left>" , withFocused $ snapMove L Nothing )
, ((modm, xK_Right), withFocused $ snapMove R Nothing)
+
,("M-<Right>" , withFocused $ snapMove R Nothing )
, ((modm, xK_Up), withFocused $ snapMove U Nothing)
+
,("M-<Up>" , withFocused $ snapMove U Nothing )
, ((modm, xK_Down), withFocused $ snapMove D Nothing)
+
,("M-<Down>" , withFocused $ snapMove D Nothing )
, ((modm .|. shiftMask, xK_Left), withFocused $ snapShrink R Nothing)
+
,("M-S-<Left>" , withFocused $ snapShrink R Nothing)
, ((modm .|. shiftMask, xK_Right), withFocused $ snapGrow R Nothing)
+
,("M-S-<Right>", withFocused $ snapGrow R Nothing)
, ((modm .|. shiftMask, xK_Up), withFocused $ snapShrink D Nothing)
+
,("M-S-<Up>" , withFocused $ snapShrink D Nothing)
, ((modm .|. shiftMask, xK_Down), withFocused $ snapGrow D Nothing)
+
,("M-S-<Down>" , withFocused $ snapGrow D Nothing)
   
,((modm .|. controlMask, xK_o), withFocused $ sendMessage . UnMerge)
+
, ("M-l", withFocused (sendMessage . expandWindowAlt) >> sendMessage Expand)
,((modm .|. shiftMask .|. controlMask, xK_o), withFocused $ sendMessage . UnMergeAll)
+
, ("M-h", withFocused (sendMessage . shrinkWindowAlt) >> sendMessage Shrink)
,((modm .|. controlMask, xK_m), withFocused $ sendMessage . MergeAll)
 
,((modm .|. controlMask, xK_period), onGroup W.focusDown')
 
,((modm .|. controlMask, xK_comma), onGroup W.focusUp')
 
   
,((modm, xK_semicolon), sendMessage Taller)
+
,("M-;", withFocused (sendMessage . tallWindowAlt) >> sendMessage Taller)
,((modm, xK_o), sendMessage Wider)
+
,("M-o", withFocused (sendMessage . wideWindowAlt) >> sendMessage Wider )
   
  +
,("M-v", toggleFF)
,((modm, xK_x), submap $ M.fromList subMaps)
 
,((modm, xK_s), submap $ defaultSublMap c)
 
   
  +
,("M-S-b", restart "/home/aavogt/bin/obtoxmd" True)
,((modm, xK_period), moveTo Next NonEmptyWS)
 
,((modm, xK_comma ), moveTo Prev NonEmptyWS)
+
,("M-S-d", restart "urxvt -e xmonad" False)
,((modm .|. shiftMask, xK_period), focusDown)
 
,((modm .|. shiftMask, xK_comma ), focusUp)
 
   
  +
,("M-S-o" , withFocused $ sendMessage . UnMerge )
,((modm .|. shiftMask, xK_a), currentTopicAction myTopicConfig)
 
  +
,("M-S-C-o", withFocused $ sendMessage . UnMergeAll)
,((modm, xK_a), goToSelected defaultGSConfig)
 
  +
,("M-C-m" , withFocused $ sendMessage . MergeAll )
,((modm, xK_Tab), switchNthLastFocused myTopicConfig 1)
 
,((modm, xK_g ), promptedGoto)
+
,("M-C-." , onGroup W.focusDown')
  +
,("M-C-," , onGroup W.focusUp' )
   
  +
,("M-p", shellPromptHere myXPConfig)
,((modm, xK_Return), dwmpromote)
 
,((modm .|. shiftMask, xK_Return), spawnShell)
+
,("M-x", submap $ M.fromList subMaps)
  +
,("M-g", submap $ defaultSublMap c )
,((modm .|. shiftMask, xK_g ), promptedShift)
 
,((modm, xK_q), spawn "~/.xmonad/xmonad-recomp.lhs && xmonad --restart")
 
,((modm .|. shiftMask, xK_q), spawn "xmonad --recompile && xmonad --restart")
 
,((0, xK_Print), spawn "scrot")
 
   
  +
,("M-S-.", focusDown)
  +
,("M-S-,", focusUp )
  +
  +
,("M-S-a", currentTopicAction myTopicConfig)
  +
,("M-a", warpToCentre >> goToSelected gsConfig)
  +
-- workaround
  +
,("M-<Tab>", switchNthLastFocused myTopicConfig . succ . length . W.visible . windowset =<< get )
  +
  +
,("M-s" , warpToCentre >> promptedGoto )
  +
,("M-S-s", warpToCentre >> promptedShift)
  +
  +
,("M-b", sendMessage ToggleStruts)
  +
,("M-<Return>", dwmpromote)
  +
,("M-S-<Return>", spawnShell)
  +
-- don't force a recompile, if nothing has changed (xmonad --recompile runs XMonad.recompile True)
  +
,("M-q", spawn "ghc -e ':m +XMonad Control.Monad System.Exit' -e 'flip unless exitFailure =<< recompile False' && xmonad --restart")
  +
,("M-S-q", spawn "~/wip/x11-wm/xmonad/rebuild.sh")
  +
,("<Print>", spawn "scrot")
 
]
 
]
 
++
 
++
concatMap (\(m,f) -> lrud (modm .|. m) f)
+
concatMap (\(m,f) -> lrud ("M-"++m) f)
[(shiftMask, (sendMessage . Swap))
+
[("S-" , sendMessage . Swap)
,(controlMask, (sendMessage . pullGroup))
+
,("C-" , sendMessage . pullGroup)
,(0, (sendMessage . Go))
+
,("S-C-", sendMessage . pushWindow)
]
+
,("" , sendMessage . Go)]
 
++ mediaKeys ++
 
++ mediaKeys ++
[((m .|. modm, key), screenWorkspace sc >>= flip whenJust (windows . f)) |
+
[("M-"++m++[key], screenWorkspace sc >>= flip whenJust (windows . f))
(f, m) <- [(W.view, 0), (W.shift, shiftMask)],
+
| (f, m) <- [(W.view, ""), (W.shift, "S-")]
(key, sc) <- zip [xK_w, xK_f, xK_p] ([0 .. ])]
+
, (key, sc) <- zip "wf" [0 .. ]]
 
++
 
++
[ ((modm, k), switchNthLastFocused myTopicConfig i)
+
[ ("M-"++m++[k], a i)
  +
| (a, m) <- [(switchNthLastFocused myTopicConfig,""),(shiftNthLastFocused, "S-")]
| (i, k) <- zip [1..] [xK_1 .. xK_9]]
 
  +
, (i, k) <- zip [1..] "123456789"]
   
 
-- helper for windowNavigation keys
 
-- helper for windowNavigation keys
 
-- note: with colemak neiu are placed where jkli are with qwerty layout
 
-- note: with colemak neiu are placed where jkli are with qwerty layout
lrud :: a -> (Direction -> b) -> [((a, KeySym), b)]
+
lrud :: String -> (Direction2D -> b) -> [(String, b)]
 
lrud m cmd = zip ks cmds
 
lrud m cmd = zip ks cmds
 
where
 
where
ks = zip (repeat m) [xK_n,xK_i,xK_u,xK_e]
+
ks = map (\x -> m ++ [x]) "niue"
 
cmds = zipWith ($) (repeat cmd) [L,R,U,D]
 
cmds = zipWith ($) (repeat cmd) [L,R,U,D]
   
 
subMaps = [((0, xK_o), runOrRaisePrompt myXPConfig),
 
subMaps = [((0, xK_o), runOrRaisePrompt myXPConfig),
((0, xK_p), shellPrompt myXPConfig),
+
((0, xK_p), shellPromptHere myXPConfig),
 
((0, xK_x), xmonadPrompt myXPConfig),
 
((0, xK_x), xmonadPrompt myXPConfig),
 
((0, xK_z), sshPrompt myXPConfig),
 
((0, xK_z), sshPrompt myXPConfig),
Line 182: Line 272:
 
((0, xK_s), promptSearch myXPConfig multi),
 
((0, xK_s), promptSearch myXPConfig multi),
 
((0, xK_m), promptSearch myXPConfig mathworld),
 
((0, xK_m), promptSearch myXPConfig mathworld),
((0, xK_d), changeDir myXPConfig),
 
 
((0, xK_b), sendMessage ToggleStruts),
 
((0, xK_b), sendMessage ToggleStruts),
 
((0, xK_f), withFocused $ windows . W.sink),
 
((0, xK_f), withFocused $ windows . W.sink),
 
((0, xK_v), refresh),
 
((0, xK_v), refresh),
((0, xK_c), asks config >>= spawnHere ?spawner . terminal),
+
((0, xK_c), asks config >>= spawnHere . terminal),
 
((0, xK_k), kill)
 
((0, xK_k), kill)
 
]
 
]
   
  +
mediaKeys = [((0, xF86XK_AudioPlay), mpcAct "toggle"),
 
  +
amarok = False
((0, xF86XK_AudioStop), hostPrompt),
 
  +
((0, xF86XK_AudioNext), mpcAct "next"),
 
  +
mediaKeys = [("<XF86AudioPlay>", do mpcAct "toggle"; when amarok $ spawn "amarok -t"),
((0, xF86XK_AudioPrev), mpcAct "prev"),
 
((0, xF86XK_AudioMute), spawn " -t"),
+
("<XF86AudioStop>", promptHost),
((shiftMask, xF86XK_AudioMute), spawn "~/bin/speakers.sh"),
+
("<XF86AudioNext>", do mpcAct "next"; when amarok $ spawn "amarok -f"),
((0, xF86XK_AudioLowerVolume), spawn "ossmix vmix0-outvol -- -1"),
+
("<XF86AudioPrev>", do mpcAct "prev"; when amarok $ spawn "amarok -r"),
((shiftMask, xF86XK_AudioLowerVolume), spawn "ossmix vmix0-outvol -- -0.1"),
+
("<XF86AudioMute>", spawn "ossmix vmix0-outvol 0"),
((0, xF86XK_AudioRaiseVolume), spawn "ossmix vmix0-outvol +1"),
+
("<XF86AudioLowerVolume>", spawn "amixer sset PCM 1-"),
((shiftMask, xF86XK_AudioRaiseVolume), spawn "ossmix vmix0-outvol +0.1"),
+
("<XF86AudioRaiseVolume>", spawn "amixer sset PCM 1+"),
((0, xF86XK_Sleep), spawn "sudo sh -c 'echo mem > /sys/power/state'")]
+
("<XF86Sleep>", spawn "sudo pm-suspend")
  +
]
 
where mpcAct c = do
 
where mpcAct c = do
h <- io $ readIORef ?mpdHost
+
h <- XS.gets hostPrompt
 
spawn $ unwords ["export MPD_HOST="++h,";","mpc",c]
 
spawn $ unwords ["export MPD_HOST="++h,";","mpc",c]
   
-- Prompt for host
+
-- Prompt for mpd host
data HostPrompt = HostPrompt
+
newtype HostPrompt = HostPrompt { hostPrompt :: String } deriving (Read,Show,Typeable)
instance XPrompt HostPrompt where showXPrompt _ = "Pick MPD Host: "
+
instance ExtensionClass HostPrompt where
  +
initialValue = HostPrompt "/home/aavogt/.mpd/socket"
hostPrompt = mkXPrompt HostPrompt myXPConfig (return . compl) (io . writeIORef ?mpdHost)
 
  +
extensionType = PersistentExtension
where compl s = nub $ filter (s `isPrefixOf`) ["localhost","dell"]
 
   
  +
instance XPrompt HostPrompt where showXPrompt _ = "Pick MPD Host: "
  +
promptHost = mkXPrompt (HostPrompt "") myXPConfig (return . compl) (XS.put . HostPrompt)
  +
where compl s = nub $ filter (s `isPrefixOf`) ["127.0.0.1","dell"]
 
--------------------------------------------------------------
 
--------------------------------------------------------------
  +
  +
warpToCentre = gets (W.screen . W.current . windowset) >>= \x -> warpToScreen x 0.5 0.5
   
 
-------------------- Support for per-screen xmobars ---------
 
-------------------- Support for per-screen xmobars ---------
-- Some parts of this will merged into contrib sometime
+
-- Some parts of this should be merged into contrib sometime
 
getScreens :: IO [Int]
 
getScreens :: IO [Int]
getScreens = withDisplay' $ fmap (enumFromTo 0 . pred . length) . getScreenInfo
+
getScreens = openDisplay "" >>= liftA2 (<*) f closeDisplay
where withDisplay' f = do
+
where f = fmap (zipWith const [0..]) . getScreenInfo
x <- openDisplay ""
 
res <- f x
 
closeDisplay x
 
return res
 
   
-- | Output to each handle what would be seen when viewing the screen with that
+
multiPP :: PP -- ^ The PP to use if the screen is focused
-- index. If the workspace is focused use the first PP, otherwise use the
+
-> PP -- ^ The PP to use otherwise
  +
-> [Handle] -- ^ Handles for the status bars, in order of increasing X
-- second PP.
 
  +
-- screen number
multiPP :: PP -> PP -> [Handle] -> X ()
 
  +
-> X ()
 
multiPP = multiPP' dynamicLogString
 
multiPP = multiPP' dynamicLogString
   
Line 232: Line 324:
 
multiPP' dynlStr focusPP unfocusPP handles = do
 
multiPP' dynlStr focusPP unfocusPP handles = do
 
state <- get
 
state <- get
  +
let pickPP :: WorkspaceId -> WriterT (Last XState) X String
let takeLength = zipWith const
 
  +
pickPP ws = do
viewWs n = put state { windowset = W.view n $ windowset state }
 
focused = W.tag . W.workspace . W.current $ windowset state
+
let isFoc = (ws ==) . W.tag . W.workspace . W.current $ windowset state
choosePP w = if w == focused then focusPP else unfocusPP
+
put state{ windowset = W.view ws $ windowset state }
  +
out <- lift $ dynlStr $ if isFoc then focusPP else unfocusPP
io . zipWithM_ hPutStrLn handles
 
=<< mapM (\w -> viewWs w >> dynlStr (choosePP w)) . catMaybes
+
when isFoc $ get >>= tell . Last . Just
  +
return out
=<< mapM screenWorkspace ([0..] `takeLength` handles)
 
put state
+
traverse put . getLast
  +
=<< execWriterT . (io . zipWithM_ hPutStrLn handles <=< mapM pickPP) . catMaybes
  +
=<< mapM screenWorkspace (zipWith const [0..] handles)
  +
return ()
   
mergePPOutputs :: PP -> [PP -> X String] -> X String
+
mergePPOutputs :: [PP -> X String] -> PP -> X String
mergePPOutputs pp = fmap (intercalate (ppSep pp)) . sequence . map ($ pp)
+
mergePPOutputs x pp = fmap (intercalate (ppSep pp)) . sequence . sequence x $ pp
   
 
onlyTitle :: PP -> PP
 
onlyTitle :: PP -> PP
onlyTitle pp = defaultPP { ppCurrent = const "", ppHidden = const "", ppVisible = const "", ppLayout = ppLayout pp, ppTitle = ppTitle pp }
+
onlyTitle pp = defaultPP { ppCurrent = const ""
  +
, ppHidden = const ""
  +
, ppVisible = const ""
  +
, ppLayout = ppLayout pp
  +
, ppTitle = ppTitle pp }
   
-- | Requires a recent addition to xmobar (>0.9.2)
+
-- | Requires a recent addition to xmobar (>0.9.2), otherwise you have to use
  +
-- multiple configuration files, which gets messy
 
xmobarScreen :: Int -> IO Handle
 
xmobarScreen :: Int -> IO Handle
xmobarScreen = spawnPipe . ("xmobar -x " ++) . show
+
xmobarScreen = spawnPipe . ("~/.cabal/bin/xmobar -x " ++) . show
 
myLogHook :: (?spawner::Spawner) => [Handle] -> X ()
 
myLogHook = multiPP'
 
(flip mergePPOutputs [pprWindowSet myTopicConfig,dynamicLogString . onlyTitle])
 
myPP { ppTitle = xmobarColor "orange" "" }
 
myPP { ppTitle = const "" }
 
   
 
myPP :: PP
 
myPP :: PP
  +
myPP = sjanssenPP { ppLayout = xmobarColor "orange" "", ppUrgent = xmobarColor "red" "" . ('^':) }
myPP = defaultPP
 
{ ppCurrent = xmobarColor "white" ""
 
, ppSep = " : "
 
, ppLayout = xmobarColor "green" ""
 
, ppVisible = xmobarColor "white" "" . wrap "(" ")"
 
, ppUrgent = xmobarColor "red" "" . ("^"++)}
 
 
--------------------------------------------------------------
 
--------------------------------------------------------------
   
Line 269: Line 358:
 
myTopics :: [Topic]
 
myTopics :: [Topic]
 
myTopics =
 
myTopics =
  +
[ "a"
[ "dashboard" -- the first one
 
  +
, "web"
, "admin", "build", "cleaning", "conf", "darcs", "haskell", "irc"
 
  +
, "haskell"
, "mail", "movie", "music", "talk", "text", "tools", "web"
 
  +
, "mail"
, "yi", "documents", "pdf", "xmobar", "xmonad-conf", "xmonad-newconfig", "xmonad-contrib"
 
, "gtk-gnutella", "gitit"
+
, "irc"
  +
, "xm-conf"
  +
, "gimp"
  +
, "gitit"
  +
, "admin"
  +
, "movie"
  +
, "music"
  +
, "pdf"
  +
, "doc"
  +
, "xmc"
  +
, "xme"
  +
, "xm"
  +
, "xmobar"
  +
, "wip"
  +
, "test"
 
]
 
]
   
  +
myTopicConfig :: (?spawner::Spawner) => TopicConfig
 
 
myTopicConfig = TopicConfig
 
myTopicConfig = TopicConfig
 
{ topicDirs = M.fromList $
 
{ topicDirs = M.fromList $
[ ("conf", "conf")
+
[ ("a", "./")
, ("dashboard", "./")
 
, ("yi", "wip/dev-haskell/yi")
 
, ("darcs", "wip/dev-haskell/darcs")
 
 
, ("haskell", "haskell")
 
, ("haskell", "haskell")
, ("xmonad-conf", ".xmonad")
+
, ("xm-conf", ".xmonad")
, ("xmonad-newconfig", "wip/x11-wm/xmonad/core/xmonad-newconfig")
+
, ("xme", "wip/x11-wm/xmonad/extras/xmonad-extras/XMonad")
, ("xmonad-contrib", "wip/x11-wm/xmonad/contrib/XMonadContrib/XMonad")
+
, ("xm", "wip/x11-wm/xmonad/core/xmonad")
  +
, ("xmc", "wip/x11-wm/xmonad/contrib/XMonadContrib/XMonad")
 
, ("xmobar", "wip/x11-wm/xmobar")
 
, ("xmobar", "wip/x11-wm/xmobar")
, ("tools", "wip/tools")
 
 
, ("movie", "media/movie")
 
, ("movie", "media/movie")
 
, ("music", "media/music")
 
, ("music", "media/music")
, ("documents", "doc")
+
, ("doc", "doc")
 
, ("pdf", "ref")
 
, ("pdf", "ref")
, ("gtk-gnutella", ".gtk-gnutella-downloads")
 
 
, ("gitit", "wip/gitit")
 
, ("gitit", "wip/gitit")
  +
, ("gimp", "./")
  +
, ("wip", "wip")
 
]
 
]
 
, defaultTopicAction = const $ spawnShell >*> 2
 
, defaultTopicAction = const $ spawnShell >*> 2
, defaultTopic = "dashboard"
+
, defaultTopic = "a"
 
, maxTopicHistory = 10
 
, maxTopicHistory = 10
 
, topicActions = M.fromList $
 
, topicActions = M.fromList $
[ ("haskell", spawnShell >*> 2 >>
+
[ ("xm-conf", spawnShellIn ".xmonad/lib/XMonad/Layout" >>
spawnShellIn "wip/dev-haskell/ghc")
 
, ("xmonad-conf", spawnShellIn ".xmonad/lib/XMonad/Layout" >>
 
 
spawn "urxvt -e vim ~/.xmonad/xmonad.hs")
 
spawn "urxvt -e vim ~/.xmonad/xmonad.hs")
, ("xmonad-contrib", spawnShell >*> 2)
+
, ("xmc" , spawnShell >*> 2)
, ("xmonad-newconfig", spawn "urxvt -e vim ~/wip/x11-wm/xmonad/core/xmonad-newconfig/XMonad/ConfigMonad.hs")
+
, ("xmobar" , spawnShellIn "wip/x11-wm/xmobar/Plugins" >*> 2)
  +
, ("music" , spawn "urxvt -e ncmpc -h /home/aavogt/.mpd/socket" >> spawn "export MPD_HOST=192.168.1.2; mpc && urxvt -e ncmpc -h 192.168.1.2")
, ("xmobar", spawnShellIn "wip/x11-wm/xmobar/Plugins" >*> 2)
 
, ("music", spawn "urxvt -e ncmpc" >> spawn "urxvt -e ncmpc -h 192.168.1.2")
+
, ("mail" , spawnOn "mail" "urxvt -e mutt")
, ("mail", spawn "urxvt -e mutt")
+
, ("irc" , spawnOn "irc" "urxvt --title irc -e ssh engage")
, ("irc", spawn "urxvt -e ssh aavogt@engage.uwaterloo.ca")
+
, ("web" , spawnOn "web" "firefox")
, ("dashboard", spawnShell)
+
, ("pdf" , spawnOn "pdf" "okular")
, ("web", spawn "firefox")
+
, ("gimp" , spawnHere "gimp")
, ("movie", spawnShell)
 
, ("pdf", spawn "okular >&| /dev/null")
 
, ("gtk-gnutella", spawn "gtk-gnutella")
 
, ("gitit", mapM_ (spawnOn ?spawner "gitit") ["firefox http://localhost:5001"] >> spawnShell)
 
 
]
 
]
 
}
 
}
   
 
-- From the sample config in TopicSpace, these should probably be exported from that module
 
-- From the sample config in TopicSpace, these should probably be exported from that module
spawnShell :: (?spawner::Spawner) => X ()
 
 
spawnShell = currentTopicDir myTopicConfig >>= spawnShellIn
 
spawnShell = currentTopicDir myTopicConfig >>= spawnShellIn
   
spawnShellIn :: (?spawner::Spawner) => [Char] -> X ()
+
spawnShellIn dir = do
  +
-- color <- randomBg' (HSV 255 255)
spawnShellIn dir = asks (terminal . config) >>= \term -> spawnHere ?spawner $ "cd " ++ dir ++ " && " ++ term ++ " "
 
  +
t <- asks (terminal . config)
  +
spawnHere $ "cd " ++ dir ++ " && " ++ t -- ++ " -bg " ++ color
  +
  +
wsgrid = gridselect gsConfig <=< asks $ map (\x -> (x,x)) . workspaces . config
  +
  +
promptedGoto = wsgrid >>= flip whenJust (switchTopic myTopicConfig)
  +
  +
promptedShift = wsgrid >>= \x -> whenJust x $ \y -> windows (W.greedyView y . W.shift y)
  +
--------------------------------------------------------------------------------
  +
  +
--------------------------------------------------------------------------------
  +
-- A nice little example of extensiblestate
  +
newtype FocusFollow = FocusFollow {getFocusFollow :: Bool } deriving (Typeable,Read,Show)
  +
instance ExtensionClass FocusFollow where
  +
initialValue = FocusFollow True
  +
extensionType = PersistentExtension
  +
  +
-- this eventHook is the same as from xmonad for handling crossing events
  +
focusFollow e@(CrossingEvent {ev_window=w, ev_event_type=t})
  +
| t == enterNotify, ev_mode e == notifyNormal =
  +
whenX (XS.gets getFocusFollow) (focus w) >> return (All True)
  +
focusFollow _ = return (All True)
  +
  +
toggleFF = XS.modify $ FocusFollow . not . getFocusFollow
  +
--------------------------------------------------------------------------------
  +
  +
{- | Sometimes this picks the wrong element to merge into (that is, not the
  +
'focused' element of the group), and SubLayouts breaks up the whole group
  +
-}
  +
queryMerge pGrp = do
  +
w <- ask
  +
aws <- liftX $ filterM (runQuery pGrp) =<< gets
  +
(W.integrate' . W.stack . W.workspace . W.current . windowset)
  +
  +
let addRem = False -- run the query with window removed??
  +
when addRem
  +
(liftX $ modify (\ws -> ws { windowset = W.insertUp w (windowset ws) }))
  +
liftX $ windows (W.insertUp w)
   
  +
mapM_ (liftX . sendMessage . XMonad.Layout.SubLayouts.Merge w) aws
goto :: (?spawner::Spawner) => Topic -> X ()
 
goto = switchTopic myTopicConfig
 
   
  +
when addRem
promptedGoto :: (?spawner::Spawner) => X ()
 
  +
(liftX $ modify (\ws -> ws { windowset = W.delete' w (windowset ws) }))
promptedGoto = workspacePrompt myXPConfig goto
 
   
  +
idHook
promptedShift :: X ()
 
promptedShift = workspacePrompt myXPConfig $ windows . W.shift
 
 
</haskell>
 
</haskell>

Latest revision as of 16:00, 31 December 2010

Xmonad/Config archive/adamvo's xmobarrc (0.9.2)

Xmonad/Config archive/obtoxmd -- script called to temporarily run another wm

-- current darcs as of 2010-12-31
{-# LANGUAGE
     DeriveDataTypeable,
     FlexibleContexts,
     FlexibleInstances,
     MultiParamTypeClasses,
     NoMonomorphismRestriction,
     PatternGuards,
     ScopedTypeVariables,
     TypeSynonymInstances,
     UndecidableInstances
     #-}
{-# OPTIONS_GHC -W -fwarn-unused-imports -fno-warn-missing-signatures #-}

import Control.Applicative
import Control.Monad
import Control.Monad.Instances ()
import Control.Monad.Writer
import Data.List
import Data.Maybe
import Data.Traversable(traverse)
import Graphics.X11.Xinerama
import qualified Data.Map as M
import qualified XMonad.StackSet as W
import qualified XMonad.Util.ExtensibleState as XS
import System.IO
import XMonad
import XMonad.Actions.DwmPromote
import XMonad.Actions.FloatSnap
import XMonad.Actions.GridSelect
import XMonad.Actions.Search
import XMonad.Actions.SpawnOn
import XMonad.Actions.Submap
import XMonad.Actions.TopicSpace
import XMonad.Actions.UpdatePointer
import XMonad.Actions.Warp
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.UrgencyHook
import XMonad.Layout.BoringWindows
import XMonad.Layout.Drawer
import XMonad.Layout.Grid
import XMonad.Layout.IM
import XMonad.Layout.LayoutHints
import XMonad.Layout.LayoutModifier
import XMonad.Layout.Magnifier
import XMonad.Layout.Master
import XMonad.Layout.Mosaic
import XMonad.Layout.MosaicAlt
import XMonad.Layout.MouseResizableTile
import XMonad.Layout.Named
import XMonad.Layout.NoBorders
import XMonad.Layout.PerWorkspace
import XMonad.Layout.Simplest
import XMonad.Layout.SimplestFloat
import XMonad.Layout.SubLayouts
import XMonad.Layout.Tabbed
import XMonad.Layout.TrackFloating
import XMonad.Layout.WindowNavigation
import XMonad.Prompt
import XMonad.Prompt.RunOrRaise
import XMonad.Prompt.Ssh
import XMonad.Prompt.Window
import XMonad.Prompt.XMonad
import XMonad.Util.EZConfig
import XMonad.Util.Replace
import XMonad.Util.Run


main :: IO ()
main = do
    replace
    checkTopicConfig myTopics myTopicConfig
    let urgency
            | True = withUrgencyHook FocusHook
            | True = withUrgencyHook NoUrgencyHook
    xmonad . ewmh . urgency . myConfig
        =<< mapM xmobarScreen =<< getScreens

sofficeToolbox = className =? "OpenOffice.org 3.1"
                <&&> isInProperty "WM_PROTOCOLS" "WM_TAKE_FOCUS"

myConfig hs = let c = defaultConfig {
      layoutHook = myLayout
    , focusFollowsMouse = False
    , focusedBorderColor = "red"
    , startupHook = do
        return () -- supposedly to avoid inf. loops with checkKeymap
        checkKeymap (myConfig []) (myKeys c)
    , terminal = "urxvt"
    , modMask = mod4Mask
    , logHook = do
        multiPP'
            (mergePPOutputs [XMonad.Actions.TopicSpace.pprWindowSet myTopicConfig,
                             dynamicLogString . onlyTitle])
            myPP
            myPP{ ppTitle = const "" }
            hs
        updatePointer (TowardsCentre 0.2 0.2)
    , handleEventHook = ewmhDesktopsEventHook <+> fullscreenEventHook <+> focusFollow <+>
                    (\e -> case e of
                        PropertyEvent{ ev_window = w } -> do
                            isURXVT <- runQuery (className =? "URxvt") w
                            if not isURXVT then hintsEventHook e else return (All True)
                        _ -> return (All True))
    , workspaces = myTopics
    , manageHook = mconcat
                    [manageSpawn
                    ,isFullscreen --> doFullFloat
                    -- ,className =? "MPlayer" --> doFullFloat
                    ,className =? "XTerm" --> queryMerge (className =? "XTerm")
                    ,manageDocks
                    ]
    } in additionalKeysP c (myKeys c)

myXPConfig :: XPConfig
myXPConfig = greenXPConfig { font = "xft:Profont:pixelsize=15:autohint=true" }

gsConfig = defaultGSConfig { gs_navigate = fix $ \self ->
    let navKeyMap = M.mapKeys ((,) 0) $ M.fromList $
                [(xK_Escape, cancel)
                ,(xK_Return, select)
                ,(xK_slash , substringSearch self)]
           ++
            map (\(k,a) -> (k,a >> self))
                [(xK_Left  , move (-1,0 ))
                ,(xK_h     , move (-1,0 ))
                ,(xK_n     , move (-1,0 ))
                ,(xK_Right , move (1,0  ))
                ,(xK_l     , move (1,0  ))
                ,(xK_i     , move (1,0  ))
                ,(xK_Down  , move (0,1  ))
                ,(xK_j     , move (0,1  ))
                ,(xK_e     , move (0,1  ))
                ,(xK_Up    , move (0,-1 ))
                ,(xK_u     , move (0,-1 ))
                ,(xK_y     , move (-1,-1))
                ,(xK_m     , move (1,-1 ))
                ,(xK_space , setPos (0,0))
                ]
    in makeXEventhandler $ shadowWithKeymap navKeyMap (const self) }

data ExpandEdges a = ExpandEdges Int deriving (Read,Show)

instance LayoutModifier ExpandEdges Window where
    modifyLayout (ExpandEdges n) ws (Rectangle x y w h) = let
            bigRect = Rectangle (x - fromIntegral n) (y - fromIntegral n)
                                (w + 2*fromIntegral n) (h + 2*fromIntegral n)
        in
        runLayout ws bigRect

-- | push edges off-screen
expandEdges n layout = ModifiedLayout (ExpandEdges n) layout



-------------------- Layout ----------------------------------
myLayout =
         trackFloating . smartBorders
         . onWorkspace "movie" (magnifier m ||| layoutHints Full)
         . avoidStruts
         . onWorkspace "test" (multimastered 2 (1/100) (1/2) Grid)
         . onWorkspace "gimp" (named "G" gimp)
         . onWorkspace "xm-conf" ((nav $ ModifiedLayout (ExpandEdges 1) (Tall 1 0.3 0.5)) ||| Full)
         $ m ||| named "F" (noBorders Full)
    where nav = configurableNavigation (navigateColor "#ffff00")
          m = named "M"
            . lessBorders Screen
            . layoutHintsToCenter
            . addTabs shrinkText defaultTheme
            . nav
            . boringAuto
            . subLayout [] (Simplest ||| simplestFloat)
            $ mosaic 1.5 [7,5,2]
          gimp = nav
               . onLeft (simpleDrawer 0.01 0.3 $ Role "gimp-toolbox")
               . withIM 0.15 (Role "gimp-dock")
               . addTabs shrinkText defaultTheme
               . nav
               . boringAuto
               . subLayout [] Simplest
               $ mouseResizableTile ||| Full
--------------------------------------------------------------
-------------------- Keys ------------------------------------
myKeys c =
    [("M-<Left>"   , withFocused $ snapMove L Nothing  )
    ,("M-<Right>"  , withFocused $ snapMove R Nothing  )
    ,("M-<Up>"     , withFocused $ snapMove U Nothing  )
    ,("M-<Down>"   , withFocused $ snapMove D Nothing  )
    ,("M-S-<Left>" , withFocused $ snapShrink R Nothing)
    ,("M-S-<Right>", withFocused $ snapGrow   R Nothing)
    ,("M-S-<Up>"   , withFocused $ snapShrink D Nothing)
    ,("M-S-<Down>" , withFocused $ snapGrow   D Nothing)

    , ("M-l", withFocused (sendMessage . expandWindowAlt) >> sendMessage Expand)
    , ("M-h", withFocused (sendMessage . shrinkWindowAlt) >> sendMessage Shrink)

    ,("M-;", withFocused (sendMessage . tallWindowAlt) >> sendMessage Taller)
    ,("M-o", withFocused (sendMessage . wideWindowAlt) >> sendMessage Wider )

    ,("M-v", toggleFF)

    ,("M-S-b", restart "/home/aavogt/bin/obtoxmd" True)
    ,("M-S-d", restart "urxvt -e xmonad" False)

    ,("M-S-o"  , withFocused $ sendMessage . UnMerge   )
    ,("M-S-C-o", withFocused $ sendMessage . UnMergeAll)
    ,("M-C-m"  , withFocused $ sendMessage . MergeAll  )
    ,("M-C-."  , onGroup W.focusDown')
    ,("M-C-,"  , onGroup W.focusUp'  )

    ,("M-p",  shellPromptHere myXPConfig)
    ,("M-x", submap $ M.fromList subMaps)
    ,("M-g", submap $ defaultSublMap c  )

    ,("M-S-.", focusDown)
    ,("M-S-,", focusUp  )

    ,("M-S-a", currentTopicAction myTopicConfig)
    ,("M-a", warpToCentre >> goToSelected gsConfig)
    -- workaround
    ,("M-<Tab>", switchNthLastFocused myTopicConfig . succ . length . W.visible . windowset =<< get )

    ,("M-s"  , warpToCentre >> promptedGoto )
    ,("M-S-s", warpToCentre >> promptedShift)

    ,("M-b", sendMessage ToggleStruts)
    ,("M-<Return>", dwmpromote)
    ,("M-S-<Return>", spawnShell)
    -- don't force a recompile, if nothing has changed (xmonad --recompile runs XMonad.recompile True)
    ,("M-q", spawn "ghc -e ':m +XMonad Control.Monad System.Exit' -e 'flip unless exitFailure =<< recompile False' && xmonad --restart")
    ,("M-S-q", spawn "~/wip/x11-wm/xmonad/rebuild.sh")
    ,("<Print>",  spawn "scrot")
    ]
    ++
    concatMap (\(m,f) -> lrud ("M-"++m) f)
        [("S-"  , sendMessage . Swap)
        ,("C-"  , sendMessage . pullGroup)
        ,("S-C-", sendMessage . pushWindow)
        ,(""    , sendMessage . Go)]
    ++ mediaKeys ++
    [("M-"++m++[key], screenWorkspace sc >>= flip whenJust (windows . f))
        | (f, m) <- [(W.view, ""), (W.shift, "S-")]
        , (key, sc) <- zip "wf" [0 .. ]]
    ++
    [ ("M-"++m++[k], a i)
        | (a, m) <- [(switchNthLastFocused myTopicConfig,""),(shiftNthLastFocused, "S-")]
        , (i, k) <- zip [1..] "123456789"]

-- helper for windowNavigation keys
--    note: with colemak neiu are placed where jkli are with qwerty layout
lrud :: String -> (Direction2D -> b) -> [(String, b)]
lrud m cmd = zip ks cmds
    where
      ks   = map (\x -> m ++ [x]) "niue"
      cmds = zipWith ($) (repeat cmd) [L,R,U,D]

subMaps = [((0, xK_o),  runOrRaisePrompt myXPConfig),
           ((0, xK_p),  shellPromptHere myXPConfig),
           ((0, xK_x), xmonadPrompt myXPConfig),
           ((0, xK_z), sshPrompt myXPConfig),
           ((shiftMask, xK_w), windowPromptGoto myXPConfig),
           ((0, xK_w), promptSearch myXPConfig wikipedia),
           ((0, xK_s), promptSearch myXPConfig multi),
           ((0, xK_m), promptSearch myXPConfig mathworld),
           ((0, xK_b), sendMessage ToggleStruts),
           ((0, xK_f), withFocused $ windows . W.sink),
           ((0, xK_v), refresh),
           ((0, xK_c), asks config >>= spawnHere . terminal),
           ((0, xK_k), kill)
           ]


amarok = False

mediaKeys = [("<XF86AudioPlay>", do mpcAct "toggle"; when amarok $ spawn "amarok -t"),
             ("<XF86AudioStop>", promptHost),
             ("<XF86AudioNext>", do mpcAct "next"; when amarok $ spawn "amarok -f"),
             ("<XF86AudioPrev>", do mpcAct "prev"; when amarok $ spawn "amarok -r"),
             ("<XF86AudioMute>", spawn "ossmix vmix0-outvol 0"),
             ("<XF86AudioLowerVolume>",   spawn "amixer sset PCM 1-"),
             ("<XF86AudioRaiseVolume>",   spawn "amixer sset PCM 1+"),
             ("<XF86Sleep>", spawn "sudo pm-suspend")
             ]
    where mpcAct c = do
            h <- XS.gets hostPrompt
            spawn $ unwords ["export MPD_HOST="++h,";","mpc",c]

-- Prompt for mpd host
newtype HostPrompt = HostPrompt { hostPrompt :: String } deriving (Read,Show,Typeable)
instance ExtensionClass HostPrompt where
    initialValue = HostPrompt "/home/aavogt/.mpd/socket"
    extensionType = PersistentExtension

instance XPrompt HostPrompt where showXPrompt _ = "Pick MPD Host: "
promptHost = mkXPrompt (HostPrompt "") myXPConfig (return . compl) (XS.put . HostPrompt)
    where compl s = nub $ filter (s `isPrefixOf`) ["127.0.0.1","dell"]
--------------------------------------------------------------

warpToCentre = gets (W.screen . W.current . windowset) >>= \x -> warpToScreen x  0.5 0.5

-------------------- Support for per-screen xmobars ---------
-- Some parts of this should be merged into contrib sometime
getScreens :: IO [Int]
getScreens = openDisplay "" >>= liftA2 (<*) f closeDisplay
    where f = fmap (zipWith const [0..]) . getScreenInfo

multiPP :: PP -- ^ The PP to use if the screen is focused
        -> PP -- ^ The PP to use otherwise
        -> [Handle] -- ^ Handles for the status bars, in order of increasing X
                    -- screen number
        -> X ()
multiPP = multiPP' dynamicLogString

multiPP' :: (PP -> X String) -> PP -> PP -> [Handle] -> X ()
multiPP' dynlStr focusPP unfocusPP handles = do
    state <- get
    let pickPP :: WorkspaceId -> WriterT (Last XState) X String
        pickPP ws = do
            let isFoc = (ws ==) . W.tag . W.workspace . W.current $ windowset state
            put state{ windowset = W.view ws $ windowset state }
            out <- lift $ dynlStr $ if isFoc then focusPP else unfocusPP
            when isFoc $ get >>= tell . Last . Just
            return out
    traverse put . getLast
        =<< execWriterT . (io . zipWithM_ hPutStrLn handles <=< mapM pickPP) . catMaybes
        =<< mapM screenWorkspace (zipWith const [0..] handles)
    return ()

mergePPOutputs :: [PP -> X String] -> PP -> X String
mergePPOutputs x pp = fmap (intercalate (ppSep pp)) . sequence . sequence x $ pp

onlyTitle :: PP -> PP
onlyTitle pp = defaultPP { ppCurrent = const ""
                         , ppHidden = const ""
                         , ppVisible = const ""
                         , ppLayout = ppLayout pp
                         , ppTitle = ppTitle pp }

-- | Requires a recent addition to xmobar (>0.9.2), otherwise you have to use
-- multiple configuration files, which gets messy
xmobarScreen :: Int -> IO Handle
xmobarScreen = spawnPipe . ("~/.cabal/bin/xmobar -x " ++) . show

myPP :: PP
myPP = sjanssenPP { ppLayout = xmobarColor "orange" "", ppUrgent = xmobarColor "red" "" . ('^':) }
--------------------------------------------------------------

-------------------- X.Actions.TopicSpace --------------------
myTopics :: [Topic]
myTopics =
  [ "a"
  , "web"
  , "haskell"
  , "mail"
  , "irc"
  , "xm-conf"
  , "gimp"
  , "gitit"
  , "admin"
  , "movie"
  , "music"
  , "pdf"
  , "doc"
  , "xmc"
  , "xme"
  , "xm"
  , "xmobar"
  , "wip"
  , "test"
  ]


myTopicConfig = TopicConfig
  { topicDirs = M.fromList $
      [ ("a", "./")
      , ("haskell", "haskell")
      , ("xm-conf", ".xmonad")
      , ("xme", "wip/x11-wm/xmonad/extras/xmonad-extras/XMonad")
      , ("xm", "wip/x11-wm/xmonad/core/xmonad")
      , ("xmc", "wip/x11-wm/xmonad/contrib/XMonadContrib/XMonad")
      , ("xmobar", "wip/x11-wm/xmobar")
      , ("movie", "media/movie")
      , ("music", "media/music")
      , ("doc", "doc")
      , ("pdf", "ref")
      , ("gitit", "wip/gitit")
      , ("gimp", "./")
      , ("wip", "wip")
      ]
  , defaultTopicAction = const $ spawnShell >*> 2
  , defaultTopic = "a"
  , maxTopicHistory = 10
  , topicActions = M.fromList $
      [ ("xm-conf", spawnShellIn ".xmonad/lib/XMonad/Layout" >>
                        spawn "urxvt -e vim ~/.xmonad/xmonad.hs")
       , ("xmc"    , spawnShell >*> 2)
       , ("xmobar" , spawnShellIn "wip/x11-wm/xmobar/Plugins" >*> 2)
       , ("music"  , spawn "urxvt -e ncmpc -h /home/aavogt/.mpd/socket" >> spawn "export MPD_HOST=192.168.1.2; mpc && urxvt -e ncmpc -h 192.168.1.2")
       , ("mail"   , spawnOn "mail" "urxvt -e mutt")
       , ("irc"    , spawnOn "irc" "urxvt --title irc -e ssh engage")
       , ("web"    , spawnOn "web" "firefox")
       , ("pdf"    , spawnOn "pdf" "okular")
       , ("gimp"   , spawnHere "gimp")
      ]
  }

-- From the sample config in TopicSpace, these should probably be exported from that module
spawnShell = currentTopicDir myTopicConfig >>= spawnShellIn

spawnShellIn dir = do
    -- color <- randomBg' (HSV 255 255)
    t <- asks (terminal . config)
    spawnHere $ "cd " ++ dir ++ " && " ++ t -- ++ " -bg " ++ color

wsgrid = gridselect gsConfig <=< asks $ map (\x -> (x,x)) . workspaces . config

promptedGoto = wsgrid >>= flip whenJust (switchTopic myTopicConfig)

promptedShift = wsgrid >>= \x -> whenJust x $ \y -> windows (W.greedyView y . W.shift y)
--------------------------------------------------------------------------------

--------------------------------------------------------------------------------
-- A nice little example of extensiblestate
newtype FocusFollow = FocusFollow {getFocusFollow :: Bool } deriving (Typeable,Read,Show)
instance ExtensionClass FocusFollow where
    initialValue = FocusFollow True
    extensionType = PersistentExtension

-- this eventHook is the same as from xmonad for handling crossing events
focusFollow e@(CrossingEvent {ev_window=w, ev_event_type=t})
                | t == enterNotify, ev_mode e == notifyNormal =
        whenX (XS.gets getFocusFollow) (focus w) >> return (All True)
focusFollow _ = return (All True)

toggleFF = XS.modify $ FocusFollow . not . getFocusFollow
--------------------------------------------------------------------------------

{- | Sometimes this picks the wrong element to merge into (that is, not the
'focused' element of the group), and SubLayouts breaks up the whole group
-}
queryMerge pGrp = do
    w <- ask
    aws <- liftX $ filterM (runQuery pGrp) =<< gets
        (W.integrate' . W.stack . W.workspace . W.current . windowset)

    let addRem = False -- run the query with window removed??
    when addRem
        (liftX $ modify (\ws -> ws { windowset = W.insertUp w (windowset ws) }))
    liftX $ windows (W.insertUp w)

    mapM_ (liftX . sendMessage . XMonad.Layout.SubLayouts.Merge w) aws

    when addRem
        (liftX $ modify (\ws -> ws { windowset = W.delete' w (windowset ws) }))

    idHook