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

From HaskellWiki
Jump to navigation Jump to search
(upload .5 version)
(update for 0.10)
(19 intermediate revisions by the same user not shown)
Line 1: Line 1:
 
<haskell>
 
<haskell>
  +
import Data.Map as M (fromList,union, Map())
import XMonad (XConfig(layoutHook, keys, modMask, focusedBorderColor,
 
  +
import XMonad
normalBorderColor, terminal, defaultGaps, XConfig),
 
  +
import XMonad.Actions.GridSelect (defaultGSConfig, goToSelected)
Layout(..))
 
import XMonad.StackSet as W (W.focusUp, W.focusDown)
+
import XMonad.Actions.Search (google, wayback, wikipedia, wiktionary, selectSearch, promptSearch)
  +
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
import Graphics.X11
 
import XMonad.Config (defaultConfig)
+
import XMonad.Config.Gnome (gnomeConfig)
import XMonad.Core (xmonad)
+
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
import XMonad.Layouts (Full(..), Mirror(..), Tall(..), (|||))
+
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
import XMonad.Operations (kill, windows, sendMessage)
+
import XMonad.Hooks.UrgencyHook (withUrgencyHook, FocusHook(..))
 
import XMonad.Layout.NoBorders (smartBorders)
 
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Layout.Tabbed (tabbed, defaultTConf, shrinkText)
+
import XMonad.Prompt (greenXPConfig)
import XMonad.Layout.WindowNavigation (Navigate(Go), Direction(..))
 
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)
import XMonad.Util.Run (safeSpawn, unsafeSpawn, runInTerm)
+
import XMonad.StackSet as W (focusUp, focusDown, sink)
  +
import XMonad.Util.Run (unsafeSpawn, runInTerm, safeSpawnProg)
 
import XMonad.Util.XSelection (safePromptSelection)
 
import XMonad.Util.XSelection (safePromptSelection)
import Data.Map as M (M.fromList, M.union)
+
import XMonad.Prompt.AppendFile
import Data.Bits (Bits((.|.)))
 
   
 
main :: IO ()
 
main :: IO ()
  +
main = spawn "killall unclutter;unclutter;" >> spawn "killall urxvtd;urxvtd -q -f -o" >> xmonad myConfig
main = xmonad $ gwernConfig
 
  +
where myConfig = withUrgencyHook FocusHook $ gnomeConfig { focusedBorderColor = "red"
 
, keys = \c -> myKeys c `M.union` keys defaultConfig c
  +
, layoutHook = avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
 
, logHook = ewmhDesktopsLogHook
 
, manageHook = myManageHook
 
, modMask = mod4Mask
 
, normalBorderColor = "grey"
 
, terminal = "urxvtc"
  +
, XMonad.workspaces = ["web", "irc", "code", "4"] }
 
