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

From HaskellWiki
Jump to navigation Jump to search
(upload .5 version)
(update for Gnome->Mate shift)
(22 intermediate revisions by the same user not shown)
Line 1: Line 1:
 
<haskell>
 
<haskell>
  +
import Data.List (isInfixOf)
import XMonad (XConfig(layoutHook, keys, modMask, focusedBorderColor,
 
  +
import Data.Map as M (fromList,union, Map())
normalBorderColor, terminal, defaultGaps, XConfig),
 
  +
import XMonad
Layout(..))
 
import XMonad.StackSet as W (W.focusUp, W.focusDown)
+
import XMonad.Actions.Search (google, scholar, wikipedia, selectSearch, promptSearch)
  +
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
import Graphics.X11
 
import XMonad.Config (defaultConfig)
+
import XMonad.Config.Mate (mateConfig)
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 Data.Bits (Bits((.|.)))
 
   
 
main :: IO ()
 
main :: IO ()
  +
main = spawn "mate-screensaver" >> spawn "killall unclutter;unclutter" >> xmonad myConfig
main = xmonad $ gwernConfig
 
  +
where myConfig = withUrgencyHook FocusHook $ mateConfig { focusedBorderColor = "red"
  +
, keys = \c -> myKeys c `M.union` keys def c
  +
, layoutHook = avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
  +
, logHook = ewmhDesktopsLogHook
  +
, manageHook = myManageHook
  +
, modMask = mod4Mask
  +
, normalBorderColor = "grey"
  +
, terminal = "urxvt"
  +
, XMonad.workspaces = ["web", "irc", "code", "background"] }
  +
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)]
 
  +
mate-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
, terminal = "urxvtc"
 
  +
myManageHook :: ManageHook
, normalBorderColor = "#dddddd"
 
  +
myManageHook = composeAll [ moveC "Iceweasel" "web",
, focusedBorderColor = "#ff0000"
 
  +
moveC "Gimp" "irc",
, modMask = mod4Mask
 
  +
moveC "Emacs" "code",
, keys = \c -> mykeys c `M.union` keys defaultConfig c
 
  +
moveC "Mnemosyne" "code",
, layoutHook = Layout (smartBorders (tiled ||| Mirror tiled ||| Full ||| tabbed shrinkText defaultTConf)) }
 
  +
moveC "Liferea" "code",
where
 
tiled = Tall 1 0.03 0.5
 
   
  +
className =? "mate-panel" --> doIgnore,
greenXPConfig :: XPConfig
 
  +
className =? "defcon.bin.x86" --> unfloat,
greenXPConfig = defaultXPConfig { font = "9x15bold,xft:Bitstream Vera Sans Mono"
 
, bgColor = "black"
+
className =? "Mnemosyne" --> unfloat,
, fgColor = "green"
+
title =? "Brain Workshop 4.8.6" --> unfloat,
, promptBorderWidth = 0
 
, position = Top
 
, height = 16
 
, historySize = 256 }
 
   
  +
title ~? "Irssi" --> doShift "irc"]
mykeys (XConfig {modMask = modm}) = M.fromList $
 
