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

From HaskellWiki
Jump to navigation Jump to search
(gnome-panel autohide!)
(update)
(6 intermediate revisions by the same user not shown)
Line 1: Line 1:
 
<haskell>
 
<haskell>
import Data.Bits (Bits((.|.)))
+
import Data.Map as M (fromList,union, Map())
import Data.Map as M (fromList, union, Map())
 
 
import XMonad
 
import XMonad
 
import XMonad.Actions.GridSelect (defaultGSConfig, goToSelected)
 
import XMonad.Actions.GridSelect (defaultGSConfig, goToSelected)
import XMonad.Actions.Search (google, isohunt, wayback, wikipedia, selectSearch, promptSearch)
+
import XMonad.Actions.Search (google, scholar, wikipedia, wiktionary, selectSearch, promptSearch)
 
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
 
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
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(..))
import XMonad.Layout (Full(..), Mirror(..), Tall(..), (|||))
 
import XMonad.Layout.Monitor (addMonitor, Property(ClassName))
 
 
import XMonad.Layout.NoBorders (smartBorders)
 
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Main (xmonad)
 
import XMonad.Operations (kill, windows, withFocused)
 
 
import XMonad.Prompt (greenXPConfig)
 
import XMonad.Prompt (greenXPConfig)
 
import XMonad.Prompt.Shell (shellPrompt, prompt, safePrompt)
 
import XMonad.Prompt.Shell (shellPrompt, prompt, safePrompt)
import XMonad.StackSet as W (focusUp, focusDown, shift, sink)
+
import XMonad.StackSet as W (focusUp, focusDown, sink)
import XMonad.Util.Run (unsafeSpawn, runInTerm)
+
import XMonad.Util.Run (unsafeSpawn, runInTerm, safeSpawnProg)
 
import XMonad.Util.XSelection (safePromptSelection)
 
import XMonad.Util.XSelection (safePromptSelection)
 
import XMonad.Prompt.AppendFile
   
 
main :: IO ()
 
main :: IO ()
main = spawn "xcompmgr" >> xmonad myConfig
+
main = spawn "killall unclutter;unclutter;" >> spawn "killall urxvtd;urxvtd -q -f -o" >> xmonad myConfig
 
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 = hideGnome $ avoidStruts $ smartBorders $ (Full ||| Mirror tiled ||| tiled )
+
, layoutHook = avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
, logHook = ewmhDesktopsLogHook >> fadeInactiveLogHook 0xdddddddd
+
, logHook = ewmhDesktopsLogHook
 
, manageHook = myManageHook
 
, manageHook = myManageHook
 
, modMask = mod4Mask
 
, modMask = mod4Mask
 
, normalBorderColor = "grey"
 
, normalBorderColor = "grey"
, terminal = "gnome-terminal"
+
, terminal = "urxvtc"
, XMonad.workspaces = ["web", "irc", "code", "5"] }
+
, XMonad.workspaces = ["web", "irc", "code", "4"] }
where tiled :: Tall a
+
where tiled = Tall 1 0.03 0.5
tiled = Tall 1 0.03 0.5
 
hideGnome = addMonitor (ClassName "gnome-panel") (Rectangle 0 0 0 0)
 
   
 
