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

From HaskellWiki
Jump to navigation Jump to search
(header tweaks)
(update for gnome-terminal)
Line 8: Line 8:
 
terminal, XConfig), X()) -}
 
terminal, XConfig), X()) -}
 
import XMonad.Actions.Search (google, wayback, wikipedia, selectSearch, promptSearch)
 
import XMonad.Actions.Search (google, wayback, wikipedia, selectSearch, promptSearch)
import XMonad.Actions.WindowGo (title, raiseMaybe, raiseBrowser, raiseEditor, runOrRaise, (=?))
+
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
 
import XMonad.Config (defaultConfig)
 
import XMonad.Config (defaultConfig)
 
import XMonad.Config.Gnome (gnomeConfig)
 
import XMonad.Config.Gnome (gnomeConfig)
 
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
 
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
  +
import XMonad.Hooks.FadeInactive (fadeInactiveLogHook)
 
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
 
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
 
import XMonad.Hooks.UrgencyHook (withUrgencyHook, FocusHook(..))
 
import XMonad.Hooks.UrgencyHook (withUrgencyHook, FocusHook(..))
Line 17: Line 18:
 
import XMonad.Layout.NoBorders (smartBorders)
 
import XMonad.Layout.NoBorders (smartBorders)
 
import XMonad.Main (xmonad)
 
import XMonad.Main (xmonad)
import XMonad.Operations (kill, windows)
+
import XMonad.Operations (kill, windows, withFocused)
 
import XMonad.Prompt (XPPosition(Top), XPConfig(historySize, height, position, promptBorderWidth, fgColor, bgColor, font), defaultXPConfig)
 
import XMonad.Prompt (XPPosition(Top), XPConfig(historySize, height, position, promptBorderWidth, fgColor, bgColor, font), defaultXPConfig)
 
import XMonad.Prompt.Shell (shellPrompt, prompt, safePrompt)
 
import XMonad.Prompt.Shell (shellPrompt, prompt, safePrompt)
Line 28: Line 29:
 
where myConfig = withUrgencyHook FocusHook $ gnomeConfig { focusedBorderColor = "red"
 
where myConfig = withUrgencyHook FocusHook $ gnomeConfig { focusedBorderColor = "red"
 
, keys = \c -> myKeys c `M.union` keys defaultConfig c
 
, keys = \c -> myKeys c `M.union` keys defaultConfig c
, layoutHook = avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
+
, layoutHook = avoidStruts $ smartBorders (Full ||| Mirror tiled ||| tiled )
, logHook = ewmhDesktopsLogHook
+
, logHook = ewmhDesktopsLogHook >> fadeInactiveLogHook 0xdddddddd
 
, manageHook = myManageHook
 
, manageHook = myManageHook
 
, modMask = mod4Mask
 
, modMask = mod4Mask
 
, normalBorderColor = "grey"
 
, normalBorderColor = "grey"
, terminal = "urxvt"
+
, terminal = "gnome-terminal"
, XMonad.workspaces = ["web", "irc", "code", "music", show (5::Int)]
+
, XMonad.workspaces = ["web", "irc", "code", "music", show (5::Int)] }
}
+
where tiled :: Tall a
where tiled :: Tall a
+
tiled = Tall 1 0.03 0.5
tiled = Tall 1 0.03 0.5
 
   
 
