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

From HaskellWiki
Jump to navigation Jump to search
(firefox changd its classname for v3.x)
(update)
 
(21 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 XMonad
 
  +
import XMonad.Actions.Search (google, scholar, wikipedia, selectSearch, promptSearch)
import Data.Bits (Bits((.|.)))
 
  +
import XMonad.Actions.WindowGo (raiseMaybe, raiseBrowser, raiseEditor, runOrRaise)
import Data.Map as M (M.fromList, M.union, Map())
 
  +
import XMonad.Config.Mate (mateConfig)
import Graphics.X11
 
  +
import XMonad.Hooks.EwmhDesktops (ewmhDesktopsLogHook)
import XMonad (XConfig(layoutHook, keys, modMask, focusedBorderColor, normalBorderColor,
 
  +
import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks)
terminal, defaultGaps, XConfig), X())
 
import XMonad.Actions.Search (google, wayback, wikipedia, selectSearch, promptSearch)
+
import XMonad.Hooks.UrgencyHook (withUrgencyHook, FocusHook(..))
import XMonad.Config (defaultConfig)
 
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)
+
import XMonad.StackSet as W (focusUp, focusDown, shift, sink, view)
import XMonad.Util.Run (safeSpawn, 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 (className, title, runOrRaise, raiseMaybe, (=?))
 
   
 
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
  +
, 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
{- Begin custom bindings.
 
  +
defaultConfig, since I don't like floating mplayer and I don't use the other
these add a need for: urxvt, Firefox, and Emacs -}
 
  +
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,
-- config :: XConfig (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.NoBorders.SmartBorder
 
-- (XMonad.Layout.Choose Full (XMonad.Layout.Choose Tall (Mirror Tall))))
+
className =? "defcon.bin.x86" --> unfloat,
  +
className =? "Mnemosyne" --> unfloat,
myConfig = defaultConfig
 
  +
-- className =? "Zenity" --> unfloat,
{ defaultGaps = [(0,0,0,0)]
 
  +
title =? "Brain Workshop 4.8.6" --> unfloat,
, terminal = "urxvt"
 
, normalBorderColor = "grey"
 
, focusedBorderColor = "red"
 
, modMask = mod4Mask
 
, keys = \c -> myKeys c `M.union` keys defaultConfig c
 
, layoutHook = smartBorders (Full ||| tiled ||| Mirror tiled)
 
}
 
   
  +
title ~? "Irssi" --> doShift "irc"]
tiled :: Tall a
 
  +
<+> manageDocks
tiled = Tall 1 0.03 0.5
 
  +
where moveC c w = className =? c --> doShift w
 
  +
-- moveT t w = title =? t --> doShift w
greenXPConfig :: XPConfig
 
  +
unfloat = ask >>= doF . W.sink
greenXPConfig = defaultXPConfig { font = "9x15bold,xft:DejaVu Vera Sans Mono"
 
, bgColor = "black"
 
, fgColor = "green"
 
, promptBorderWidth = 0
 
, position = Top
 
, height = 16
 
, historySize = 256 }
 
   
  +
-- 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 ())
myKeys (XConfig {modMask = modm}) =
+
myKeys XConfig {modMask = m, terminal = term} = M.fromList $ [ -- rebind standard keys
  +
((m .|. shiftMask,xK_p), shellPrompt greenXPConfig')
M.fromList $
 
[ ((modm .|. shiftMask, xK_p ), shellPrompt greenXPConfig)
+
, ((m, xK_k), kill)
, ((modm, xK_k ), kill ) -- %! Move focus to the previous WindowSet
+
, ((m, xK_n), windows W.focusDown)
, ((modm, xK_n ), windows W.focusUp)
+
, ((m, xK_p), windows W.focusUp)
, ((modm, xK_p ), windows W.focusDown)
+
, ((m, xK_z), withFocused $ windows . W.sink) -- unfloat
  +
-- Custom bindings and commands
 
, ((modm .|. shiftMask, xK_b ), safePromptSelection ff)
+
, ((m, xK_b), safePrompt "firefox" greenXPConfig')
, ((modm .|. shiftMask, xK_c ), prompt (term ++ " -e") greenXPConfig)
+
, ((m .|. shiftMask,xK_b), safePromptSelection "firefox")
, ((modm .|. shiftMask, xK_d ), runInTerm "" "elinks")
+
, ((m, xK_c), safeSpawnProg term)
, ((modm .|. shiftMask, xK_e ), prompt "emacsclient -a emacs" greenXPConfig)
+
, ((m .|. shiftMask,xK_c), prompt (term ++ " -e") greenXPConfig')
, ((modm .|. shiftMask, xK_g ), selectSearch ff google)
+
, ((m, xK_e), raiseEditor)
, ((modm .|. shiftMask, xK_t ), selectSearch ff wikipedia)
+
, ((m .|. shiftMask,xK_e), prompt "emacs" greenXPConfig')
, ((modm .|. shiftMask, xK_y ), selectSearch ff wayback)
+
, ((m, xK_g), promptSearch greenXPConfig' google)
  +
, ((m .|. shiftMask,xK_g), selectSearch google)
, ((modm, xK_Print ), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png")
 
, ((modm, xK_b ), safePrompt ff greenXPConfig)
+
, ((m, xK_t), promptSearch greenXPConfig' wikipedia)
, ((modm, xK_c ), unsafeSpawn term)
+
, ((m .|. shiftMask,xK_t), selectSearch wikipedia)
, ((modm, xK_e ), runOrRaise "emacs" (className =? "Emacs"))
+
, ((m, xK_y), promptSearch greenXPConfig' scholar)
, ((modm, xK_g ), promptSearch greenXPConfig ff google)
+
, ((m .|. shiftMask,xK_y), selectSearch scholar)
, ((modm, xK_t ), promptSearch greenXPConfig ff wikipedia)
+
, ((m, xK_Print), unsafeSpawn "import -quality 90 -descend png:$HOME/xwd-$(date +%s)$$.png")
, ((modm, xK_y ), promptSearch greenXPConfig ff wayback)
+
, ((m, xK_i), raiseMaybe (runInTerm "-title Irssi" "sh -c 'screen -A -r irssi'") (title ~? "Irssi"))
, ((modm, xK_i ), raiseMaybe (runInTerm "-title irssi" "sh -c 'screen -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")
, ((modm, xK_m ), raiseMaybe (runInTerm "-title mutt" "sh -c 'mutt'") (title =? "mutt"))
+
, ((m, xK_m), runOrRaise "mnemosyne" (className =? "Mnemosyne"))
, ((modm, xK_r ), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
+
, ((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")
, ((modm, xK_d ), runOrRaise "firefox" (className =? "Firefox"))
 
  +
, ((m, xK_f), raiseBrowser)
-- Extension-provided key bindings
 
  +
, ((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))
ff, term :: String
 
  +
| (key, sc) <- zip [xK_s, xK_a] [0..]
ff = "firefox"
 
  +
, (f, m') <- [(W.view, 0), (W.shift, shiftMask)]]
term = "urxvtc"
 
  +
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" }