where tiled = Tall 1 0.03 0.5
   
  +
{- Important things to note: We specifically don't use 'managehook
gwernConfig :: XConfig
 
  +
defaultConfig, since I don't like floating mplayer and I don't use the other
gwernConfig = defaultConfig
 
  +
specified applications. Otherwise, we have manageDocks there to allow use of
{ defaultGaps = [(0,0,0,0)]
 
  +
gnome-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
, terminal = "urxvtc"
 
  +
myManageHook :: ManageHook
, normalBorderColor = "#dddddd"
 
  +
myManageHook = composeAll [moveT "Amphetype" "code",
, focusedBorderColor = "#ff0000"
 
  +
moveT "Brain Workshop 4.8.1" "code",
, modMask = mod4Mask
 
  +
moveC "Emacs" "code",
, keys = \c -> mykeys c `M.union` keys defaultConfig c
 
  +
moveC "Iceweasel" "web",
, layoutHook = Layout (smartBorders (tiled ||| Mirror tiled ||| Full ||| tabbed shrinkText defaultTConf)) }
 
  +
moveC "Gimp" "irc",
where
 
  +
moveC "gscan2pdf" "code",
tiled = Tall 1 0.03 0.5
 
  +
moveC "Mnemosyne" "code",
  +
moveT "irssi" "irc",
  +
className =? "defcon.bin.x86" --> unfloat,
  +
className =? "Darwinia" --> unfloat,
  +
className =? "gnome-panel" --> doIgnore,
  +
className =? "Mnemosyne" --> unfloat,
  +
title =? "Brain Workshop 4.8.1" --> unfloat]
 
<+> manageDocks
  +
where moveC c w = className =? c --> doShift w
  +
moveT t w = title =? t --> doShift w
  +
unfloat = ask >>= doF . W.sink
   
  +
myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
greenXPConfig :: XPConfig
 
 
myKeys (XConfig {modMask = m, terminal = term}) = M.fromList [ -- rebind standard keys
greenXPConfig = defaultXPConfig { font = "9x15bold,xft:Bitstream Vera Sans Mono"
 
, bgColor = "black"
+
((m .|. shiftMask,xK_p), shellPrompt greenXPConfig)
, fgColor = "green"
+
, ((m, xK_k), kill)
, promptBorderWidth = 0
+
, ((m, xK_n), windows W.focusDown)
, position = Top
+
, ((m, xK_p), windows W.focusUp)
, height = 16
+
, ((m, xK_z), withFocused $ windows . W.sink) -- unfloat
  +
-- Custom bindings and commands
, historySize = 256 }
 
  +
, ((m, xK_s), goToSelected defaultGSConfig)
 
  +
, ((m ,xK_a), safeSpawnProg "/home/gwern/bin/bin/amphetype")
mykeys (XConfig {modMask = modm}) = M.fromList $
 
[ ((modm .|. shiftMask, xK_p ), shellPrompt greenXPConfig)
+
, ((m, xK_b), safePrompt "firefox" greenXPConfig)
  +
, ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
, ((modm, xK_k ), kill ) -- %! Move focus to the previous WindowSet
 
, ((modm, xK_n ), windows W.focusUp)
+
, ((m, xK_c), safeSpawnProg term)
  +
, ((m .|. shiftMask,xK_c), prompt (term ++ " -e") greenXPConfig)
, ((modm, xK_p ), windows W.focusDown)
 
  +
, ((m .|. shiftMask,xK_d), raiseMaybe (runInTerm "-title elinks" "elinks") (title =? "elinks"))
 
, ((modm .|. shiftMask, xK_b ), safePromptSelection "firefox")
+
, ((m, xK_e), raiseEditor)
, ((modm .|. shiftMask, xK_c ), prompt ((terminal gwernConfig) ++ " -e") greenXPConfig)
+
, ((m .|. shiftMask,xK_e), prompt "emacs" greenXPConfig)
, ((modm .|. shiftMask, xK_d ), runInTerm "elinks")
+
, ((m, xK_g), promptSearch greenXPConfig google)
, ((modm .|. shiftMask, xK_e ), prompt "emacsclient -a emacs" greenXPConfig)
+
, ((m .|. shiftMask,xK_g), selectSearch google)
, ((modm .|. shiftMask, xK_g ), safePromptSelection "google")
+
, ((m, xK_t), promptSearch greenXPConfig wikipedia)
, ((modm .|. shiftMask, xK_t ), safePromptSelection "wikipedia")
+
, ((m .|. shiftMask,xK_t), selectSearch wikipedia)
, ((modm .|. shiftMask, xK_y ), safePromptSelection "wayback")
+
, ((m, xK_y), promptSearch greenXPConfig wayback)
  +
, ((m .|. shiftMask,xK_y), selectSearch wayback)
, ((modm, xK_Print ), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png")
 
  +
, ((m .|. shiftMask,xK_w), selectSearch wiktionary)
, ((modm, xK_b ), safePrompt "firefox" greenXPConfig)
 
, ((modm, xK_c ), unsafeSpawn (terminal gwernConfig))
+
, ((m, xK_w), safeSpawnProg "/home/gwern/bin/bin/brainworkshop")
, ((modm, xK_d ), safeSpawn "firefox" "")
+
, ((m, xK_Print), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png")
, ((modm, xK_e ), unsafeSpawn "emacs")
+
, ((m, xK_i), raiseMaybe (runInTerm "-title irssi" "sh -c 'screen -r irssi'") (title =? "irssi"))
  +
, ((m .|. shiftMask,xK_i), spawn "xclip -o|tr '\n' ' '|sed -e 's/- //' > ~/z.txt && screen -S irssi -X readbuf ~/z.txt && screen -S irssi -X paste .;rm ~/z.txt")
, ((modm, xK_g ), safePrompt "google" greenXPConfig)
 
, ((modm, xK_t ), safePrompt "wikipedia" greenXPConfig)
+
, ((m, xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
, ((modm, xK_y ), safePrompt "wayback" greenXPConfig)
+
, ((m, xK_r), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
, ((modm, xK_i ), runInTerm "sh -c 'screen -r irssi'")
+
, ((m, xK_d), raiseBrowser)
, ((modm, xK_m ), runInTerm "sh -c 'mutt'")
+
, ((m, xK_x), spawn ("date>>"++lg) >> appendFilePrompt greenXPConfig lg)]
  +
where lg = "/home/gwern/doc/archive/wiki/log.txt"
, ((modm, xK_r ), runInTerm "sh -c 'screen -r rtorrent'")
 
 
-- Extension-provided key bindings
 
, ((modm, xK_Right), sendMessage $ Go R)
 
, ((modm, xK_Left), sendMessage $ Go L)
 
, ((modm, xK_Up), sendMessage $ Go U)
 
, ((modm, xK_Down), sendMessage $ Go D)
 
]
 
 
</haskell>
 
</haskell>
[[Category: XMonad configuration]]
 

Revision as of 13:16, 4 December 2011

import Data.Map as M (fromList,union, Map())
import XMonad
import XMonad.Actions.GridSelect (defaultGSConfig, goToSelected)
import XMonad.Actions.Search (google, wayback, wikipedia, wiktionary, selectSearch, promptSearch)
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
import XMonad.Config.Gnome (gnomeConfig)
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
import XMonad.Hooks.UrgencyHook (withUrgencyHook, FocusHook(..))
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Prompt (greenXPConfig)
import XMonad.Prompt.Shell (shellPrompt, prompt, safePrompt)
import XMonad.StackSet as W (focusUp, focusDown, sink)
import XMonad.Util.Run (unsafeSpawn, runInTerm, safeSpawnProg)
import XMonad.Util.XSelection (safePromptSelection)
import XMonad.Prompt.AppendFile

main :: IO ()
main = spawn "killall unclutter;unclutter;" >> spawn "killall urxvtd;urxvtd -q -f -o" >> xmonad myConfig
 where myConfig = withUrgencyHook FocusHook $ gnomeConfig { focusedBorderColor = "red"
                         , keys = \c -> myKeys c `M.union` keys defaultConfig c
                         , layoutHook =  avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
                         , logHook    = ewmhDesktopsLogHook
                         , manageHook = myManageHook
                         , modMask = mod4Mask
                         , normalBorderColor  = "grey"
                         , terminal = "urxvtc"
                         , XMonad.workspaces = ["web", "irc", "code", "4"] }
           where 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 [moveT "Amphetype" "code",
                           moveT "Brain Workshop 4.8.1" "code",
                           moveC "Emacs"     "code",
                           moveC "Iceweasel" "web",
                           moveC "Gimp"      "irc",
                           moveC "gscan2pdf" "code",
                           moveC "Mnemosyne" "code",
                           moveT "irssi"     "irc",
                           className =? "defcon.bin.x86" --> unfloat,
                           className =? "Darwinia" --> unfloat,
                           className =? "gnome-panel" --> doIgnore,
                           className =? "Mnemosyne" --> unfloat,
                           title     =? "Brain Workshop 4.8.1" --> unfloat]
                           <+> manageDocks
          where moveC c w = className =? c --> doShift w
                moveT t w = title     =? t --> doShift w
                unfloat = ask >>= doF . W.sink

myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
myKeys (XConfig {modMask = m, terminal = term}) = M.fromList [ -- rebind standard keys
            ((m .|. shiftMask,xK_p), shellPrompt greenXPConfig)
          , ((m,              xK_k), kill)
          , ((m,              xK_n), windows W.focusDown)
          , ((m,              xK_p), windows W.focusUp)
          , ((m,              xK_z), withFocused $ windows . W.sink) -- unfloat
          -- Custom bindings and commands
          , ((m,              xK_s), goToSelected defaultGSConfig)
          , ((m               ,xK_a), safeSpawnProg "/home/gwern/bin/bin/amphetype")
          , ((m,              xK_b), safePrompt "firefox" greenXPConfig)
          , ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
          , ((m,              xK_c), safeSpawnProg 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 "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 .|. shiftMask,xK_w), selectSearch wiktionary)
          , ((m,              xK_w), safeSpawnProg "/home/gwern/bin/bin/brainworkshop")
          , ((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 .|. shiftMask,xK_i), spawn "xclip -o|tr '\n' ' '|sed -e 's/- //' > ~/z.txt && screen -S irssi -X readbuf ~/z.txt && screen -S irssi -X paste .;rm ~/z.txt")
          , ((m,              xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
          , ((m,              xK_r), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
          , ((m,              xK_d), raiseBrowser)
          , ((m,              xK_x), spawn ("date>>"++lg) >> appendFilePrompt greenXPConfig lg)]
  where lg = "/home/gwern/doc/archive/wiki/log.txt"