]> code.delx.au - dotfiles/blobdiff - .xmonad/xmonad.hs
xmonad: remove unused layout
[dotfiles] / .xmonad / xmonad.hs
index 4779b0f6583e69abd294335b46f0daa91625ed4a..d36078b694fd103c1a7bbd9606abd4473cfd9db3 100644 (file)
@@ -1,11 +1,13 @@
+{-# LANGUAGE FlexibleContexts #-}
 import System.IO
 import XMonad
+import XMonad.Actions.CycleRecentWS
+import XMonad.Actions.PhysicalScreens
 import XMonad.Hooks.DynamicLog
 import XMonad.Hooks.EwmhDesktops
 import XMonad.Hooks.ICCCMFocus
 import XMonad.Hooks.ManageDocks
 import XMonad.Hooks.ManageHelpers
-import XMonad.Hooks.Script
 import XMonad.Hooks.SetWMName
 import XMonad.Layout.IM
 import XMonad.Layout.LayoutHints
@@ -17,194 +19,158 @@ import XMonad.Layout.PerWorkspace
 import XMonad.Layout.Renamed
 import XMonad.Layout.Reflect
 import XMonad.Layout.Tabbed
-import XMonad.Layout.ThreeColumns
 import XMonad.Util.Run(spawnPipe)
-import XMonad.Util.WindowProperties(getProp32s)
 import qualified Data.Map as M
 import qualified XMonad.StackSet as W
 
 
 myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $
-       [
-               ((modm .|. shiftMask, xK_h), spawn "xfce4-session-logout"),
-               ((modm .|. shiftMask, xK_l), spawn "xscreensaver-command --lock"),
-
-               ((modm, xK_n), spawn "xfce4-terminal"),
-               ((modm, xK_i), spawn "firefox"),
-
-               ((modm .|. shiftMask, xK_c ), kill),
-               ((modm, xK_space ), sendMessage NextLayout),
-               ((modm .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf),
-               ((modm, xK_Tab ), windows W.focusDown),
-               ((modm, xK_j ), windows W.focusDown),
-               ((modm, xK_k ), windows W.focusUp ),
-               ((modm, xK_m ), windows W.focusMaster ),
-               ((modm, xK_Return), windows W.swapMaster),
-               ((modm .|. shiftMask, xK_j ), windows W.swapDown ),
-               ((modm .|. shiftMask, xK_k ), windows W.swapUp ),
-               ((modm, xK_h ), sendMessage Shrink),
-               ((modm, xK_l ), sendMessage Expand),
-               ((modm, xK_t ), withFocused $ windows . W.sink),
-               ((modm , xK_comma ), sendMessage (IncMasterN 1)),
-               ((modm , xK_period), sendMessage (IncMasterN (-1))),
-               ((modm , xK_b ), sendMessage ToggleStruts),
-               ((modm , xK_z ), sendMessage Mag.Toggle)
-       ]
-       ++
-
-       -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
-       -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
-       [((m .|. modm, key), screenWorkspace sc >>= flip whenJust (windows . f))
-               | (key, sc) <- zip [xK_o, xK_e, xK_u] [0..]
-               , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
-       ]
-       ++
-
-       -- mod-[1..9], Switch to workspace N
-       -- mod-shift-[1..9], Move client to workspace N
-       [((m .|. modm, k), windows $ f i)
-               | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
-               , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
-       ]
+    [
+        ((modm .|. shiftMask, xK_h), spawn "xfce4-session-logout"),
+        ((modm .|. shiftMask, xK_l), spawn "xscreensaver-command --lock"),
+        ((modm .|. shiftMask, xK_r), spawn "xmonad --restart"),
+
+        ((modm, xK_n), spawn "xfce4-terminal"),
+        ((modm, xK_i), spawn "firefox"),
+        ((modm, xK_c), spawn "emacsclient --create-frame --no-wait"),
+        ((modm, xK_p), spawn "kupfer"),
+
+        ((modm .|. shiftMask, xK_c ), kill),
+        ((modm, xK_space ), sendMessage NextLayout),
+        ((modm .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf),
+        ((modm, xK_j ), windows W.focusDown),
+        ((modm, xK_k ), windows W.focusUp ),
+        ((modm, xK_m ), windows W.focusMaster ),
+        ((modm, xK_Return), windows W.swapMaster),
+        ((modm .|. shiftMask, xK_j ), windows W.swapDown ),
+        ((modm .|. shiftMask, xK_k ), windows W.swapUp ),
+        ((modm, xK_h ), sendMessage Shrink),
+        ((modm, xK_l ), sendMessage Expand),
+        ((modm, xK_t ), withFocused $ windows . W.sink),
+        ((modm , xK_comma ), sendMessage (IncMasterN 1)),
+        ((modm , xK_period), sendMessage (IncMasterN (-1))),
+        ((modm , xK_b ), sendMessage ToggleStruts),
+        ((modm , xK_z ), sendMessage Mag.Toggle),
+        ((modm , xK_a), cycleRecentWS [xK_Super_L] xK_a xK_a)
+    ]
+    ++
+
+    -- mod-{o,e,u}, Switch to physical/Xinerama screens 1, 2, or 3
+    -- mod-shift-{o,e,u}, Move client to screen 1, 2, or 3
+    [((m .|. modm, key), f sc)
+        | (key, sc) <- zip [xK_o, xK_e, xK_u] [0..]
+        , (f, m) <- [(viewScreen, 0), (sendToScreen, shiftMask)]
+    ]
+    ++
+
+    -- mod-[1..9], Switch to workspace N
+    -- mod-shift-[1..9], Move client to workspace N
+    [((m .|. modm, k), windows $ f i)
+        | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
+        , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
+    ]
 
 
 avoidMaster = W.modify' $ \c -> case c of
-       W.Stack t [] (r:rs) -> W.Stack t [r] rs
-       otherwise -> c
+    W.Stack t [] (r:rs) -> W.Stack t [r] rs
+    otherwise -> c
 
-isTransient = ask >>= \w -> liftX $ do
-       r <- getProp32s "WM_TRANSIENT_FOR" w
-       return $ case r of
-               Just [_] -> True
-               _ -> False
+isSkipTaskBar = isInProperty "_NET_WM_STATE" "_NET_WM_STATE_SKIP_TASKBAR"
 
 myManageHook =
-       manageDocks <+>
-       composeOne [
-               (className =? "Firefox" <&&> resource =? "Popup") -?> (ask >>= doF . W.sink),
-               (className =? "Firefox" <&&> resource =? "Navigator" <&&> currentWs =? "1") -?> (doShift "2"),
-               (className =? "Kupfer.py" <&&> resource =? "kupfer.py") -?> doFloat,
-               (className =? "Xfce4-appfinder" <&&> resource =? "xfce4-appfinder") -?> doFloatAt 0.1 0.1,
-               (isDialog -?> doFloatAt 0.1 0.1),
-               (isTransient -?> doFloatAt 0.1 0.1),
-               (isFullscreen -?> doFullFloat),
-               (fmap Just $ doF avoidMaster)
-       ]
+    manageDocks <+>
+    composeOne [
+        transience,
+        (isSkipTaskBar -?> doFloat),
+        (isDialog -?> doFloatAt 0.1 0.1),
+        (isFullscreen -?> doFullFloat),
+        (fmap Just $ doF avoidMaster)
+    ]
 
 
 myWorkspaces = ["1", "2", "3", "4", "5", "6", "7", "8", "9"]
 
 myPP = xmobarPP
-       {
-               ppCurrent = xmobarColor "#A01010" "" . wrap "[" "]",
-               ppTitle = xmobarColor "#10A010" ""
-       }
+    {
+        ppCurrent = xmobarColor "#A01010" "" . wrap "[" "]",
+        ppTitle = xmobarColor "#10A010" ""
+    }
 
-myLogHook h1 h2 =
-       dynamicLogWithPP myPP { ppOutput = hPutStrLn h1 } >>
-       dynamicLogWithPP myPP { ppOutput = hPutStrLn h2 } >>
-       takeTopFocus -- fix for Java Swing apps
-
-myStartupHook =
-       setWMName "LG3D" -- fix for Java Swing apps
+myLogHook hooks = do
+    mapM (\h -> dynamicLogWithPP myPP { ppOutput = hPutStrLn h }) hooks
+    takeTopFocus -- fix for Java Swing apps
 
+myStartupHook = do
+    setWMName "LG3D" -- fix for Java Swing apps
+    spawn "xfce4-panel --restart" -- ensure it appears on top of xmobar
 
 goldenRatio = (toRational (2/(1+sqrt(5)::Double)))
 
 myTitleTheme = defaultTheme {
-               fontName = "xft:sans-serif:size=10",
-               decoHeight = 22
-       }
+        fontName = "xft:sans-serif:size=10",
+        decoHeight = 24
+    }
 
 createLayout name layout =
-       renamed [Replace name] $
-       layoutHints $
-       smartBorders $
-       layout
+    renamed [Replace name] $
+    layoutHints $
+    smartBorders $
+    layout
 
 myFullLayout = createLayout "Full" $
-       Full
+    noBorders $
+    Full
 
 myTiledLayout = createLayout "Tall" $
-       avoidStruts $
-       Mag.magnifierOff $
-       Tall nMaster ratioIncrement masterRatio
-       where
-               nMaster = 1
-               ratioIncrement = 3/100
-               masterRatio = goldenRatio
+    avoidStruts $
+    Mag.magnifierOff $
+    Tall nMaster ratioIncrement masterRatio
+    where
+        nMaster = 1
+        ratioIncrement = 3/100
+        masterRatio = goldenRatio
 
 myTabbedLayout = createLayout "Tab" $
-       avoidStruts $
-       tabbed shrinkText myTitleTheme
-
-myThreeColLayout = createLayout "ThreeCol" $
-       avoidStruts $
-       Mag.magnifierOff $
-       ThreeCol numMaster resizeDelta masterRatio
-       where
-               resizeDelta = 3/100
-               masterRatio = 4/10
-               numMaster = 1
+    avoidStruts $
+    tabbed shrinkText myTitleTheme
 
 myMasterTabbedLayout = createLayout "MTab" $
-       avoidStruts $
-       Mag.magnifierOff $
-       mastered resizeDelta masterRatio $
-       tabbed shrinkText myTitleTheme
-       where
-               resizeDelta = 3/100
-               masterRatio = goldenRatio
-
-myImLayout = createLayout "IM" $
-       avoidStruts $
-       noFrillsDeco shrinkText myTitleTheme $
-       withIM rosterRatio roster $
-       myTiledLayout
----    myThreeColLayout -- use this on wider screens
-       where
-               rosterRatio = 1/8
-               roster = (Or (Title "Buddy List") (And (Resource "main") (ClassName "psi")))
+    avoidStruts $
+    Mag.magnifierOff $
+    mastered resizeDelta masterRatio $
+    tabbed shrinkText myTitleTheme
+    where
+        resizeDelta = 3/100
+        masterRatio = goldenRatio
 
 myGimpLayout = createLayout "Gimp" $
-       avoidStruts $
-       withIM (1/6) (Role "gimp-toolbox") $
-       reflectHoriz $
-       withIM (1/6) (Role "gimp-dock") $
-       reflectHoriz $
-       tabbed shrinkText myTitleTheme
-
-
--- This was the easiest way I found to avoid a compile error when I have
--- an unused layout
-referenceAllLayoutsToAvoidErrors =
-       myFullLayout |||
-       myTiledLayout |||
-       myTabbedLayout |||
-       myThreeColLayout |||
-       myMasterTabbedLayout |||
-       myImLayout |||
-       myGimpLayout
-
+    avoidStruts $
+    withIM (1/6) (Role "gimp-toolbox") $
+    reflectHoriz $
+    withIM (1/6) (Role "gimp-dock") $
+    reflectHoriz $
+    tabbed shrinkText myTitleTheme
 
 myLayout =
-       (
-               onWorkspace "1" (myImLayout) $
-               onWorkspace "2" (myTabbedLayout ||| myMasterTabbedLayout) $
-               onWorkspace "9" (myMasterTabbedLayout ||| myTabbedLayout ||| myTiledLayout ||| myFullLayout ||| myGimpLayout) $
-               (myMasterTabbedLayout ||| myTabbedLayout ||| myTiledLayout)
-       )
+    (
+        onWorkspace "1" (myTabbedLayout ||| myMasterTabbedLayout) $
+        onWorkspace "2" (myTabbedLayout ||| myMasterTabbedLayout) $
+        onWorkspace "9" (myFullLayout ||| myMasterTabbedLayout ||| myTabbedLayout ||| myTiledLayout ||| myGimpLayout) $
+        (myMasterTabbedLayout ||| myTabbedLayout ||| myTiledLayout)
+    )
 
 main = do
-       xmonadDir <- getXMonadDir
-       xmobar <- spawnPipe ("xmobar " ++ xmonadDir ++ "/xmobar.hs")
-       xmobar2 <- spawnPipe ("xmobar -x 1 " ++ xmonadDir ++ "/xmobar.hs")
-       xmonad $ ewmh defaultConfig {
-               manageHook = myManageHook,
-               layoutHook = myLayout,
-               workspaces = myWorkspaces,
-               logHook = myLogHook xmobar xmobar2,
-               startupHook = myStartupHook,
-               keys = myKeys
-       }
+    xmonadDir <- getXMonadDir
+    xmobars <- mapM (\x -> spawnPipe ("xmobar -x " ++ (show x) ++ " " ++ xmonadDir ++ "/xmobar.hs")) [1, 2]
+    xmonad $ ewmh defaultConfig {
+        manageHook = myManageHook,
+        layoutHook = myLayout,
+        workspaces = myWorkspaces,
+        logHook = myLogHook xmobars,
+        startupHook = myStartupHook,
+        keys = myKeys,
+        modMask = mod4Mask,
+        handleEventHook = handleEventHook defaultConfig <+> fullscreenEventHook,
+        focusFollowsMouse = False
+    }