summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--xmonad.hs275
1 files changed, 180 insertions, 95 deletions
diff --git a/xmonad.hs b/xmonad.hs
index 1bcb311..54ec5a8 100644
--- a/xmonad.hs
+++ b/xmonad.hs
@@ -33,6 +33,8 @@ import XMonad.Actions.FindEmptyWorkspace
import XMonad.Actions.FloatSnap
import XMonad.Actions.GridSelect
import XMonad.Actions.SinkAll
+import XMonad.Actions.SpawnOn
+import XMonad.Actions.TopicSpace hiding (pprWindowSet)
import XMonad.Actions.UpdateFocus
import qualified XMonad.Actions.FlexibleManipulate as Flex
@@ -58,6 +60,9 @@ import XMonad.Util.Replace (replace)
import Control.Monad (when)
import System.Environment (getArgs)
+import Data.Maybe (fromMaybe, fromJust, isNothing, isJust)
+import Data.Ord (comparing)
+
-- for hostname handling (no windows key on "Australien")
import Network.HostName
@@ -68,16 +73,14 @@ import Pass
import qualified Confirm
font :: String
-font = "-*-terminus-medium-r-normal-*-12-*-*-*-*-*-*-*"
+font = "xft:Hack:size=10"
term :: String
term = "urxvt"
browser :: String
-browser = "viewurl-opera.sh"
+browser = "browser"
-myWorkspaces :: [String]
-myWorkspaces = ["1:web", "2:mail" ,"3:irc", "4:im", "5:code"] ++ map show [6 .. 9 :: Int] ++ ["0", "video", "music"]
modM :: String -> KeyMask
-- mod1Mask = Alt, mod2Mask = , mod3Mask= , mod4Mask = Win, mod5Mask = AltGrk
@@ -86,10 +89,13 @@ modM _ = mod4Mask
myDzenUrgencyConfig = DzenUrgencyHook
{ args = ["-bg", "red", "-fg", "black", "-fn", font,
- "-w", "480", "-ta", "c", "-x", "480"]
+ "-w", "600", "-ta", "c", "-x", "520", "-y", "10",
+ "-h", "30" ]
, duration = seconds 5
}
+--{{{ main
+
main = do
args <- getArgs
when ("--replace" `elem` args) replace
@@ -102,27 +108,80 @@ main = do
-- end of your custom hooks (esp. the startup hook) and this would
-- overwrite the setWMName "LG3D" and some Java apps will not work.
$ withUrgencyHook myDzenUrgencyConfig
- $ myConfig dzenStatusFile hostname
-
-myConfig statusFile hostname = defaultConfig
- { modMask = modM hostname
- , terminal = term
- , borderWidth = 1
- , normalBorderColor = "#545454"
- , focusedBorderColor = "#A00000"
- , logHook = myLogHook statusFile
- , manageHook = myManageHook
- , keys = \c -> mkKeymap c $ myKeys c hostname
- , mouseBindings = \c -> M.union (M.fromList $ myMouse (modM hostname) c) $ mouseBindings defaultConfig c
- , layoutHook = myLayout
- , workspaces = myWorkspaces
- , handleEventHook = myEventHook
- , startupHook = myStartupHook
- }
+ $ defaultConfig { modMask = modM hostname
+ , terminal = term
+ , borderWidth = 1
+ , normalBorderColor = "#545454"
+ , focusedBorderColor = "#A00000"
+ , logHook = myLogHook dzenStatusFile
+ , manageHook = myManageHook
+ , keys = \c -> mkKeymap c $ myKeys c hostname
+ , mouseBindings = \c -> M.union (M.fromList $ myMouse (modM hostname) c) $ mouseBindings defaultConfig c
+ , layoutHook = myLayout
+ , workspaces = topics
+ , handleEventHook = myEventHook
+ , startupHook = myStartupHook
+ }
+
+--}}}
+
+--{{{ TopicSpaces
+
+topics :: [Topic]
+topics = [ "web", "mail", "irc", "im", "video", "music"
+ , "spline", "usdx", "partdb", "riot", "zedat"
+ , "emacs", "xmonad", "gimp"]
+
+topicsConfig = TopicConfig
+ { topicDirs = M.fromList $
+ [ ("web", "./")
+ , ("mail", "./")
+ , ("irc", "./")
+ , ("im", "./")
+ , ("video", "media/video")
+ , ("music", "media/audio/")
+ , ("spline", "dev/spline/")
+ , ("usdx", "dev/usdx/")
+ , ("partdb", "dev/Part-DB/")
+ , ("riot", "dev/RIOT/")
+ , ("zedat", "./")
+ , ("emacs", "./")
+ , ("xmoand", ".xmonad/")
+ , ("gimp", "./")
+ ]
+ , defaultTopicAction = const $ spawnShell >*> 2
+ , defaultTopic = "web"
+ , maxTopicHistory = 10
+ , topicActions = M.fromList $
+ [ ("web" , spawnHere browser)
+ , ("mail" , spawn "emacsclient -e '(wl-start)'")
+ , ("irc" , spawnHere "hexchat")
+ , ("im" , spawnHere "tkabber")
+ , ("music" , spawnHere "guayadeque")
+ , ("zedat" , spawnHere $ term ++ " -e is")
+ , ("emacs" , spawnHere "emacs")
+ , ("gimp" , spawnHere "gimp")
+ ]
+ }
+ where
+ spawnShell = currentTopicDir topicsConfig >>= spawnShellIn
+ spawnShellIn dir =
+ spawnHere $ "cd " ++ dir ++ " && " ++ term
+
+topicsGrid =
+ withWindowSet $ \w -> do
+ let wss = W.workspaces w
+ usednames = filter (\w -> w /= "NSP") $ map W.tag $ wss
+ newnames = filter (\used -> (show used `notElem` (map show topics))) usednames
+ gridselect topicsGridConfig (map (\t -> (t, t)) (topics ++ newnames))
+
+promptedGoto = topicsGrid >>= flip whenJust (switchTopic topicsConfig)
+
+promptedShift = topicsGrid >>= \x -> whenJust x $ \y -> windows (W.greedyView y . W.shift y)
+
+--}}}
---
--- Prompts
---
+--{{{ Prompts
data MyShell = MyShell
instance XPrompt MyShell where
@@ -132,9 +191,9 @@ myShellPrompt c = do
cmds <- io getCommands
mkXPrompt MyShell c (getShellCompl cmds) spawn
---
--- Scratchpads
---
+--}}}
+
+--{{{ Scratchpads
scratchpads =
[ NS "hotot" "hotot" (className =? "Hotot")
@@ -143,26 +202,26 @@ scratchpads =
(customFloating $ W.RationalRect 0.03 0.03 0.94 0.6)
]
-hiddenWS :: X (WindowSpace -> Bool)
-hiddenWS = do hs <- gets (map W.tag . W.hidden . windowset)
- return (\w -> W.tag w `elem` hs)
+notNspHiddenWS :: X (WindowSpace -> Bool)
+notNspHiddenWS = do notNsp <- notNspWS
+ hidden <- hiddenWS
+ nonEmpty <- nonEmptyWS
+ return (\w -> hidden w && nonEmpty w && notNsp w)
+ where
+ hiddenWS = do hs <- gets (map W.tag . W.hidden . windowset)
+ return (\w -> W.tag w `elem` hs)
+ nonEmptyWS = return $ isJust . W.stack
+ notNspWS = return $ ("NSP" /=) . W.tag
-notNspWS :: X (WindowSpace -> Bool)
-notNspWS = return $ ("NSP" /=) . W.tag
-notNspHiddenWS :: X (WindowSpace -> Bool)
-notNspHiddenWS = do nn <- notNspWS
- hi <- hiddenWS
- return (\w -> hi w && nn w)
+--}}}
+--{{{ Themes
---
--- Themes
---
myPP statusFile = namedScratchpadFilterOutWorkspacePP $ defaultPP
{ ppCurrent = wrap "^fg(#FF0000) " " "
, ppVisible = wrap "^fg(#0000FF) " " "
- , ppHiddenNoWindows = \(_)->""
+ , ppHiddenNoWindows = \_ -> ""
, ppUrgent = wrap "^bg(#FFFF00)^fg(#FF0000) " " "
, ppHidden = pad
, ppWsSep = "^fg(#888)^bg(#000):"
@@ -201,7 +260,7 @@ alexTheme = defaultTheme
, inactiveTextColor = "#ffffff"
, activeTextColor = "#ffffff"
, fontName = font
- , decoHeight = 15
+ , decoHeight = 19
}
alexXPConfig :: XPConfig
@@ -213,9 +272,19 @@ historyGridConfig = defaultGSConfig
{ gs_cellheight = 50
, gs_cellwidth = 300
, gs_navigate = navNSearch
- , gs_font = "xft:Droid Sans Mono Slashed-8"
+ , gs_font = font
}
+topicsGridConfig = defaultGSConfig
+ { gs_navigate = navNSearch
+ , gs_font = font
+ , gs_colorizer = colorizer
+ }
+ where
+ colorizer topic selected
+ | selected = return ("#839596", "#002b36")
+ | otherwise = return ("#002b36", "#839496")
+
confirmConfig :: HasColorizer a => GSConfig a
confirmConfig = defaultGSConfig
{ gs_cellheight = 150
@@ -229,12 +298,34 @@ confirmConfig = defaultGSConfig
confirm :: String -> X() -> X()
confirm = Confirm.confirm confirmConfig
---
--- Hooks
---
+--}}}
+
+--{{{ Hooks
+
myLogHook statusFile = do
ewmhDesktopsLogHook
- dynamicLogWithPP $ myPP statusFile
+ topicOutput <- lastTopics topicsConfig pp
+ otherOutput <- dynamicLogString pp { ppVisible = \_ -> ""
+ , ppCurrent = \_ -> ""
+ , ppUrgent = \_ -> ""
+ , ppHidden = \_ -> ""
+ }
+ io $ ppOutput pp (topicOutput ++ otherOutput)
+ where
+ pp = myPP statusFile
+ lastTopics tg pp = do
+ winset <- gets windowset
+ urgents <- readUrgents
+ let empty_workspaces = map W.tag $ filter (isNothing . W.stack) $ W.workspaces winset
+ maxDepth = maxTopicHistory tg
+ setLastFocusedTopic (W.tag . W.workspace . W.current $ winset)
+ (\t -> (t `notElem` empty_workspaces && t /= "NSP"))
+ lastWs <- getLastFocusedTopics
+ let depth topic = fromJust $ elemIndex topic $ lastWs ++ [topic]
+ add_depth proj topic = proj pp . (((topic++":")++) . show) . depth $ topic
+ pp' = pp { ppHidden = add_depth ppHidden, ppVisible = add_depth ppVisible, ppUrgent = add_depth ppUrgent }
+ sortWindows = take maxDepth . sortBy (comparing $ depth . W.tag) . namedScratchpadFilterOutWorkspace
+ return $ pprWindowSet sortWindows urgents pp' winset
myEventHook = do
ewmhDesktopsEventHook
@@ -297,29 +388,30 @@ xPropMatches =
"Eclipse"])]
]
- shifts = [ ("1:web", [(wM_CLASS, anyOf ["Opera", "Chrome", "Google-chrome", "Chromium-browser",
- "Firefox-bin"])])
- , ("2:mail", [(wM_CLASS, anyOf ["Claws-mail", "Evolution", "Mitter", "wanderlust"])])
- , ("2:mail", [(wM_NAME, anyOf ["newsbeuter"])])
- , ("3:irc", [(wM_CLASS, anyOf ["Hexchat"])])
- , ("4:im", [(wM_CLASS, anyOf ["TKabber", "headlines", "Vacuum"])])
+ shifts = [ ("web", [(wM_CLASS, anyOf ["Opera", "Chrome", "Google-chrome", "Chromium-browser",
+ "Firefox-bin"])])
+ , ("mail", [(wM_CLASS, anyOf ["Claws-mail", "Evolution", "Mitter", "wanderlust"])])
+ , ("mail", [(wM_NAME, anyOf ["newsbeuter"])])
+ , ("irc", [(wM_CLASS, anyOf ["Hexchat"])])
+ , ("im", [(wM_CLASS, anyOf ["TKabber", "headlines", "Vacuum"])])
-- tkabber single messages
- , ("4:im", [(wM_CLASS, anyOf' isPrefixOf ["chat_##xmpp##1_zedatconferencejabberfuberlinde",
- "chat_##xmpp##1_mailanimuxdeSyslogBot"])])
+ , ("im", [(wM_CLASS, anyOf' isPrefixOf ["chat_##xmpp##1_zedatconferencejabberfuberlinde",
+ "chat_##xmpp##1_mailanimuxdeSyslogBot"])])
- , ("5:code", [(wM_CLASS, anyOf ["emacs"])])
+ , ("code", [(wM_CLASS, anyOf ["emacs"])])
- , ("video", [(wM_CLASS, anyOf ["MPlayer"])])
- , ("music", [(wM_CLASS, anyOf ["Amarokapp"])])
+ , ("video", [(wM_CLASS, anyOf ["MPlayer"])])
+ , ("music", [(wM_CLASS, anyOf ["Amarokapp"])])
]
anyOf' op valids tests = any (\test -> any (\valid -> op valid test) valids) tests
anyOf = anyOf' (==)
---
--- Keys
---
+--}}}
+
+--{{{ Keys
+
myKeys c hostname =
-- this line is critical to reload config - DON'T REMOVE
[ ("M-q", broadcastMessage ReleaseResources >> restart "xmonad" True)
@@ -374,8 +466,7 @@ myKeys c hostname =
, ("M-d", spawn "fbsetroot -solid black")
, ("M-f", spawn "fbsetroot -l")
- , ("M-^", viewEmptyWorkspace)
- , ("M-S-^", tagToEmptyWorkspace)
+ , ("M-^", focusUrgent)
, ("M-p", myShellPrompt alexXPConfig)
, ("M-e", launchApp alexXPConfig "emacsclient" >> (windows (W.greedyView "5:code")))
@@ -387,15 +478,14 @@ myKeys c hostname =
, ("M-o M-s", sshPrompt alexXPConfig)
, ("M-o M-x", xmonadPrompt alexXPConfig)
- , ("M-g", goToSelected defaultGSConfig)
- , ("M-S-g", bringSelected defaultGSConfig)
-
- , ("M-<Escape>", focusUrgent)
-
, ("M-+", sendMessage Mag.MagnifyMore)
, ("M-S-+", sendMessage Mag.MagnifyLess)
, ("M-#", sendMessage Mag.Toggle)
+ -- topics
+ ,("M-s" , promptedGoto)
+ ,("M-S-s", promptedShift)
+
-- multimedia keys
, ("<XF86AudioLowerVolume>", spawn "amixer -c0 -- set Master playback 2dB-")
, ("<XF86AudioRaiseVolume>", spawn "amixer -c0 -- set Master playback 2dB+")
@@ -406,19 +496,11 @@ myKeys c hostname =
]
++
-
- -- switch to / move / copy to workspace
[
- (m ++ k, windows $ f i)
- | (i, k) <- zip myWorkspaces $ [[k] | k <- "1234567890"] ++ ["<ssharp>", "<acute>"],
- (m, f) <- [("M-", W.view), ("M-S-", W.shift), ("M-C-", copy)]
- ]
- ++
-
- [
- (m ++ k, screenWorkspace s >>= flip whenJust (windows . f))
- | (k, s) <- [("a", 0), ("s", 1)],
- (m, f) <- [("M-", W.view), ("M-S-", W.shift), ("M-C-", copy)]
+ -- switch to / move to topic
+ ("M-" ++ m ++ [k], a i)
+ | (a, m) <- [(switchNthLastFocused topicsConfig,""), (shiftNthLastFocused, "S-")]
+ , (i, k) <- zip [1..] "123456789"
]
where
shutdownKey = case hostname of
@@ -436,9 +518,10 @@ myMouse modm c =
(\w -> focus w >> Flex.mouseWindow Flex.resize w))
]
---
--- Layout
---
+--}}}
+
+--{{{ Layout
+
myLayout =
avoidStruts
$ smartBorders
@@ -448,20 +531,22 @@ myLayout =
$ onWorkspace "2:mail" layoutsTabbed
$ onWorkspace "4:im" (imgrid ||| imtab ||| immosaic)
$ onWorkspace "5:code" layoutsTabbed
- $ onWorkspace "video" (noBorders tabbed)
+ $ onWorkspace "video" (noBorders myTabbed)
$ onWorkspace "gimp" gimp
$ layouts
where
- layouts = tiled ||| Mirror tiled ||| ThreeColMid 1 (3/100) (1/2) ||| tabbed
- layoutsTabbed = tabbed ||| tiled ||| Mirror tiled ||| ThreeColMid 1 (3/100) (1/2)
- tiled = Tall 1 (3/100) (1/2)
- gimp = named "gimp"
- $ withIM (0.11) (Role "gimp-toolbox")
- $ reflectHoriz
- $ withIM (0.15) (Role "gimp-dock") (trackFloating tabbed)
- tabbed = named "Tabbed"
- $ tabbedBottom shrinkText alexTheme
+ layouts = tiled ||| Mirror tiled ||| ThreeColMid 1 (3/100) (1/2) ||| myTabbed
+ layoutsTabbed = myTabbed ||| tiled ||| Mirror tiled ||| ThreeColMid 1 (3/100) (1/2)
+ tiled = Tall 1 (3/100) (1/2)
+ gimp = named "gimp"
+ $ withIM (0.11) (Role "gimp-toolbox")
+ $ reflectHoriz
+ $ withIM (0.15) (Role "gimp-dock") (trackFloating myTabbed)
imbase a = withIM (1%7) (Or (ClassName "Tkabber") (Role "roster")) a
- imgrid = imbase Grid
- imtab = imbase tabbed
+ imgrid = imbase Grid
+ imtab = imbase myTabbed
immosaic = imbase $ MosaicAlt M.empty
+ myTabbed = named "Tabbed"
+ $ tabbedBottom shrinkText alexTheme
+
+--}}}