{- Important things to note: We specifically don't use 'managehook
 
{- Important things to note: We specifically don't use 'managehook
Line 43: Line 43:
 
specified applications. Otherwise, we have manageDocks there to allow use of
 
specified applications. Otherwise, we have manageDocks there to allow use of
 
gnome-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
 
gnome-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
-- TODO: suggest that these functions be moved into XMonad proper; lots of
 
-- redundancy there...
 
 
myManageHook :: ManageHook
 
myManageHook :: ManageHook
 
myManageHook = composeAll [ moveToC "Emacs" "code",
 
myManageHook = composeAll [ moveToC "Emacs" "code",
 
moveToC "Firefox" "web",
 
moveToC "Firefox" "web",
moveToC "MPlayer" "music",
 
 
moveToC "amarokapp" "music",
 
moveToC "amarokapp" "music",
 
moveToC "rhythmbox" "music",
 
moveToC "rhythmbox" "music",
 
moveToC "totem" "music",
 
moveToC "totem" "music",
moveToT "irssi" "irc" ]
+
moveToT "irssi" "irc",
 
className =? "defcon.bin.x86" --> unfloat ]
 
<+> manageDocks
 
<+> manageDocks
 
where moveToC c w = className =? c --> doF (W.shift w)
 
where moveToC c w = className =? c --> doF (W.shift w)
 
moveToT t w = title =? t --> doF (W.shift w)
 
moveToT t w = title =? t --> doF (W.shift w)
 
unfloat = ask >>= doF . W.sink
   
 
-- Green and black are easier on my eyes.
 
-- Green and black are easier on my eyes.
Line 80: Line 79:
 
, ((m, xK_c), unsafeSpawn term)
 
, ((m, xK_c), unsafeSpawn term)
 
, ((m .|. shiftMask,xK_c), prompt (term ++ " -e") greenXPConfig)
 
, ((m .|. shiftMask,xK_c), prompt (term ++ " -e") greenXPConfig)
, ((m .|. shiftMask,xK_d), raiseMaybe (runInTerm "-title elinks" "elinks") (title =? "elinks"))
+
, ((m .|. shiftMask,xK_d), raiseMaybe (runInTerm "--title=elinks" "elinks") (title =? "elinks"))
 
, ((m, xK_e), raiseEditor)
 
, ((m, xK_e), raiseEditor)
 
, ((m .|. shiftMask,xK_e), prompt "emacsclient -a emacs" greenXPConfig)
 
, ((m .|. shiftMask,xK_e), prompt "emacsclient -a emacs" greenXPConfig)
Line 90: Line 89:
 
, ((m .|. shiftMask,xK_y), selectSearch wayback)
 
, ((m .|. shiftMask,xK_y), selectSearch wayback)
 
, ((m, xK_Print), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png")
 
, ((m, xK_Print), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png")
, ((m, xK_i), raiseMaybe (runInTerm "-title irssi" "sh -c 'screen -r irssi'") (title =? "irssi"))
+
, ((m, xK_i), raiseMaybe (runInTerm "--title=irssi" "\"sh -c 'screen -r irssi'\"") (title =? "irssi"))
-- We ask for zsh specifically so .zshenv gets picked up and my
+
-- We ask for zsh specifically so ~/.zshenv gets picked up and my
 
-- expanded $PATH gets used; otherwise Mutt can't find needed scripts.
 
-- expanded $PATH gets used; otherwise Mutt can't find needed scripts.
, ((m, xK_m), raiseMaybe (runInTerm "-title mutt" "zsh -c 'mutt'") (title =? "mutt"))
+
, ((m, xK_m), raiseMaybe (runInTerm "--title=mutt" "\"zsh -c 'mutt'\"") (title =? "mutt"))
 
, ((m .|. shiftMask,xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
 
, ((m .|. shiftMask,xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
, ((m, xK_r), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
+
, ((m, xK_r), raiseMaybe (runInTerm "--title='rtorrent'" "\"sh -c 'screen -r rtorrent'\"") (title =? "rtorrent"))
 
, ((m, xK_d), raiseBrowser) ]
 
, ((m, xK_d), raiseBrowser) ]
 
where term :: String
 
where term :: String

Revision as of 21:45, 4 October 2008

import Data.Bits (Bits((.|.)))
import Data.Map as M (fromList, union, Map())
import XMonad
{- XMonad re-exports Graphics.X11, so we can't enumerate imports without also
 enumerating all the keys and such-like. The stuff from XMonad itself is:
    (XConfig(layoutHook, keys, modMask, focusedBorderColor, normalBorderColor,
                                  terminal, XConfig), X()) -}
import XMonad.Actions.Search (google, wayback, wikipedia, selectSearch, promptSearch)
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
import XMonad.Config (defaultConfig)
import XMonad.Config.Gnome (gnomeConfig)
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
import XMonad.Hooks.FadeInactive (fadeInactiveLogHook)
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
import XMonad.Hooks.UrgencyHook (withUrgencyHook, FocusHook(..))
import XMonad.Layout (Full(..), Mirror(..), Tall(..), (|||))
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Main (xmonad)
import XMonad.Operations (kill, windows, withFocused)
import XMonad.Prompt (XPPosition(Top), XPConfig(historySize, height, position, promptBorderWidth, fgColor, bgColor, font), defaultXPConfig)
import XMonad.Prompt.Shell (shellPrompt, prompt, safePrompt)
import XMonad.StackSet as W -- (W.focusUp, W.focusDown, W.sink)
import XMonad.Util.Run (unsafeSpawn, runInTerm)
import XMonad.Util.XSelection (safePromptSelection)

main :: IO ()
main = xmonad myConfig
 where myConfig = withUrgencyHook FocusHook $ gnomeConfig { focusedBorderColor = "red"
                         , keys = \c -> myKeys c `M.union` keys defaultConfig c
                         , layoutHook = avoidStruts $ smartBorders (Full ||| Mirror tiled ||| tiled )
                         , logHook    = ewmhDesktopsLogHook >> fadeInactiveLogHook 0xdddddddd
                         , manageHook = myManageHook
                         , modMask = mod4Mask
                         , normalBorderColor  = "grey"
                         , terminal = "gnome-terminal"
                         , XMonad.workspaces = ["web", "irc", "code", "music", show (5::Int)] }
           where tiled :: Tall a
                 tiled = Tall 1 0.03 0.5

{- Important things to note: We specifically don't use 'managehook
   defaultConfig, since I don't like floating mplayer and I don't use the other
   specified applications. Otherwise, we have manageDocks there to allow use of
   gnome-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
myManageHook :: ManageHook
myManageHook = composeAll [ moveToC "Emacs"     "code",
                            moveToC "Firefox"   "web",
                            moveToC "amarokapp" "music",
                            moveToC "rhythmbox" "music",
                            moveToC "totem"     "music",
                            moveToT "irssi"     "irc",
                            className =? "defcon.bin.x86" --> unfloat ]
               <+> manageDocks
                   where moveToC c w = className =? c --> doF (W.shift w)
                         moveToT t w = title     =? t --> doF (W.shift w)
                         unfloat = ask >>= doF . W.sink

-- Green and black are easier on my eyes.
greenXPConfig :: XPConfig
greenXPConfig = defaultXPConfig {  font        = "9x15bold,xft:Bitstream Vera Sans"
                                 , bgColor     = "black"
                                 , fgColor     = "green"
                                 , promptBorderWidth = 0
                                 , position    = Top
                                 , height      = 16
                                 , historySize = 256 }

myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
myKeys conf@(XConfig {modMask = m}) = M.fromList $ [ -- rebind standard actions
            ((m .|. shiftMask,xK_p), shellPrompt greenXPConfig)
          , ((m,              xK_k), kill)
          , ((m,              xK_n), windows W.focusDown)
          , ((m,              xK_p), windows W.focusUp)
          , ((m,              xK_u), withFocused $ windows . W.sink) -- unfloat
          -- Add custom bindings and commands
          , ((m,              xK_a), runOrRaise "amarok" (className =? "amarokapp"))
          , ((m,              xK_b), safePrompt "firefox" greenXPConfig)
          , ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
          , ((m,              xK_c), unsafeSpawn term)
          , ((m .|. shiftMask,xK_c), prompt (term ++ " -e") greenXPConfig)
          , ((m .|. shiftMask,xK_d), raiseMaybe (runInTerm "--title=elinks" "elinks") (title =? "elinks"))
          , ((m,              xK_e), raiseEditor)
          , ((m .|. shiftMask,xK_e), prompt "emacsclient -a emacs" greenXPConfig)
          , ((m,              xK_g), promptSearch greenXPConfig google)
          , ((m .|. shiftMask,xK_g), selectSearch google)
          , ((m,              xK_t), promptSearch greenXPConfig wikipedia)
          , ((m .|. shiftMask,xK_t), selectSearch wikipedia)
          , ((m,              xK_y), promptSearch greenXPConfig wayback)
          , ((m .|. shiftMask,xK_y), selectSearch wayback)
          , ((m,          xK_Print), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png")
          , ((m,              xK_i), raiseMaybe (runInTerm "--title=irssi" "\"sh -c 'screen -r irssi'\"") (title =? "irssi"))
          -- We ask for zsh specifically so ~/.zshenv gets picked up and my
          -- expanded $PATH gets used; otherwise Mutt can't find needed scripts.
          , ((m,              xK_m), raiseMaybe (runInTerm "--title=mutt"  "\"zsh -c 'mutt'\"") (title =? "mutt"))
          , ((m .|. shiftMask,xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
          , ((m,              xK_r), raiseMaybe (runInTerm "--title='rtorrent'" "\"sh -c 'screen -r rtorrent'\"") (title =? "rtorrent"))
          , ((m,              xK_d), raiseBrowser) ]
           where term :: String
                 term = XMonad.terminal conf