Difference between revisions of "Xmonad/Config archive/loupgaroublonds xmonad.hs"

From HaskellWiki
Jump to navigation Jump to search
(first post to this page)
 
(updated config)
 
(5 intermediate revisions by the same user not shown)
Line 1: Line 1:
  +
This is my configuration that works under gnome. It's not too sophisticated, although there's a certain amount of verbosity i could get rid of if i wanted to. Most of it's there, though because of some fun plans i have for Prompt. If only prompt would work on 64-bit....
  +
  +
Highlights include:
  +
  +
No static desktops used, starts up in dashboard mode.
  +
  +
Makes use of dynamic workspaces on top of workspace directories and topic space to bind the idea of a directory, a context, and a workspace. Good for development of projects.
  +
  +
Replaces Full with Tabs. The philosophy is that you should always know what's on a workspace when you look at it. Nothing should be hiding behind something else.
  +
  +
Alternate Mod Key so not to interfere with other programs.
  +
  +
For each application hotkey, there is also one that will invoke it on what ever is on the clipboard. There is also a bit of hackery for the terminal, so that it doesn't close when the app is done running. This is good for reviewing the output.
  +
  +
EZConfig for easier configuration of key presses. It's not just easier, but also cleaner and easier on the eyes.
  +
  +
Zero borders because programs, windows and applications are not important, functionality is. Terminals are multicoloured to make them easier to see.
  +
  +
Since there are no borders, when something is full screen, it is genuinely full screen.
  +
  +
The usual EWMH and Dock hooks for all your bloated DE needs.
  +
  +
Single key for logging on to shell server for chatting on irssi.
  +
  +
That should be the big stuff. Enjoy.
  +
  +
This is a work in progress, see inline comments for more tidbits of info
  +
  +
[[Image:Loupgaroublond-config.png|thumb|Description]]
  +
 
<haskell>
 
<haskell>
  +
{-# OPTIONS_GHC -fglasgow-exts #-}
  +
 
import XMonad
 
import XMonad
import System.Exit
+
import XMonad.Operations
  +
 
import qualified XMonad.StackSet as W
+
import XMonad.Actions.Commands
import qualified Data.Map as M
+
import XMonad.Actions.CycleWS
  +
import XMonad.Actions.DeManage
  +
import qualified XMonad.Actions.DynamicWorkspaces as DW
  +
  +
import XMonad.Hooks.DynamicLog as DL
 
import XMonad.Hooks.EwmhDesktops
 
import XMonad.Hooks.EwmhDesktops
 
import XMonad.Hooks.ManageDocks
 
import XMonad.Hooks.ManageDocks
  +
import XMonad.Hooks.ManageHelpers
   
  +
import XMonad.Util.Loggers as LS
main = xmonad $ defaultConfig
 
  +
import XMonad.Util.Run
{ borderWidth = 3
 
  +
import XMonad.Util.WindowProperties
, terminal = "gnome-terminal"
 
  +
import XMonad.Util.XSelection
, defaultGaps = _defaultGaps
 
, normalBorderColor = _normalBorderColor
 
, focusedBorderColor = _focusedBorderColor
 
 
, layoutHook = _layout
 
, keys = _keys
 
, manageHook = _manageHook
 
, logHook = _logHook }
 
   
  +
import qualified XMonad.Actions.DwmPromote as DwmP
_defaultGaps = [(0,0,0,0)]
 
  +
import qualified XMonad.Actions.FlexibleResize as Flex
  +
import qualified XMonad.Actions.RandomBackground as RandBg
  +
import qualified XMonad.Actions.SinkAll as SinkAll
  +
import qualified XMonad.Actions.TopicSpace as TS
  +
import qualified XMonad.Actions.UpdatePointer as UP
  +
import qualified XMonad.Actions.WithAll as WithAll
   
  +
import qualified XMonad.Layout.Accordion as Acc
_normalBorderColor = "#e7e7e7"
 
  +
import qualified XMonad.Layout.Circle as Cir
_focusedBorderColor = "#AFD6ED"
 
  +
import qualified XMonad.Layout.PerWorkspace as PW
  +
import qualified XMonad.Layout.Tabbed as Tab
  +
import qualified XMonad.Layout.WorkspaceDir as WD
   
  +
import qualified XMonad.Prompt as P
_keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
 
  +
import qualified XMonad.Prompt.Input as PI
-- launch a terminal
 
  +
import qualified XMonad.Prompt.Shell as PS
[ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
 
  +
import qualified XMonad.Prompt.Ssh as PSsh
-- launch dmenu
 
  +
import qualified XMonad.Prompt.Window as PWin
, ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"")
 
  +
import qualified XMonad.Prompt.Workspace as PWork
-- launch gmrun
 
  +
import qualified XMonad.StackSet as W
, ((modMask .|. shiftMask, xK_p ), spawn "gmrun")
 
  +
-- close focused window
 
  +
import qualified XMonad.Util.EZConfig as EZ
, ((modMask .|. shiftMask, xK_c ), kill)
 
  +
-- Rotate through the available layout algorithms
 
  +
import Control.Monad
, ((modMask, xK_space ), sendMessage NextLayout)
 
  +
import Data.Either.Utils
-- Reset the layouts on the current workspace to default
 
  +
import Data.Monoid
, ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)
 
  +