{- Important things to note: We specifically don't use 'managehook
 
{- Important things to note: We specifically don't use 'managehook
Line 43: Line 35:
 
gnome-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
 
gnome-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
 
myManageHook :: ManageHook
 
myManageHook :: ManageHook
myManageHook = composeAll [ moveToC "Emacs" "code",
+
myManageHook = composeAll [moveT "Amphetype" "code",
moveToC "Firefox" "web",
+
moveT "Brain Workshop 4.8.1" "code",
moveToT "irssi" "irc",
+
moveC "Emacs" "code",
className =? "defcon.bin.x86" --> unfloat,
+
moveC "Iceweasel" "web",
className =? "Darwinia" --> unfloat,
+
moveC "Gimp" "irc",
className =? "gnome-panel" --> doIgnore ]
+
moveC "gscan2pdf" "code",
<+> manageDocks
+
moveC "Mnemosyne" "code",
where moveToC c w = className =? c --> doF (W.shift w)
+
moveT "irssi" "irc",
moveToT t w = title =? t --> doF (W.shift w)
+
className =? "defcon.bin.x86" --> unfloat,
unfloat = ask >>= doF . W.sink
+
className =? "Darwinia" --> unfloat,
  +
className =? "gnome-panel" --> doIgnore,
  +
className =? "Mnemosyne" --> unfloat,
  +
title =? "Brain Workshop 4.8.6" --> 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 t -> M.Map (KeyMask, KeySym) (X ())
myKeys conf@(XConfig {modMask = m}) = M.fromList [ -- rebind standard keys
+
myKeys (XConfig {modMask = m, terminal = term}) = M.fromList [ -- rebind standard keys
 
((m .|. shiftMask,xK_p), shellPrompt greenXPConfig)
 
((m .|. shiftMask,xK_p), shellPrompt greenXPConfig)
 
, ((m, xK_k), kill)
 
, ((m, xK_k), kill)
Line 63: Line 62:
 
-- Custom bindings and commands
 
-- Custom bindings and commands
 
, ((m, xK_s), goToSelected defaultGSConfig)
 
, ((m, xK_s), goToSelected defaultGSConfig)
, ((m, xK_a), runOrRaise "amarok" (className =? "amarokapp"))
+
, ((m ,xK_a), safeSpawnProg "/home/gwern/bin/bin/amphetype")
 
, ((m, xK_b), safePrompt "firefox" greenXPConfig)
 
, ((m, xK_b), safePrompt "firefox" greenXPConfig)
 
, ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
 
, ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
, ((m, xK_c), unsafeSpawn term)
+
, ((m, xK_c), safeSpawnProg 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 "emacs" greenXPConfig)
 
, ((m, xK_g), promptSearch greenXPConfig google)
 
, ((m, xK_g), promptSearch greenXPConfig google)
 
, ((m .|. shiftMask,xK_g), selectSearch google)
 
, ((m .|. shiftMask,xK_g), selectSearch google)
 
, ((m, xK_t), promptSearch greenXPConfig wikipedia)
 
, ((m, xK_t), promptSearch greenXPConfig wikipedia)
 
, ((m .|. shiftMask,xK_t), selectSearch wikipedia)
 
, ((m .|. shiftMask,xK_t), selectSearch wikipedia)
, ((m, xK_u), promptSearch greenXPConfig isohunt)
+
, ((m, xK_y), promptSearch greenXPConfig scholar)
, ((m .|. shiftMask,xK_u), selectSearch isohunt)
+
, ((m .|. shiftMask,xK_y), selectSearch scholar)
, ((m, xK_y), promptSearch greenXPConfig wayback)
+
, ((m .|. shiftMask,xK_w), selectSearch wiktionary)
, ((m .|. shiftMask,xK_y), selectSearch wayback)
+
, ((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_Print), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png; nice optipng ~/*.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"))
  +
, ((m .|. shiftMask,xK_i), spawn "xclip -o|tr '\n' ' '|sed -e 's/- //' -e 's/^ *//' -e 's/ *$//' > /tmp/z.txt && screen -S irssi -X readbuf /tmp/z.txt && screen -S irssi -X paste .;rm /tmp/z.txt")
-- We ask for zsh specifically so ~/.zshenv gets picked up and my
 
  +
, ((m, xK_m), runOrRaise "/home/gwern/bin/bin/mnemosyne" (className =? "Mnemosyne"))
-- 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_r), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
, ((m .|. shiftMask,xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
+
, ((m, xK_d), raiseBrowser)
, ((m, xK_r), raiseMaybe (runInTerm "--title='rtorrent'" "\"sh -c 'screen -r rtorrent'\"") (title =? "rtorrent"))
+
, ((m, xK_x), spawn ("date>>"++lg) >> appendFilePrompt greenXPConfig lg)]
  +
where lg = "/home/gwern/doc/2013/log.txt"
, ((m, xK_d), raiseBrowser) ]
 
where term :: String
 
term = XMonad.terminal conf
 
 
</haskell>
 
</haskell>

Revision as of 21:39, 10 September 2013

import Data.Map as M (fromList,union, Map())
import XMonad
import XMonad.Actions.GridSelect (defaultGSConfig, goToSelected)
import XMonad.Actions.Search (google, scholar, 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.6" --> 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 scholar)
          , ((m .|. shiftMask,xK_y), selectSearch scholar)
          , ((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; nice optipng ~/*.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/- //' -e 's/^ *//' -e 's/ *$//' > /tmp/z.txt && screen -S irssi -X readbuf /tmp/z.txt && screen -S irssi -X paste .;rm /tmp/z.txt")
          , ((m,              xK_m), runOrRaise "/home/gwern/bin/bin/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/2013/log.txt"