Xmonad/Config archive/Gwern's xmonad.hs

From HaskellWiki
< Xmonad‎ | Config archive
Revision as of 22:05, 1 June 2008 by Gwern (talk | contribs) (update for use with gnome)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module Main where

import Data.Bits (Bits((.|.)))
import Data.Map as M (M.fromList, M.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.Config (defaultConfig)
import XMonad.Layout (Full(..), Mirror(..), Tall(..), (|||))
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Main (xmonad)
import XMonad.Operations (kill, windows)
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)
import XMonad.Actions.WindowGo (title, raiseMaybe, (=?), raiseBrowser, raiseEditor, runOrRaise)
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
import XMonad.Config.Gnome

main :: IO ()
main = xmonad myConfig

-- Begin customizations
myConfig = gnomeConfig { focusedBorderColor = "red"
                         , keys = \c -> myKeys c `M.union` keys defaultConfig c
                         , layoutHook = avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
                         , logHook    = ewmhDesktopsLogHook
                         , manageHook = manageDocks <+> manageHook defaultConfig
                         , modMask = mod4Mask
                         , normalBorderColor  = "grey"
                         , terminal = "urxvt"
                       }
                         where tiled :: Tall a
                               tiled = Tall 1 0.03 0.5

greenXPConfig :: XPConfig
greenXPConfig = defaultXPConfig {  font        = "9x15bold,xft:DejaVu Vera Sans Mono"
                                 , bgColor     = "black"
                                 , fgColor     = "green"
                                 , promptBorderWidth = 0
                                 , position    = Top
                                 , height      = 16
                                 , historySize = 256 }

myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
myKeys (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_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 = "urxvt"