import Data.Maybe
-- Resize viewed windows to the correct size
 
  +
import System.IO
, ((modMask, xK_n ), refresh)
 
  +
import System.Exit
-- Move focus to the next window
 
  +
, ((modMask, xK_Tab ), windows W.focusDown)
 
  +
import qualified Data.Map as M
-- Move focus to the next window
 
  +
, ((modMask, xK_j ), windows W.focusDown)
 
  +
import qualified Network.MPD as MPD
-- Move focus to the previous window
 
  +
, ((modMask, xK_k ), windows W.focusUp )
 
  +
main :: IO ()
-- Move focus to the master window
 
  +
main = do
, ((modMask, xK_m ), windows W.focusMaster )
 
  +
-- TS.checkTopicConfig _workspaces _topicConfig
-- Swap the focused window and the master window
 
  +
dzen <- spawnPipe "dzen2 -fn '-*-terminus-*-*-*-*-12-*-*-*-*-*-*-*' -ta l"
, ((modMask, xK_Return), windows W.swapMaster)
 
  +
xmonad $ defaultConfig
-- Swap the focused window with the next window
 
, ((modMask .|. shiftMask, xK_j ), windows W.swapDown )
+
{ borderWidth = 0
  +
, terminal = terminalCmd
-- Swap the focused window with the previous window
 
, ((modMask .|. shiftMask, xK_k ), windows W.swapUp )
+
, normalBorderColor = _normalBorderColor
  +
, focusedBorderColor = _focusedBorderColor
-- Shrink the master area
 
, ((modMask, xK_h ), sendMessage Shrink)
+
, workspaces = _workspaces
  +
, layoutHook = _layout
-- Expand the master area
 
, ((modMask, xK_l ), sendMessage Expand)
+
, keys = _keys
  +
, modMask = mod4Mask
-- Push window back into tiling
 
, ((modMask, xK_t ), withFocused $ windows . W.sink)
+
, logHook = _logHook dzen
  +
, handleEventHook = ewmhDesktopsEventHook
-- Increment the number of windows in the master area
 
, ((modMask , xK_comma ), sendMessage (IncMasterN 1))
+
, manageHook = _manageHook }
  +
-- Deincrement the number of windows in the master area
 
  +
, ((modMask , xK_period), sendMessage (IncMasterN (-1)))
 
  +
-- Workspaces
-- toggle the status bar gap
 
  +
, ((modMask , xK_b ),
 
  +
_spaces = M.fromList $
modifyGap (\i n -> let x = (XMonad.defaultGaps conf ++ repeat (0,0,0,0)) !! i
 
  +
[ ("schutbord", "~")
in if n == x then (0,0,0,0) else x))
 
  +
, ("browsen", "~")
-- Quit xmonad
 
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
+
, ("praten", "~")
  +
, ("muziek", "~/Muziek")
-- Restart xmonad
 
, ((modMask , xK_q ),
+
, ("berichten", "~/Mail")
  +
, ("agenda", "~/Documenten/Day Planner")
broadcastMessage ReleaseResources >> restart (Just "xmonad") True)
 
  +
, ("ldap", "~")
]
 
  +
, ("flim", "~")
++
 
  +
, ("terminals", "~")
--
 
-- mod-[1..9], Switch to workspace N
+
]
  +
-- mod-shift-[1..9], Move client to workspace N
 
  +
_workspaces = [ "schutbord"]
--
 
  +