[ ((modm .|. shiftMask, xK_p ), shellPrompt greenXPConfig)
+
<+> manageDocks
  +
where moveC c w = className =? c --> doShift w
, ((modm, xK_k ), kill ) -- %! Move focus to the previous WindowSet
 
, ((modm, xK_n ), windows W.focusUp)
+
-- moveT t w = title =? t --> doShift w
, ((modm, xK_p ), windows W.focusDown)
+
unfloat = ask >>= doF . W.sink
   
  +
-- helper function for doing a simple string match on window titles
, ((modm .|. shiftMask, xK_b ), safePromptSelection "firefox")
 
  +
(~?) :: (Eq a, Functor f) => f [a] -> [a] -> f Bool
, ((modm .|. shiftMask, xK_c ), prompt ((terminal gwernConfig) ++ " -e") greenXPConfig)
 
  +
q ~? x = fmap (x `isInfixOf`) q
, ((modm .|. shiftMask, xK_d ), runInTerm "elinks")
 
, ((modm .|. shiftMask, xK_e ), prompt "emacsclient -a emacs" greenXPConfig)
 
, ((modm .|. shiftMask, xK_g ), safePromptSelection "google")
 
, ((modm .|. shiftMask, xK_t ), safePromptSelection "wikipedia")
 
, ((modm .|. shiftMask, xK_y ), safePromptSelection "wayback")
 
, ((modm, xK_Print ), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png")
 
, ((modm, xK_b ), safePrompt "firefox" greenXPConfig)
 
, ((modm, xK_c ), unsafeSpawn (terminal gwernConfig))
 
, ((modm, xK_d ), safeSpawn "firefox" "")
 
, ((modm, xK_e ), unsafeSpawn "emacs")
 
, ((modm, xK_g ), safePrompt "google" greenXPConfig)
 
, ((modm, xK_t ), safePrompt "wikipedia" greenXPConfig)
 
, ((modm, xK_y ), safePrompt "wayback" greenXPConfig)
 
, ((modm, xK_i ), runInTerm "sh -c 'screen -r irssi'")
 
, ((modm, xK_m ), runInTerm "sh -c 'mutt'")
 
, ((modm, xK_r ), runInTerm "sh -c 'screen -r rtorrent'")
 
   
  +
myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
-- Extension-provided key bindings
 
  +
myKeys (XConfig {modMask = m, terminal = term}) = M.fromList [ -- rebind standard keys
, ((modm, xK_Right), sendMessage $ Go R)
 
, ((modm, xK_Left), sendMessage $ Go L)
+
((m .|. shiftMask,xK_p), shellPrompt greenXPConfig)
, ((modm, xK_Up), sendMessage $ Go U)
+
, ((m, xK_k), kill)
, ((modm, xK_Down), sendMessage $ Go D)
+
, ((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_b), safePrompt "firefox" greenXPConfig)
  +
, ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
  +
, ((m, xK_c), safeSpawnProg term)
  +
, ((m .|. shiftMask,xK_c), prompt (term ++ " -e") greenXPConfig)
  +
, ((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, xK_w), safeSpawnProg "/home/gwern/bin/bin/brainworkshop")
  +
, ((m, xK_Print), unsafeSpawn "import -quality 90 -descend 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/ *$//' -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 "mnemosyne" (className =? "Mnemosyne"))
  +
, ((m, xK_r), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
  +
, ((m, xK_d), raiseBrowser)
  +
, ((m, xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/2015/log.txt")
  +
, ((m .|. shiftMask,xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/2015/log-media.txt")]
 
</haskell>
 
</haskell>
[[Category: XMonad configuration]]
 

Revision as of 14:40, 11 July 2015

import Data.List (isInfixOf)
import Data.Map as M (fromList,union, Map())
import XMonad
import XMonad.Actions.Search (google, scholar, wikipedia, selectSearch, promptSearch)
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
import XMonad.Config.Mate (mateConfig)
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)

main :: IO ()
main = spawn "mate-screensaver" >> spawn "killall unclutter;unclutter" >> xmonad myConfig
 where myConfig = withUrgencyHook FocusHook $ mateConfig { focusedBorderColor = "red"
                         , keys = \c -> myKeys c `M.union` keys def c
                         , layoutHook =  avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
                         , logHook    = ewmhDesktopsLogHook
                         , manageHook = myManageHook
                         , modMask = mod4Mask
                         , normalBorderColor  = "grey"
                         , terminal = "urxvt"
                         , XMonad.workspaces = ["web", "irc", "code", "background"] }
           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
   mate-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
myManageHook :: ManageHook
myManageHook = composeAll [ moveC "Iceweasel" "web",
                            moveC "Gimp"      "irc",
                            moveC "Emacs"     "code",
                            moveC "Mnemosyne" "code",
                            moveC "Liferea"   "code",

                            className =? "mate-panel"          --> doIgnore,
                            className =? "defcon.bin.x86"       --> unfloat,
                            className =? "Mnemosyne"            --> unfloat,
                            title     =? "Brain Workshop 4.8.6" --> unfloat,

                            title     ~? "Irssi" --> doShift "irc"]
                           <+> manageDocks
          where moveC c w = className =? c --> doShift w
                -- moveT t w = title     =? t --> doShift w
                unfloat = ask >>= doF . W.sink

-- helper function for doing a simple string match on window titles
(~?) :: (Eq a, Functor f) => f [a] -> [a] -> f Bool
q ~? x  = fmap (x `isInfixOf`) q

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_b), safePrompt "firefox" greenXPConfig)
          , ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
          , ((m,              xK_c), safeSpawnProg term)
          , ((m .|. shiftMask,xK_c), prompt (term ++ " -e") greenXPConfig)
          , ((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,              xK_w), safeSpawnProg "/home/gwern/bin/bin/brainworkshop")
          , ((m,          xK_Print), unsafeSpawn "import -quality 90 -descend 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/ *$//' -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 "mnemosyne" (className =? "Mnemosyne"))
          , ((m,              xK_r), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
          , ((m,              xK_d), raiseBrowser)
          , ((m,              xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/2015/log.txt")
          , ((m .|. shiftMask,xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/2015/log-media.txt")]