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

From HaskellWiki
Jump to navigation Jump to search
(update for 2014)
(update for Gnome->Mate shift)
Line 1: Line 1:
 
<haskell>
 
<haskell>
  +
import Data.List (isInfixOf)
 
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.Search (google, scholar, wikipedia, selectSearch, promptSearch)
 
import XMonad.Actions.Search (google, scholar, wikipedia, selectSearch, promptSearch)
 
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
 
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
import XMonad.Config.Gnome (gnomeConfig)
+
import XMonad.Config.Mate (mateConfig)
 
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
 
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
 
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
 
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
Line 15: Line 15:
 
import XMonad.Util.Run (unsafeSpawn, runInTerm, safeSpawnProg)
 
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 "killall unclutter;unclutter;" >> spawn "killall urxvtd;urxvtd -q -f -o" >> xmonad myConfig
+
main = spawn "mate-screensaver" >> spawn "killall unclutter;unclutter" >> xmonad myConfig
where myConfig = withUrgencyHook FocusHook $ gnomeConfig { focusedBorderColor = "red"
+
where myConfig = withUrgencyHook FocusHook $ mateConfig { focusedBorderColor = "red"
, keys = \c -> myKeys c `M.union` keys defaultConfig c
+
, keys = \c -> myKeys c `M.union` keys def c
 
, layoutHook = avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
 
, layoutHook = avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
 
, logHook = ewmhDesktopsLogHook
 
, logHook = ewmhDesktopsLogHook
Line 26: Line 25:
 
, modMask = mod4Mask
 
, modMask = mod4Mask
 
, normalBorderColor = "grey"
 
, normalBorderColor = "grey"
, terminal = "urxvtc"
+
, terminal = "urxvt"
 
, XMonad.workspaces = ["web", "irc", "code", "background"] }
 
, XMonad.workspaces = ["web", "irc", "code", "background"] }
 
where tiled = Tall 1 0.03 0.5
 
where tiled = Tall 1 0.03 0.5
Line 33: Line 32:
 
defaultConfig, since I don't like floating mplayer and I don't use the other
 
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
 
specified applications. Otherwise, we have manageDocks there to allow use of
gnome-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
+
mate-panel; Firefox/Emacs/Irssi go to their designated workspaces. -}
 
myManageHook :: ManageHook
 
myManageHook :: ManageHook
myManageHook = composeAll [moveC "Emacs" "code",
+
myManageHook = composeAll [ moveC "Iceweasel" "web",
moveC "Iceweasel" "web",
+
moveC "Gimp" "irc",
moveC "Gimp" "irc",
+
moveC "Emacs" "code",
moveC "Mnemosyne" "code",
+
moveC "Mnemosyne" "code",
moveT "irssi" "irc",
+
moveC "Liferea" "code",
  +
className =? "defcon.bin.x86" --> unfloat,
 
className =? "gnome-panel" --> doIgnore,
+
className =? "mate-panel" --> doIgnore,
className =? "Mnemosyne" --> unfloat,
+
className =? "defcon.bin.x86" --> unfloat,
title =? "Brain Workshop 4.8.6" --> unfloat]
+
className =? "Mnemosyne" --> unfloat,
 
title =? "Brain Workshop 4.8.6" --> unfloat,
  +
  +
title ~? "Irssi" --> doShift "irc"]
 
<+> manageDocks
 
<+> manageDocks
 
where moveC c w = className =? c --> doShift w
 
where moveC c w = className =? c --> doShift w
moveT t w = title =? t --> doShift w
+
-- moveT t w = title =? t --> doShift w
 
unfloat = ask >>= doF . W.sink
 
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 t -> M.Map (KeyMask, KeySym) (X ())
Line 57: Line 63:
 
, ((m, xK_z), withFocused $ windows . W.sink) -- unfloat
 
, ((m, xK_z), withFocused $ windows . W.sink) -- unfloat
 
-- Custom bindings and commands
 
-- Custom bindings and commands
, ((m, xK_s), goToSelected defaultGSConfig)
 
 
, ((m, xK_b), safePrompt "firefox" greenXPConfig)
 
, ((m, xK_b), safePrompt "firefox" greenXPConfig)
 
, ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
 
, ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
Line 71: Line 76:
 
, ((m .|. shiftMask,xK_y), selectSearch scholar)
 
, ((m .|. shiftMask,xK_y), selectSearch scholar)
 
, ((m, xK_w), safeSpawnProg "/home/gwern/bin/bin/brainworkshop")
 
, ((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_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, 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 .|. 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 "/home/gwern/bin/bin/mnemosyne" (className =? "Mnemosyne"))
+
, ((m, 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)
, ((m, xK_x), spawn ("date>>"++lg) >> appendFilePrompt greenXPConfig lg)]
+
, ((m, xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/2015/log.txt")
where lg = "/home/gwern/doc/2014/log.txt"
+
, ((m .|. shiftMask,xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/2015/log-media.txt")]
 
</haskell>
 
</haskell>

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")]