[((m .|. modMask, k), windows $ f i)
 
  +
_topicConfig = TS.TopicConfig {
| (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
 
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
+
TS.topicDirs = _spaces
  +
, TS.topicActions = _topicActions
++
 
  +
, TS.defaultTopicAction = (const $ return ())
--
 
  +
, TS.defaultTopic = "schutbord"
-- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
 
  +
, TS.maxTopicHistory = 10
-- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
 
--
+
}
  +
[((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
 
  +
_topicActions = M.fromList $
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
 
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
+
[ ("schutbord", replicateM_ 2 runColourTerminal)
  +
, ("terminals", replicateM_ 2 runColourTerminal)
 
  +
, ("browsen", runBrowser)
------------------------------------------------------------------------
 
  +
, ("praten", runChat)
-- Mouse bindings: default actions bound to mouse events
 
  +
, ("berichten", runMail)
--
 
  +
, ("muziek", runMixer >> runMusicPlayer)
  +
, ("transmission", runTorrent)
  +
, ("agenda", runEditor)
  +
, ("flim", runFilm)
  +
]
  +
  +
-- creates the workspace if needed
  +
goto :: TS.Topic -> X ()
  +
goto t = newWorkspace t >> TS.switchTopic _topicConfig t
  +
  +
shift = windows . W.shift
  +
  +
  +
-- Themes
  +
  +
_normalBorderColor :: String
  +
_normalBorderColor = "#EFEFEF"
  +
  +
_focusedBorderColor :: String
  +
_focusedBorderColor= "#000000"
  +
  +
-- Applications
  +
  +
terminalCmd = "urxvtc"
  +
runTerminal :: X()
  +
runTerminal = spawn terminalCmd
  +
runColourTerminal = RandBg.randomBg $ RandBg.HSV 0x44 0x00
  +
  +
saveSession cmd = "/bin/bash -c '" ++ cmd ++ "; /bin/bash'"
  +
manPage cmd = saveSession $ "/usr/bin/man " ++ cmd
  +
inTerminal cmd = terminalCmd ++ " -e " ++ cmd
  +
runInTerminal f = transformPromptSelection f $ terminalCmd ++ " -e "
  +
pasteTerminal = runInTerminal saveSession
  +
manTerminal = runInTerminal manPage
  +
  +
terminalIrssiCmd = terminalCmd
  +
chatCmd = inTerminal irssiCmd
  +
irssiCmd = "ssh -t some.irc.server.com screen -dr irc" -- opens up your irssi right away
  +
runChat = spawn chatCmd
  +
  +
browserCmd = "firefox"
  +
runBrowser = spawn browserCmd
  +
pasteBrowser = safePromptSelection browserCmd
  +
  +
mailCmd = inTerminal "mutt"
  +
runMail = spawn mailCmd
  +
  +
runCmdLine = PS.shellPrompt P.defaultXPConfig
  +
  +
fileManagerCmd = "thunar"
  +
runFileManager = spawn fileManagerCmd
  +
  +
musicPlayerCmd = inTerminal "ncmpc"
  +
runMusicPlayer = spawn musicPlayerCmd
  +
pasteMusicPlayer = promptSelection musicPlayerCmd
  +
  +
mixerCmd = inTerminal "alsamixer"
  +
runMixer = spawn mixerCmd
  +
  +
restartXMonad = broadcastMessage ReleaseResources >>
  +
restart "xmonad" True
  +
  +
rememberCmd = "/path/to/emacsclient-starter org-protocol:/remember:/t/foo/" -- for adding quick reminders to your agenda
  +
runRemember = spawn rememberCmd
  +
  +
torrentCmd = "transmission"
  +
runTorrent = spawn torrentCmd
  +
  +
filmCmd = "smplayer"
  +
runFilm = spawn filmCmd
  +
  +
-- starter for emacs that has a seperate emacs server per working directory, so the files open for one context are not in the other context
  +
editorCmd :: String
  +
editorCmd = "edit"
  +
  +
runEditor :: X ()
  +
runEditor = spawn editorCmd
  +
  +
  +
-- Keys
  +
  +
_keys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X())
  +
_keys = \conf -> EZ.mkKeymap conf $(_emacsKeys conf)
  +
  +
_emacsKeys :: XConfig Layout -> [(String, X())]
  +
_emacsKeys = \conf ->
  +
[ -- Applications
  +
("M-t", goto "terminals")
  +
, ("M-S-t", runColourTerminal)
  +
, ("M-v M-t", pasteTerminal)
  +
, ("M-v M-d", manTerminal)
  +
, ("M-i", goto "browsen")
  +
, ("M-S-i", runBrowser)
  +
, ("M-v M-i", pasteBrowser)
  +
, ("M-p", runCmdLine)
  +
, ("M-x", WD.changeDir P.defaultXPConfig)
  +
, ("M-e", goto "muziek")
  +
-- , ("M-o", runMixer)
  +
, ("M-h", runFileManager)
  +
, ("M-s", goto "praten")
  +
, ("M-m", goto "berichten")
  +
, ("M-S-m", runMail)
  +
, ("M-u", goto "agenda")
  +
, ("M-0", goto "schutbord")
  +
, ("M-w", goto "flim")
  +
  +
-- mpd
  +
, ("<XF86AudioPlay>", io $ return . fromRight =<< MPD.withMPD MPD.toggle)
  +
, ("<XF86AudioStop>", io $ return . fromRight =<< MPD.withMPD MPD.stop)
  +
, ("<XF86AudioNext>", io $ return . fromRight =<< MPD.withMPD MPD.next)
  +
, ("<XF86AudioPrev>", io $ return . fromRight =<< MPD.withMPD MPD.previous)
  +
, ("<XF86AudioLowerVolume>", spawn "amixer set Master 2-")
  +
, ("<XF86AudioRaiseVolume>", spawn "amixer set Master 2+")
  +
, ("<XF86AudioMute>", spawn "amixer set Master toggle")
  +
  +
-- couple of scripts to change brightness, very hardware specific to my laptop
  +
-- brightness
  +
, ("<XF86MonBrightnessUp>", spawn "lcd-brightness-inc")
  +
, ("<XF86MonBrightnessDown>", spawn "lcd-brightness-dec")
  +
  +
-- Layouts
  +
, ("M-n", refresh)
  +
, ("M-S-<Space>", setLayout $ XMonad.layoutHook conf)
  +
, ("M-<Space>", sendMessage NextLayout)
  +
, ("M-<Tab>", windows W.focusDown)
  +
, ("M-j", windows W.focusDown)
  +
, ("M-k", windows W.focusUp)
  +
, ("M-<Return>", windows W.focusMaster)
  +
, ("M-S-<Return>", DwmP.dwmpromote)
  +
, ("M-S-j", windows W.swapDown)
  +
, ("M-S-k", windows W.swapUp)
  +
, ("M-g", sendMessage Shrink)
  +
, ("M-l", sendMessage Expand)
  +
, ("M-r", withFocused $ windows . W.sink)
  +
, ("M-,", sendMessage (IncMasterN 1))
  +
, ("M-.", sendMessage (IncMasterN (-1)))
  +
  +
-- Toggle full screen
  +
, ("M-<F12>", sendMessage ToggleStruts >> refresh)
  +
  +
-- Windows
  +
, ("M-[", PWork.workspacePrompt P.defaultXPConfig goto)
  +
, ("M-]", PWin.windowPromptGoto P.defaultXPConfig)
  +
,("M-S-[", PWork.workspacePrompt P.defaultXPConfig shift)
  +
  +
, ("M-c", kill) -- window
  +
, ("M-S-c", WithAll.killAll) ] -- window
  +
-- ++
  +
-- [ ("M-" ++ [num], goto name)
  +
-- | (name, num) <-
  +
-- zip _workspaces (['1' .. '9'] ++ ['0'])]
  +
  +
-- -- Workspaces
  +
-- ++
  +
-- [ ("M-S-" ++ [num], shift name)
  +
-- | (name, num) <-
  +
-- zip _workspaces (['1' .. '9'] ++ ['0'])]
  +
++
  +
[ ("M-<Right>", moveTo Next NonEmptyWS)
  +
, ("M-<Left>", moveTo Prev NonEmptyWS)
  +
, ("M-S-<Right>", moveTo Next EmptyWS)
  +
, ("M-S-<Left>", moveTo Prev EmptyWS)
  +
-- Toggle between current and previous
  +
, ("M-`", toggleWS)
  +
  +
, ("M-S-n", PI.inputPrompt P.defaultXPConfig "New Workspace:" PI.?+ newWorkspaceDir)
  +
, ("M-S-<Backspace>", WithAll.killAll >> DW.removeWorkspace) --buggy, messes with focus and creates flicker, needs to be fixed
  +
, ("M-S-r", DW.renameWorkspace P.defaultXPConfig)
  +
  +
-- -- Commands
  +
-- , ("M-y", runCommand _commands)
  +
  +
-- -- Remember
  +
, ("M1-C-r", runRemember)
  +
-- xmonad
  +
, ("M1-q", restartXMonad)]
  +
  +
newWorkspace :: WorkspaceId -> X ()
  +
newWorkspace w = do exists <- widExist w
  +
if (not exists) then DW.addHiddenWorkspace w else return ()
  +
  +
newWorkspaceDir :: WorkspaceId -> X ()
  +
newWorkspaceDir w = do exists <- widExist w
  +
if (not exists)
  +
then do DW.addHiddenWorkspace w
  +
goto w
  +
WD.changeDir P.defaultXPConfig
  +
else return ()
  +
  +
widExist :: WorkspaceId -> X Bool
  +
widExist wid = do xs <- get
  +
return $ widExists wid ( windowset xs )
  +
  +
widExists :: WorkspaceId -> W.StackSet WorkspaceId l a s sd -> Bool
  +
widExists wid ws = wid `elem` map W.tag (W.workspaces ws)
  +
  +
  +
-- isWorkspace sc w = w `elem` map W.tag (W.current w : W.visible w)
  +
  +
-- Mouse bindings
  +
  +
_mouseBindings :: XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ())
 
_mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
 
_mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
 
 
-- mod-button1, Set the window to floating mode and move by dragging
 
-- mod-button1, Set the window to floating mode and move by dragging
 
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
 
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
Line 101: Line 341:
 
, ((modMask, button2), (\w -> focus w >> windows W.swapMaster))
 
, ((modMask, button2), (\w -> focus w >> windows W.swapMaster))
 
-- mod-button3, Set the window to floating mode and resize by dragging
 
-- mod-button3, Set the window to floating mode and resize by dragging
, ((modMask, button3), (\w -> focus w >> mouseResizeWindow w))
+
, ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w))
 
-- you may also bind events to the mouse scroll wheel (button4 and button5)
 
-- you may also bind events to the mouse scroll wheel (button4 and button5)
 
]
 
]
  +
