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

From HaskellWiki
Jump to navigation Jump to search
(+amarok binding)
(update)
 
(17 intermediate revisions by the same user not shown)
Line 1: Line 1:
 
<haskell>
 
<haskell>
 
import Data.List (isInfixOf)
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
 
 
import Data.Map as M (fromList,union, Map())
module Main where
 
 
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,
 
 
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
terminal, XConfig), X()) -}
 
import XMonad.Actions.Search (google, wayback, wikipedia, selectSearch, promptSearch)
+
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
import XMonad.Config (defaultConfig)
+
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, XPConfig(font))
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, shift, sink, view)
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.Hooks.SetWMName
import XMonad.Actions.WindowGo (title, raiseMaybe, (=?), raiseBrowser, raiseEditor, runOrRaise)
 
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
 
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
 
import XMonad.Config.Gnome
 
   
 
main :: IO ()
 
main :: IO ()
main = xmonad myConfig
+
main = spawn "killall unclutter;unclutter" >> xmonad myConfig
  +
where myConfig = withUrgencyHook FocusHook $ mateConfig {
 
 
keys = \c -> myKeys c `M.union` keys def c
-- Begin customizations
 
 
, layoutHook = avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
myConfig = gnomeConfig { focusedBorderColor = "red"
 
, keys = \c -> myKeys c `M.union` keys defaultConfig c
 
, layoutHook = avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
 
 
, logHook = ewmhDesktopsLogHook
 
, logHook = ewmhDesktopsLogHook
, manageHook = manageDocks <+> manageHook defaultConfig
+
, manageHook = myManageHook
 
, modMask = mod4Mask
 
, modMask = mod4Mask
 
, normalBorderColor = "grey"
 
, normalBorderColor = "grey"
 
, focusedBorderColor = "red"
 
, borderWidth = 2
 
, terminal = "urxvt"
 
, terminal = "urxvt"
}
+
, startupHook = setWMName "LD3D"
where tiled :: Tall a
+
, XMonad.workspaces = ["web", "irc", "code", "background"] }
tiled = Tall 1 0.03 0.5
+
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 "Firefox" "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,
  +
-- className =? "Zenity" --> 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
greenXPConfig :: XPConfig
 
  +
(~?) :: (Eq a, Functor f) => f [a] -> [a] -> f Bool
greenXPConfig = defaultXPConfig { font = "9x15bold,xft:DejaVu Vera Sans Mono"
 
  +
q ~? x = fmap (x `isInfixOf`) q
, 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 (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_Print), unsafeSpawn "import -quality 90 -descend png:$HOME/xwd-$(date +%s)$$.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 -A -r irssi'") (title ~? "Irssi"))
  +
, ((m .|. shiftMask,xK_i), spawn "TMP=$(mktemp --suffix='.txt'); xclip -o|tr '\n' ' '|sed -e 's/- //' -e 's/^ *//' -e 's/ *$//' -e 's/[[:blank:]]\\+/ /g' > $TMP && screen -S 'irssi' -X readbuf $TMP && screen -S 'irssi' -X paste .;rm $TMP")
-- We ask for zsh specifically so .zshenv gets picked up and my
 
 
, ((m, xK_m), runOrRaise "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 -A -r rtorrent'") (title =? "rtorrent"))
, ((m .|. shiftMask,xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
+
, ((m .|. shiftMask,xK_r), spawn "/home/gwern/bin/bin/rotate-screen.sh")
, ((m, xK_r), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
+
, ((m, xK_f), raiseBrowser)
, ((m, xK_d), raiseBrowser) ]
+
, ((m, xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/$(date +%Y)/log.txt")
  +
, ((m .|. shiftMask,xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/$(date +%Y)/log-media.txt")]
where term :: String
 
term = "urxvt"
+
++ [((m .|. m', key), screenWorkspace sc >>= flip whenJust (windows . f))
  +
| (key, sc) <- zip [xK_s, xK_a] [0..]
  +
, (f, m') <- [(W.view, 0), (W.shift, shiftMask)]]
  +
where greenXPConfig' = greenXPConfig { font = "xft:Bitstream Vera Sans Mono:pixelsize=18" }
 
</haskell>
 
</haskell>

Latest revision as of 23:47, 28 November 2018

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, XPConfig(font))
import XMonad.Prompt.Shell (shellPrompt, prompt, safePrompt)
import XMonad.StackSet as W (focusUp, focusDown, shift, sink, view)
import XMonad.Util.Run (unsafeSpawn, runInTerm, safeSpawnProg)
import XMonad.Util.XSelection (safePromptSelection)
import XMonad.Hooks.SetWMName

main :: IO ()
main = spawn "killall unclutter;unclutter" >> xmonad myConfig
 where myConfig = withUrgencyHook FocusHook $ mateConfig {
                           keys = \c -> myKeys c `M.union` keys def c
                         , layoutHook =  avoidStruts $ smartBorders (Full ||| tiled ||| Mirror tiled)
                         , logHook    = ewmhDesktopsLogHook
                         , manageHook = myManageHook
                         , modMask = mod4Mask
                         , normalBorderColor  = "grey"
                         , focusedBorderColor = "red"
                         , borderWidth = 2
                         , terminal = "urxvt"
                         , startupHook = setWMName "LD3D"
                         , 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 "Firefox" "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,
                            -- className =? "Zenity"               --> 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_Print), unsafeSpawn "import -quality 90 -descend png:$HOME/xwd-$(date +%s)$$.png")
          , ((m,              xK_i), raiseMaybe (runInTerm "-title Irssi" "sh -c 'screen -A -r irssi'") (title ~? "Irssi"))
          , ((m .|. shiftMask,xK_i), spawn "TMP=$(mktemp --suffix='.txt'); xclip -o|tr '\n' ' '|sed -e 's/- //' -e 's/^ *//' -e 's/ *$//' -e 's/[[:blank:]]\\+/ /g' > $TMP && screen -S 'irssi' -X readbuf $TMP && screen -S 'irssi' -X paste .;rm $TMP")
          , ((m,              xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
          , ((m,              xK_r), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -A -r rtorrent'") (title =? "rtorrent"))
          , ((m .|. shiftMask,xK_r), spawn "/home/gwern/bin/bin/rotate-screen.sh")
          , ((m,              xK_f), raiseBrowser)
          , ((m,              xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/$(date +%Y)/log.txt")
          , ((m .|. shiftMask,xK_v), spawn "/home/gwern/bin/bin/logprompt.sh /home/gwern/doc/$(date +%Y)/log-media.txt")]
          ++ [((m .|. m', key), screenWorkspace sc >>= flip whenJust (windows . f))
                   | (key, sc) <- zip [xK_s, xK_a] [0..]
                   , (f, m') <- [(W.view, 0), (W.shift, shiftMask)]]
    where greenXPConfig' = greenXPConfig { font = "xft:Bitstream Vera Sans Mono:pixelsize=18" }