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

From HaskellWiki
(firefox changd its classname for v3.x)
(update)
Line 5: Line 5:
import Data.Bits (Bits((.|.)))
import Data.Bits (Bits((.|.)))
import Data.Map as M (M.fromList, M.union, Map())
import Data.Map as M (M.fromList, M.union, Map())
import Graphics.X11
 
import XMonad (XConfig(layoutHook, keys, modMask, focusedBorderColor, normalBorderColor,
import XMonad
                                 terminal, defaultGaps, XConfig), X())
-- XMonad re-exports Graphics.X11, so we can't enumerate imports without also
-- enumerating all the keys and such-like. The stuff from XMonad itself is:
--    (XConfig(layoutHook, keys, modMask, focusedBorderColor, normalBorderColor,
--                                 terminal, XConfig), X())
import XMonad.Actions.Search (google, wayback, wikipedia, selectSearch, promptSearch)
import XMonad.Actions.Search (google, wayback, wikipedia, selectSearch, promptSearch)
import XMonad.Config (defaultConfig)
import XMonad.Config (defaultConfig)
Line 18: Line 21:
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 (W.focusUp, W.focusDown)
import XMonad.Util.Run (safeSpawn, unsafeSpawn, runInTerm)
import XMonad.Util.Run (unsafeSpawn, runInTerm)
import XMonad.Util.XSelection (safePromptSelection)
import XMonad.Util.XSelection (safePromptSelection)
import XMonad.Actions.WindowGo (className, title, runOrRaise, raiseMaybe, (=?))
import XMonad.Actions.WindowGo (className, title, runOrRaise, raiseMaybe, (=?))
Line 27: Line 30:
{- Begin custom bindings.
{- Begin custom bindings.
     these add a need for: urxvt, Firefox, and Emacs -}
     these add a need for: urxvt, Firefox, and Emacs -}
-- config :: XConfig (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.NoBorders.SmartBorder
--                                          (XMonad.Layout.Choose Full (XMonad.Layout.Choose Tall (Mirror Tall))))
myConfig = defaultConfig
myConfig = defaultConfig
     { defaultGaps = [(0,0,0,0)]
     { terminal = "urxvt"
    , terminal = "urxvt"
     , normalBorderColor  = "grey"
     , normalBorderColor  = "grey"
     , focusedBorderColor = "red"
     , focusedBorderColor = "red"
     , modMask = mod4Mask
     , modMask = mod4Mask
     , keys = \c -> myKeys c `M.union` keys defaultConfig c
     , keys = \c -> myKeys c `M.union` keys defaultConfig c
     , layoutHook = smartBorders (Full ||| tiled ||| Mirror tiled)
     , layoutHook = smartBorders (Full ||| tiled ||| Mirror tiled) }
    }


tiled :: Tall a
tiled :: Tall a
tiled = Tall 1 0.03 0.5
tiled = Tall 1 0.03 0.5
ff, term :: String
ff = "firefox"
term = "urxvtc"


greenXPConfig :: XPConfig
greenXPConfig :: XPConfig
greenXPConfig = defaultXPConfig {   font        = "9x15bold,xft:DejaVu Vera Sans Mono"
greenXPConfig = defaultXPConfig { font        = "9x15bold,xft:DejaVu Vera Sans Mono"
                                    , bgColor    = "black"
                                , bgColor    = "black"
                                    , fgColor    = "green"
                                , fgColor    = "green"
                                    , promptBorderWidth = 0
                                , promptBorderWidth = 0
                                    , position    = Top
                                , position    = Top
                                    , height      = 16
                                , height      = 16
                                    , historySize = 256 }
                                , historySize = 256 }
 


myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
Line 57: Line 58:
     M.fromList $
     M.fromList $
           [ ((modm .|. shiftMask, xK_p    ), shellPrompt greenXPConfig)
           [ ((modm .|. shiftMask, xK_p    ), shellPrompt greenXPConfig)
           , ((modm,              xK_k    ), kill ) -- %! Move focus to the previous WindowSet
           , ((modm,              xK_k    ), kill)
           , ((modm,              xK_n    ), windows W.focusUp)
           , ((modm,              xK_n    ), windows W.focusDown)
           , ((modm,              xK_p    ), windows W.focusDown)
           , ((modm,              xK_p    ), windows W.focusUp)


           , ((modm .|. shiftMask, xK_b    ), safePromptSelection ff)
           , ((modm .|. shiftMask, xK_b    ), safePromptSelection ff)
           , ((modm .|. shiftMask, xK_c    ), prompt (term ++ " -e") greenXPConfig)
           , ((modm .|. shiftMask, xK_c    ), prompt (term ++ " -e") greenXPConfig)
           , ((modm .|. shiftMask, xK_d    ), runInTerm "" "elinks")
           , ((modm .|. shiftMask, xK_d    ), raiseMaybe (runInTerm "-title elinks" "elinks") (title =? "elinks"))
           , ((modm .|. shiftMask, xK_e    ), prompt "emacsclient -a emacs" greenXPConfig)
           , ((modm .|. shiftMask, xK_e    ), prompt "emacsclient -a emacs" greenXPConfig)
           , ((modm .|. shiftMask, xK_g    ), selectSearch ff google)
           , ((modm .|. shiftMask, xK_g    ), selectSearch ff google)
Line 78: Line 79:
           , ((modm,              xK_m    ), raiseMaybe (runInTerm "-title mutt"  "sh -c 'mutt'") (title =? "mutt"))
           , ((modm,              xK_m    ), raiseMaybe (runInTerm "-title mutt"  "sh -c 'mutt'") (title =? "mutt"))
           , ((modm,              xK_r    ), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
           , ((modm,              xK_r    ), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
           , ((modm,              xK_d    ), runOrRaise "firefox" (className =? "Firefox"))
           , ((modm,              xK_d    ), runOrRaise "firefox" (className =? "Firefox")) ]
          -- Extension-provided key bindings
          ]
 
ff, term :: String
ff = "firefox"
term = "urxvtc"
</haskell>
</haskell>

Revision as of 03:20, 30 March 2008

{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module Main where

import Data.Bits (Bits((.|.)))
import Data.Map as M (M.fromList, M.union, Map())

import XMonad
-- XMonad re-exports Graphics.X11, so we can't enumerate imports without also
-- enumerating all the keys and such-like. The stuff from XMonad itself is:
--    (XConfig(layoutHook, keys, modMask, focusedBorderColor, normalBorderColor,
--                                  terminal, XConfig), X())
import XMonad.Actions.Search (google, wayback, wikipedia, selectSearch, promptSearch)
import XMonad.Config (defaultConfig)
import XMonad.Layout (Full(..), Mirror(..), Tall(..), (|||))
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Main (xmonad)
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.StackSet as W (W.focusUp, W.focusDown)
import XMonad.Util.Run (unsafeSpawn, runInTerm)
import XMonad.Util.XSelection (safePromptSelection)
import XMonad.Actions.WindowGo (className, title, runOrRaise, raiseMaybe, (=?))

main :: IO ()
main = xmonad myConfig

{- Begin custom bindings.
    these add a need for: urxvt, Firefox, and Emacs -}
myConfig = defaultConfig
    { terminal = "urxvt"
    , normalBorderColor  = "grey"
    , focusedBorderColor = "red"
    , modMask = mod4Mask
    , keys = \c -> myKeys c `M.union` keys defaultConfig c
    , layoutHook = smartBorders (Full ||| tiled ||| Mirror tiled) }

tiled :: Tall a
tiled = Tall 1 0.03 0.5

ff, term :: String
ff = "firefox"
term = "urxvtc"

greenXPConfig :: XPConfig
greenXPConfig = defaultXPConfig {  font        = "9x15bold,xft:DejaVu Vera Sans Mono"
                                 , bgColor     = "black"
                                 , fgColor     = "green"
                                 , promptBorderWidth = 0
                                 , position    = Top
                                 , height      = 16
                                 , historySize = 256 }

myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ())
myKeys (XConfig {modMask = modm}) =
    M.fromList $
          [ ((modm .|. shiftMask, xK_p     ), shellPrompt greenXPConfig)
          , ((modm,               xK_k     ), kill)
          , ((modm,               xK_n     ), windows W.focusDown)
          , ((modm,               xK_p     ), windows W.focusUp)

          , ((modm .|. shiftMask, xK_b     ), safePromptSelection ff)
          , ((modm .|. shiftMask, xK_c     ), prompt (term ++ " -e") greenXPConfig)
          , ((modm .|. shiftMask, xK_d     ), raiseMaybe (runInTerm "-title elinks" "elinks") (title =? "elinks"))
          , ((modm .|. shiftMask, xK_e     ), prompt "emacsclient -a emacs" greenXPConfig)
          , ((modm .|. shiftMask, xK_g     ), selectSearch ff google)
          , ((modm .|. shiftMask, xK_t     ), selectSearch ff wikipedia)
          , ((modm .|. shiftMask, xK_y     ), selectSearch ff wayback)
          , ((modm,               xK_Print ), unsafeSpawn "import -quality 90 -window root png:$HOME/xwd-$(date +%s)$$.png")
          , ((modm,               xK_b     ), safePrompt ff greenXPConfig)
          , ((modm,               xK_c     ), unsafeSpawn term)
          , ((modm,               xK_e     ), runOrRaise  "emacs" (className =? "Emacs"))
          , ((modm,               xK_g     ), promptSearch greenXPConfig ff google)
          , ((modm,               xK_t     ), promptSearch greenXPConfig ff wikipedia)
          , ((modm,               xK_y     ), promptSearch greenXPConfig ff wayback)
          , ((modm,               xK_i     ), raiseMaybe (runInTerm "-title irssi" "sh -c 'screen -r irssi'") (title =? "irssi"))
          , ((modm,               xK_m     ), raiseMaybe (runInTerm "-title mutt"  "sh -c 'mutt'") (title =? "mutt"))
          , ((modm,               xK_r     ), raiseMaybe (runInTerm "-title rtorrent" "sh -c 'screen -r rtorrent'") (title =? "rtorrent"))
          , ((modm,               xK_d     ), runOrRaise "firefox" (className =? "Firefox")) ]