------------------------------------------------------------------------
 
-- Layouts:
+
-- Layouts
  +
 
  +
-- this is by far not finished either
-- You can specify and transform your layouts by modifying these values.
 
  +
_layout = avoidStruts
-- If you change layout bindings be sure to use 'mod-shift-space' after
 
  +
$ _onWorkspace "agenda" Tab.simpleTabbed --scaffolding :)
-- restarting (with 'mod-q') to reset your layout state to the new
 
  +
$ _onWorkspace "browsen" Tab.simpleTabbed
-- defaults, as xmonad preserves your old layout settings by default.
 
  +
$ _onWorkspace "foo" Tab.simpleTabbed
--
 
  +
$ _homeDir
-- The available layouts. Note that each layout is separated by |||,
 
  +
-- which denotes layout choice.
 
  +
_easyLay = _tiled ||| Mirror _tiled ||| Tab.simpleTabbed
--
 
  +
_layout = avoidStruts (tiled ||| Mirror tiled ||| Full)
 
  +
_tiled = Tall nmaster delta ratio
 
where
 
where
-- default tiling algorithm partitions the screen into two panes
 
tiled = Tall nmaster delta ratio
 
-- The default number of windows in the master pane
 
 
nmaster = 1
 
nmaster = 1
-- Default proportion of screen occupied by master pane
 
 
ratio = 1/2
 
