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

From HaskellWiki
Jump to navigation Jump to search
(update for managehooks)
(update for Gnome->Mate shift)
(15 intermediate revisions by the same user not shown)
Line 1: Line 1:
 
<haskell>
 
<haskell>
 
import Data.List (isInfixOf)
module Main where
 
 
import Data.Map as M (fromList,union, Map())
 
import Data.Bits (Bits((.|.)))
 
import Data.Map as M (M.fromList, M.union, Map())
 
 
import XMonad
 
import XMonad
 
import XMonad.Actions.Search (google, scholar, wikipedia, selectSearch, promptSearch)
{- XMonad re-exports Graphics.X11, so we can't enumerate imports without also
 
 
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
enumerating all the keys and such-like. The stuff from XMonad itself is:
 
 
import XMonad.Config.Mate (mateConfig)
(XConfig(layoutHook, keys, modMask, focusedBorderColor, normalBorderColor,
 
terminal, XConfig), X()) -}
 
import XMonad.Actions.Search (google, wayback, wikipedia, selectSearch, promptSearch)
 
import XMonad.Actions.WindowGo (title, raiseMaybe, raiseBrowser, raiseEditor, runOrRaise, (=?))
 
import XMonad.Config (defaultConfig)
 
import XMonad.Config.Gnome (gnomeConfig)
 
 
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
 
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
 
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.NoBorders (smartBorders)
 
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Main (xmonad)
+
import XMonad.Prompt (greenXPConfig)
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.Prompt.Shell (shellPrompt, prompt, safePrompt)
import XMonad.StackSet as W -- (W.focusUp, W.focusDown, W.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)
   
 
main :: IO ()
 
main :: IO ()
main = 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
 
, manageHook = myManageHook
 
, manageHook = myManageHook
Line 36: Line 26:
 
, normalBorderColor = "grey"
 
, normalBorderColor = "grey"
 
, terminal = "urxvt"
 
, terminal = "urxvt"
, XMonad.workspaces = ["web", "irc", "code", "music", show (5::Int)]
+
, XMonad.workspaces = ["web", "irc", "code", "background"] }
}
+
where tiled = Tall 1 0.03 0.5
where tiled :: Tall a
 
tiled = Tall 1 0.03 0.5
 
   
 
{- Important things to note: We specifically don't use 'managehook
 
{- 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
 
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. -}
-- TODO: suggest that these functions be moved into XMonad proper; lots of
 
-- redundancy there...
 
 
myManageHook :: ManageHook
 
myManageHook :: ManageHook
myManageHook = composeAll [ moveToC "Emacs" "code",
+
myManageHook = composeAll [ moveC "Iceweasel" "web",
moveToC "Firefox" "web",
+
moveC "Gimp" "irc",
moveToC "MPlayer" "music",
+
moveC "Emacs" "code",
moveToC "amarokapp" "music",
+
moveC "Mnemosyne" "code",
moveToC "rhythmbox" "music",
+
moveC "Liferea" "code",
  +
moveToC "totem" "music",
 
moveToT "irssi" "irc" ]
+
className =? "mate-panel" --> doIgnore,
<+> manageDocks
+
className =? "defcon.bin.x86" --> unfloat,
where moveToC c w = className =? c --> doF (W.shift w)
+
className =? "Mnemosyne" --> unfloat,
moveToT t w = title =? t --> doF (W.shift w)
+
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
-- Green and black are easier on my eyes.
 
  +
(~?) :: (Eq a, Functor f) => f [a] -> [a] -> f Bool
greenXPConfig :: XPConfig
 
  +
q ~? x = fmap (x `isInfixOf`) q
greenXPConfig = defaultXPConfig { font = "9x15bold,xft:Bitstream Vera Sans"
 
, bgColor = "black"
 
, fgColor = "green"
 
, promptBorderWidth = 0
 
, position = Top
 
, height = 16
 
, historySize = 256 }
 
   
 
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 actions
+
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)
 
, ((m, xK_n), windows W.focusDown)
 
, ((m, xK_n), windows W.focusDown)
 
, ((m, xK_p), windows W.focusUp)
 
, ((m, xK_p), windows W.focusUp)
, ((m, xK_u), withFocused $ windows . W.sink) -- unfloat
+
, ((m, xK_z), withFocused $ windows . W.sink) -- unfloat
-- Add custom bindings and commands
+
-- Custom bindings and commands
, ((m, xK_a), runOrRaise "amarok" (className =? "amarokapp"))
 
 
, ((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, 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_y), promptSearch greenXPConfig wayback)
+
, ((m, xK_y), promptSearch greenXPConfig scholar)
, ((m .|. shiftMask,xK_y), selectSearch wayback)
+
, ((m .|. shiftMask,xK_y), selectSearch scholar)
, ((m, xK_Print), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png")
+
, ((m, xK_w), safeSpawnProg "/home/gwern/bin/bin/brainworkshop")
, ((m, xK_i), raiseMaybe (runInTerm "-title irssi" "sh -c 'screen -r irssi'") (title =? "irssi"))
+
, ((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"))
-- We ask for zsh specifically so .zshenv gets picked up and my
 
  +
, ((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")
-- 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_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
, ((m .|. shiftMask,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_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/2015/log.txt")
where term :: String
 
  +
, ((m .|. shiftMask,xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/2015/log-media.txt")]
term = XMonad.terminal conf
 
 
</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")]