mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-31 04:01:51 -07:00
use Data.Default wherever possible, and deprecate the things it replaces
This commit is contained in:
@@ -36,7 +36,6 @@ import XMonad.Layout.NoBorders
|
||||
import XMonad.Layout.SimpleFloat
|
||||
import XMonad.Layout.Tabbed
|
||||
import XMonad.Layout.WindowArranger
|
||||
import XMonad.Prompt
|
||||
import XMonad.Prompt.Shell
|
||||
import XMonad.Prompt.Ssh
|
||||
import XMonad.Prompt.Theme
|
||||
@@ -120,7 +119,7 @@ arossatoConfig = do
|
||||
newManageHook = myManageHook
|
||||
|
||||
-- xmobar
|
||||
myDynLog h = dynamicLogWithPP defaultPP
|
||||
myDynLog h = dynamicLogWithPP def
|
||||
{ ppCurrent = xmobarColor "yellow" "" . wrap "[" "]"
|
||||
, ppTitle = xmobarColor "green" "" . shorten 40
|
||||
, ppVisible = wrap "(" ")"
|
||||
@@ -144,12 +143,12 @@ arossatoConfig = do
|
||||
[(shiftMask .|. modMask x, k) | k <- [xK_1 .. xK_9]]
|
||||
-- These are my personal key bindings
|
||||
toAdd x =
|
||||
[ ((modMask x , xK_F12 ), xmonadPrompt defaultXPConfig )
|
||||
, ((modMask x , xK_F3 ), shellPrompt defaultXPConfig )
|
||||
, ((modMask x , xK_F4 ), sshPrompt defaultXPConfig )
|
||||
, ((modMask x , xK_F5 ), themePrompt defaultXPConfig )
|
||||
, ((modMask x , xK_F6 ), windowPromptGoto defaultXPConfig )
|
||||
, ((modMask x , xK_F7 ), windowPromptBring defaultXPConfig )
|
||||
[ ((modMask x , xK_F12 ), xmonadPrompt def )
|
||||
, ((modMask x , xK_F3 ), shellPrompt def )
|
||||
, ((modMask x , xK_F4 ), sshPrompt def )
|
||||
, ((modMask x , xK_F5 ), themePrompt def )
|
||||
, ((modMask x , xK_F6 ), windowPromptGoto def )
|
||||
, ((modMask x , xK_F7 ), windowPromptBring def )
|
||||
, ((modMask x , xK_comma ), prevWS )
|
||||
, ((modMask x , xK_period), nextWS )
|
||||
, ((modMask x , xK_Right ), windows W.focusDown )
|
||||
|
@@ -307,12 +307,12 @@ xmobarCommand (S s) = unwords ["xmobar",
|
||||
allPPs nScreens = sequence_ [dynamicLogWithPP (pp s) | s <- [0..nScreens-1], pp <- [ppFocus, ppWorkspaces]]
|
||||
color c = xmobarColor c ""
|
||||
|
||||
ppFocus s@(S s_) = whenCurrentOn s defaultPP {
|
||||
ppFocus s@(S s_) = whenCurrentOn s def {
|
||||
ppOrder = \(_:_:windowTitle:_) -> [windowTitle],
|
||||
ppOutput = appendFile (pipeName "focus" s_) . (++ "\n")
|
||||
}
|
||||
|
||||
ppWorkspaces s@(S s_) = marshallPP s defaultPP {
|
||||
ppWorkspaces s@(S s_) = marshallPP s def {
|
||||
ppCurrent = color "white",
|
||||
ppVisible = color "white",
|
||||
ppHiddenNoWindows = color dark,
|
||||
|
@@ -16,7 +16,7 @@ import qualified XMonad.StackSet as W
|
||||
import qualified Data.Map as M
|
||||
import System.Exit ( exitWith, ExitCode(ExitSuccess) )
|
||||
|
||||
import XMonad.Layout.Tabbed ( tabbed, defaultTheme,
|
||||
import XMonad.Layout.Tabbed ( tabbed,
|
||||
shrinkText, Shrinker, shrinkIt, CustomShrink(CustomShrink) )
|
||||
import XMonad.Layout.Combo ( combineTwo )
|
||||
import XMonad.Layout.Named ( named )
|
||||
@@ -32,7 +32,7 @@ import XMonad.Layout.ToggleLayouts ( toggleLayouts, ToggleLayout(ToggleLayout) )
|
||||
import XMonad.Layout.ShowWName ( showWName )
|
||||
import XMonad.Layout.Magnifier ( maximizeVertical, MagnifyMsg(Toggle) )
|
||||
|
||||
import XMonad.Prompt ( defaultXPConfig, font, height, XPConfig )
|
||||
import XMonad.Prompt ( font, height, XPConfig )
|
||||
import XMonad.Prompt.Layout ( layoutPrompt )
|
||||
import XMonad.Prompt.Shell ( shellPrompt )
|
||||
|
||||
@@ -46,8 +46,8 @@ import XMonad.Hooks.ManageDocks ( avoidStruts, manageDocks )
|
||||
import XMonad.Hooks.EwmhDesktops ( ewmh )
|
||||
|
||||
myXPConfig :: XPConfig
|
||||
myXPConfig = defaultXPConfig {font="-*-lucida-medium-r-*-*-14-*-*-*-*-*-*-*"
|
||||
,height=22}
|
||||
myXPConfig = def {font="-*-lucida-medium-r-*-*-14-*-*-*-*-*-*-*"
|
||||
,height=22}
|
||||
|
||||
|
||||
------------------------------------------------------------------------
|
||||
@@ -137,7 +137,7 @@ config = ewmh def
|
||||
, XMonad.keys = keys
|
||||
}
|
||||
|
||||
mytab = tabbed CustomShrink defaultTheme
|
||||
mytab = tabbed CustomShrink def
|
||||
|
||||
instance Shrinker CustomShrink where
|
||||
shrinkIt shr s | Just s' <- dropFromHead " " s = shrinkIt shr s'
|
||||
|
@@ -62,8 +62,8 @@ sjanssenConfig =
|
||||
]
|
||||
|
||||
myFont = "xft:Bitstream Vera Sans Mono:pixelsize=10"
|
||||
myTheme = defaultTheme { fontName = myFont }
|
||||
myPromptConfig = defaultXPConfig
|
||||
myTheme = def { fontName = myFont }
|
||||
myPromptConfig = def
|
||||
{ position = Top
|
||||
, font = myFont
|
||||
, showCompletionOnTab = True
|
||||
|
Reference in New Issue
Block a user