ratio = 1/2
-- Percent of screen to increment by when resizing panes
 
 
delta = 3/100
 
delta = 3/100
  +
 
  +
_onWorkspace t l = PW.onWorkspace t $ WD.workspaceDir (_folderOf t) l
------------------------------------------------------------------------
 
  +
-- Window rules:
 
  +
_folderOf = fromMaybe "~" . flip M.lookup _spaces
 
  +
-- Execute arbitrary actions and WindowSet manipulations when managing
 
  +
_homeDir = WD.workspaceDir "~" _easyLay
-- a new window. You can use this to, for example, always float a
 
  +
_homeDirT = WD.workspaceDir "~" Tab.simpleTabbed
-- particular program, or have a client always appear on a particular
 
  +
-- workspace.
 
  +
-- ManageHooks
--
 
-- To find the property name associated with a program, use
 
-- > xprop | grep WM_CLASS
 
-- and click on the client you're interested in.
 
--
 
-- To match on the WM_NAME, you can use 'title' in the same way that
 
-- 'className' and 'resource' are used below.
 
--
 
 
_manageHook = composeAll
 
_manageHook = composeAll
[ className =? "MPlayer" --> doFloat
+
[ isFullscreen --> doFullFloat
, className =? "Gimp" --> doFloat
+
, className =? "MPlayer" --> doFloat
, resource =? "desktop_window" --> doIgnore
+
, checkDock --> doIgnore ]
, resource =? "kdesktop" --> doIgnore ]
+
<+> composeOne
  +
[ transience
<+> manageDocks
 
  +
, className =? "Firefox" -?> doF (W.shift "web")
 
  +
]
------------------------------------------------------------------------
 
  +
<+> manageDocks
-- Status bars and logging
 
  +
 
  +
-- Perform an arbitrary action on each internal state change or X event.
 
  +
-- LogHooks
-- See the 'DynamicLog' extension for examples.
 
  +
--
 
  +
_logHook dzen = do
-- To emulate dwm's status bar
 
  +
DL.dynamicLogWithPP $ DL.defaultPP{ DL.ppOutput = hPutStrLn dzen
--
 
  +
, DL.ppExtras = [ LS.logCmd "acpi -b"
-- > logHook = dynamicLogDzen
 
  +
, LS.loadAvg
--
 
  +
, LS.date "%a %b %d %H.%M.%S"
_logHook = do ewmhDesktopsLogHook
 
  +
, LS.logCmd "acpi -t"
return ()
 
  +
, LS.logCmd "nm-tool |grep State "] }
  +
ewmhDesktopsLogHook
  +
UP.updatePointer (UP.Relative 0.9 0.9)
  +
  +
 
</haskell>
 
</haskell>

Latest revision as of 10:25, 24 May 2010

This is my configuration that works under gnome. It's not too sophisticated, although there's a certain amount of verbosity i could get rid of if i wanted to. Most of it's there, though because of some fun plans i have for Prompt. If only prompt would work on 64-bit....

Highlights include:

No static desktops used, starts up in dashboard mode.

Makes use of dynamic workspaces on top of workspace directories and topic space to bind the idea of a directory, a context, and a workspace. Good for development of projects.

Replaces Full with Tabs. The philosophy is that you should always know what's on a workspace when you look at it. Nothing should be hiding behind something else.

Alternate Mod Key so not to interfere with other programs.

For each application hotkey, there is also one that will invoke it on what ever is on the clipboard. There is also a bit of hackery for the terminal, so that it doesn't close when the app is done running. This is good for reviewing the output.

EZConfig for easier configuration of key presses. It's not just easier, but also cleaner and easier on the eyes.

Zero borders because programs, windows and applications are not important, functionality is. Terminals are multicoloured to make them easier to see.

Since there are no borders, when something is full screen, it is genuinely full screen.

The usual EWMH and Dock hooks for all your bloated DE needs.

Single key for logging on to shell server for chatting on irssi.

That should be the big stuff. Enjoy.

This is a work in progress, see inline comments for more tidbits of info

Description
{-# OPTIONS_GHC -fglasgow-exts #-}

import XMonad
import XMonad.Operations

import XMonad.Actions.Commands
import XMonad.Actions.CycleWS
import XMonad.Actions.DeManage
import qualified XMonad.Actions.DynamicWorkspaces as DW

import XMonad.Hooks.DynamicLog as DL
import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers

import XMonad.Util.Loggers as LS
import XMonad.Util.Run
import XMonad.Util.WindowProperties
import XMonad.Util.XSelection

import qualified XMonad.Actions.DwmPromote as DwmP
import qualified XMonad.Actions.FlexibleResize as Flex
import qualified XMonad.Actions.RandomBackground as RandBg
import qualified XMonad.Actions.SinkAll as SinkAll
import qualified XMonad.Actions.TopicSpace as TS
import qualified XMonad.Actions.UpdatePointer as UP
import qualified XMonad.Actions.WithAll as WithAll

import qualified XMonad.Layout.Accordion as Acc
import qualified XMonad.Layout.Circle as Cir
import qualified XMonad.Layout.PerWorkspace as PW
import qualified XMonad.Layout.Tabbed as Tab
import qualified XMonad.Layout.WorkspaceDir as WD

import qualified XMonad.Prompt as P
import qualified XMonad.Prompt.Input as PI
import qualified XMonad.Prompt.Shell as PS
import qualified XMonad.Prompt.Ssh as PSsh
import qualified XMonad.Prompt.Window as PWin
import qualified XMonad.Prompt.Workspace as PWork
import qualified XMonad.StackSet as W

import qualified XMonad.Util.EZConfig as EZ

import Control.Monad
import Data.Either.Utils
import Data.Monoid
import Data.Maybe
import System.IO
import System.Exit

import qualified Data.Map as M

import qualified Network.MPD as MPD

main :: IO ()
main = do
  -- TS.checkTopicConfig _workspaces _topicConfig
  dzen <- spawnPipe "dzen2 -fn '-*-terminus-*-*-*-*-12-*-*-*-*-*-*-*' -ta l"
  xmonad $ defaultConfig
             { borderWidth        = 0
             , terminal           = terminalCmd
             , normalBorderColor  = _normalBorderColor
             , focusedBorderColor = _focusedBorderColor
             , workspaces = _workspaces
             , layoutHook = _layout
             , keys = _keys
             , modMask = mod4Mask
             , logHook = _logHook dzen
	     , handleEventHook = ewmhDesktopsEventHook
             , manageHook = _manageHook }


-- Workspaces

_spaces = M.fromList $
          [ ("schutbord", "~")
          , ("browsen", "~")
          , ("praten", "~")
          , ("muziek", "~/Muziek")
          , ("berichten", "~/Mail")
          , ("agenda", "~/Documenten/Day Planner")
          , ("ldap", "~")
          , ("flim", "~")
          , ("terminals", "~")
          ]

_workspaces = [ "schutbord"]

_topicConfig = TS.TopicConfig {
                 TS.topicDirs = _spaces
               , TS.topicActions = _topicActions
               , TS.defaultTopicAction = (const $ return ())
               , TS.defaultTopic = "schutbord"
               , TS.maxTopicHistory = 10
               }

_topicActions = M.fromList $
                [ ("schutbord", replicateM_ 2 runColourTerminal)
                , ("terminals", replicateM_ 2 runColourTerminal)
                , ("browsen", runBrowser)
                , ("praten", runChat)
                , ("berichten", runMail)
                , ("muziek", runMixer >> runMusicPlayer)
                , ("transmission", runTorrent)
                , ("agenda", runEditor)
                , ("flim", runFilm)
                ]

-- creates the workspace if needed
goto :: TS.Topic -> X ()
goto t = newWorkspace t >> TS.switchTopic _topicConfig t

shift = windows . W.shift


-- Themes

_normalBorderColor :: String
_normalBorderColor = "#EFEFEF"

_focusedBorderColor :: String
_focusedBorderColor= "#000000"

-- Applications

terminalCmd = "urxvtc"
runTerminal :: X()
runTerminal = spawn terminalCmd
runColourTerminal = RandBg.randomBg $ RandBg.HSV 0x44 0x00

saveSession cmd = "/bin/bash -c '" ++ cmd ++ "; /bin/bash'"
manPage cmd = saveSession $ "/usr/bin/man " ++ cmd
inTerminal cmd = terminalCmd ++ " -e " ++ cmd
runInTerminal f = transformPromptSelection f $ terminalCmd ++ " -e "
pasteTerminal = runInTerminal saveSession
manTerminal = runInTerminal manPage

terminalIrssiCmd = terminalCmd
chatCmd = inTerminal irssiCmd
irssiCmd = "ssh -t some.irc.server.com screen -dr irc" -- opens up your irssi right away
runChat = spawn chatCmd

browserCmd = "firefox"
runBrowser = spawn browserCmd
pasteBrowser = safePromptSelection browserCmd

mailCmd = inTerminal "mutt"
runMail = spawn mailCmd

runCmdLine = PS.shellPrompt P.defaultXPConfig

fileManagerCmd = "thunar"
runFileManager = spawn fileManagerCmd

musicPlayerCmd = inTerminal "ncmpc"
runMusicPlayer = spawn musicPlayerCmd
pasteMusicPlayer = promptSelection musicPlayerCmd

mixerCmd = inTerminal "alsamixer"
runMixer = spawn mixerCmd

restartXMonad = broadcastMessage ReleaseResources >>
                restart "xmonad" True

rememberCmd = "/path/to/emacsclient-starter org-protocol:/remember:/t/foo/" -- for adding quick reminders to your agenda
runRemember = spawn rememberCmd

torrentCmd = "transmission"
runTorrent = spawn torrentCmd

filmCmd = "smplayer"
runFilm = spawn filmCmd

-- starter for emacs that has a seperate emacs server per working directory, so the files open for one context are not in the other context
editorCmd :: String
editorCmd = "edit"

runEditor :: X ()
runEditor = spawn editorCmd


-- Keys

_keys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X())
_keys = \conf -> EZ.mkKeymap conf $(_emacsKeys conf)

_emacsKeys :: XConfig Layout -> [(String, X())]
_emacsKeys  = \conf ->
              [ -- Applications
                ("M-t", goto "terminals")
              , ("M-S-t", runColourTerminal)
              , ("M-v M-t", pasteTerminal)
              , ("M-v M-d", manTerminal)
              , ("M-i", goto "browsen")
              , ("M-S-i", runBrowser)
              , ("M-v M-i", pasteBrowser)
              , ("M-p", runCmdLine)
              , ("M-x", WD.changeDir P.defaultXPConfig)
              , ("M-e", goto "muziek")
              -- , ("M-o", runMixer)
              , ("M-h", runFileManager)
              , ("M-s", goto "praten")
              , ("M-m", goto "berichten")
              , ("M-S-m", runMail)
              , ("M-u", goto "agenda")
              , ("M-0", goto "schutbord")
              , ("M-w", goto "flim")

              -- mpd
              , ("<XF86AudioPlay>", io $ return . fromRight =<< MPD.withMPD MPD.toggle)
              , ("<XF86AudioStop>", io $ return . fromRight =<< MPD.withMPD MPD.stop)
              , ("<XF86AudioNext>", io $ return . fromRight =<< MPD.withMPD MPD.next)
              , ("<XF86AudioPrev>", io $ return . fromRight =<< MPD.withMPD MPD.previous)
              , ("<XF86AudioLowerVolume>", spawn "amixer set Master 2-")
              , ("<XF86AudioRaiseVolume>", spawn "amixer set Master 2+")
              , ("<XF86AudioMute>", spawn "amixer set Master toggle")

              -- couple of scripts to change brightness, very hardware specific to my laptop
              -- brightness
              , ("<XF86MonBrightnessUp>", spawn "lcd-brightness-inc")
              , ("<XF86MonBrightnessDown>", spawn "lcd-brightness-dec")

              -- Layouts
              , ("M-n", refresh)
              , ("M-S-<Space>", setLayout $ XMonad.layoutHook conf)
              , ("M-<Space>", sendMessage NextLayout)
              , ("M-<Tab>", windows W.focusDown)
              , ("M-j", windows W.focusDown)
              , ("M-k", windows W.focusUp)
              , ("M-<Return>", windows W.focusMaster)
              , ("M-S-<Return>",  DwmP.dwmpromote)
              , ("M-S-j", windows W.swapDown)
              , ("M-S-k", windows W.swapUp)
              , ("M-g", sendMessage Shrink)
              , ("M-l", sendMessage Expand)
              , ("M-r", withFocused $ windows . W.sink)
              , ("M-,", sendMessage (IncMasterN 1))
              , ("M-.", sendMessage (IncMasterN (-1)))

              -- Toggle full screen
              , ("M-<F12>", sendMessage ToggleStruts >> refresh)

              -- Windows
              , ("M-[", PWork.workspacePrompt P.defaultXPConfig goto)
              , ("M-]", PWin.windowPromptGoto P.defaultXPConfig)
              ,("M-S-[", PWork.workspacePrompt P.defaultXPConfig shift)

              , ("M-c", kill)             -- window
              , ("M-S-c", WithAll.killAll) ] -- window
              -- ++
              -- [ ("M-" ++ [num], goto name)
              --       | (name, num) <-
              --           zip _workspaces (['1' .. '9'] ++ ['0'])]

              -- -- Workspaces
              -- ++
              -- [ ("M-S-" ++ [num], shift name)
              --       | (name, num) <-
              --           zip _workspaces (['1' .. '9'] ++ ['0'])]
              ++
              [ ("M-<Right>", moveTo Next NonEmptyWS)
              , ("M-<Left>", moveTo Prev NonEmptyWS)
              , ("M-S-<Right>", moveTo Next EmptyWS)
              , ("M-S-<Left>", moveTo Prev EmptyWS)
              -- Toggle between current and previous
              , ("M-`", toggleWS)

              , ("M-S-n", PI.inputPrompt P.defaultXPConfig "New Workspace:" PI.?+ newWorkspaceDir)
              , ("M-S-<Backspace>", WithAll.killAll >> DW.removeWorkspace) --buggy, messes with focus and creates flicker, needs to be fixed
              , ("M-S-r", DW.renameWorkspace P.defaultXPConfig)

              -- -- Commands
              -- , ("M-y", runCommand _commands)

              -- -- Remember
              , ("M1-C-r", runRemember)
              -- xmonad
              , ("M1-q", restartXMonad)]

newWorkspace :: WorkspaceId -> X ()
newWorkspace w = do exists <- widExist w
                    if (not exists) then DW.addHiddenWorkspace w else return ()

newWorkspaceDir :: WorkspaceId -> X ()
newWorkspaceDir w = do exists <- widExist w
                       if (not exists)
                           then do DW.addHiddenWorkspace w
                                   goto w
                                   WD.changeDir P.defaultXPConfig
                           else return ()

widExist :: WorkspaceId -> X Bool
widExist wid = do xs <- get
                  return $ widExists wid ( windowset xs )

widExists :: WorkspaceId -> W.StackSet WorkspaceId l a s sd -> Bool
widExists wid ws = wid `elem` map W.tag  (W.workspaces ws)


-- isWorkspace sc w = w `elem` map W.tag (W.current w : W.visible w)

-- Mouse bindings

_mouseBindings :: XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ())
_mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
    -- mod-button1, Set the window to floating mode and move by dragging
    [ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
    -- mod-button2, Raise the window to the top of the stack
    , ((modMask, button2), (\w -> focus w >> windows W.swapMaster))
    -- mod-button3, Set the window to floating mode and resize by dragging
    , ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w))
    -- you may also bind events to the mouse scroll wheel (button4 and button5)
    ]

-- Layouts

-- this is by far not finished either
_layout = avoidStruts
          $ _onWorkspace "agenda" Tab.simpleTabbed --scaffolding :)
          $ _onWorkspace "browsen" Tab.simpleTabbed
          $ _onWorkspace "foo" Tab.simpleTabbed
          $ _homeDir

_easyLay = _tiled ||| Mirror _tiled ||| Tab.simpleTabbed

_tiled   = Tall nmaster delta ratio
    where
      nmaster = 1
      ratio   = 1/2
      delta   = 3/100

_onWorkspace t l = PW.onWorkspace t $ WD.workspaceDir (_folderOf t) l

_folderOf = fromMaybe "~" . flip M.lookup _spaces

_homeDir = WD.workspaceDir "~" _easyLay
_homeDirT = WD.workspaceDir "~" Tab.simpleTabbed

-- ManageHooks
_manageHook = composeAll
              [ isFullscreen                  --> doFullFloat
              , className =? "MPlayer"        --> doFloat
              , checkDock --> doIgnore ]
              <+> composeOne
                      [ transience
                      , className =? "Firefox"    -?> doF (W.shift "web")
                      ]
              <+> manageDocks


-- LogHooks

_logHook dzen = do
  DL.dynamicLogWithPP $ DL.defaultPP{ DL.ppOutput = hPutStrLn dzen
                                    , DL.ppExtras = [ LS.logCmd "acpi -b"
                                                    , LS.loadAvg
                                                    , LS.date "%a %b %d %H.%M.%S"
                                                    , LS.logCmd "acpi -t"
                                                    , LS.logCmd "nm-tool |grep State "] }
  ewmhDesktopsLogHook
  UP.updatePointer (UP.Relative 0.9 0.9)