aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDaniel Wagner <daniel@wagner-home.com>2013-05-28 02:58:25 +0200
committerDaniel Wagner <daniel@wagner-home.com>2013-05-28 02:58:25 +0200
commitfe066e8e9ca5326dd146630a6d729fae51af12cf (patch)
treec5596ebcdaef64f3421ea5e5b5fb2a9409ba09f6
parentd65d41e4b629413c2d8b9fe3e2b03f5ae46e6cde (diff)
downloadXMonadContrib-fe066e8e9ca5326dd146630a6d729fae51af12cf.tar.gz
XMonadContrib-fe066e8e9ca5326dd146630a6d729fae51af12cf.tar.xz
XMonadContrib-fe066e8e9ca5326dd146630a6d729fae51af12cf.zip
eliminate references to defaultConfig
Ignore-this: 37ae613e4b943e99c5200915b9d95e58 darcs-hash:20130528005825-76d51-89eaf6f1aeeb02086371f9c4ae2afade984f62e0.gz
-rw-r--r--XMonad/Actions/BluetileCommands.hs2
-rw-r--r--XMonad/Actions/CopyWindow.hs2
-rw-r--r--XMonad/Actions/GroupNavigation.hs2
-rw-r--r--XMonad/Actions/MouseResize.hs4
-rw-r--r--XMonad/Actions/Navigation2D.hs6
-rw-r--r--XMonad/Actions/Plane.hs6
-rw-r--r--XMonad/Actions/SpawnOn.hs4
-rw-r--r--XMonad/Actions/TopicSpace.hs2
-rw-r--r--XMonad/Actions/UpdateFocus.hs4
-rw-r--r--XMonad/Actions/WindowNavigation.hs2
-rw-r--r--XMonad/Actions/WorkspaceCursors.hs4
-rw-r--r--XMonad/Config/Arossato.hs4
-rw-r--r--XMonad/Config/Azerty.hs2
-rw-r--r--XMonad/Config/Bluetile.hs2
-rw-r--r--XMonad/Config/Desktop.hs15
-rw-r--r--XMonad/Config/Dmwit.hs2
-rw-r--r--XMonad/Config/Droundy.hs4
-rw-r--r--XMonad/Config/Sjanssen.hs6
-rw-r--r--XMonad/Doc/Configuring.hs2
-rw-r--r--XMonad/Doc/Extending.hs32
-rw-r--r--XMonad/Hooks/CurrentWorkspaceOnTop.hs2
-rw-r--r--XMonad/Hooks/DynamicLog.hs10
-rw-r--r--XMonad/Hooks/EwmhDesktops.hs4
-rw-r--r--XMonad/Hooks/FadeInactive.hs2
-rw-r--r--XMonad/Hooks/FadeWindows.hs2
-rw-r--r--XMonad/Hooks/FloatNext.hs2
-rw-r--r--XMonad/Hooks/InsertPosition.hs2
-rw-r--r--XMonad/Hooks/ManageHelpers.hs2
-rw-r--r--XMonad/Hooks/Minimize.hs4
-rw-r--r--XMonad/Hooks/Place.hs4
-rw-r--r--XMonad/Hooks/PositionStoreHooks.hs8
-rw-r--r--XMonad/Hooks/RestoreMinimized.hs2
-rw-r--r--XMonad/Hooks/Script.hs2
-rw-r--r--XMonad/Hooks/ServerMode.hs2
-rw-r--r--XMonad/Hooks/ToggleHook.hs4
-rw-r--r--XMonad/Hooks/UrgencyHook.hs6
-rw-r--r--XMonad/Hooks/WorkspaceByPos.hs4
-rw-r--r--XMonad/Hooks/WorkspaceHistory.hs2
-rw-r--r--XMonad/Layout/Accordion.hs2
-rw-r--r--XMonad/Layout/BorderResize.hs2
-rw-r--r--XMonad/Layout/BoringWindows.hs2
-rw-r--r--XMonad/Layout/ButtonDecoration.hs4
-rw-r--r--XMonad/Layout/Circle.hs2
-rw-r--r--XMonad/Layout/Cross.hs2
-rw-r--r--XMonad/Layout/DecorationMadness.hs2
-rw-r--r--XMonad/Layout/Dishes.hs2
-rw-r--r--XMonad/Layout/DragPane.hs2
-rw-r--r--XMonad/Layout/Drawer.hs2
-rw-r--r--XMonad/Layout/DwmStyle.hs10
-rw-r--r--XMonad/Layout/FixedColumn.hs2
-rw-r--r--XMonad/Layout/Fullscreen.hs6
-rw-r--r--XMonad/Layout/Grid.hs2
-rw-r--r--XMonad/Layout/HintedGrid.hs2
-rw-r--r--XMonad/Layout/HintedTile.hs2
-rw-r--r--XMonad/Layout/IM.hs2
-rw-r--r--XMonad/Layout/ImageButtonDecoration.hs4
-rw-r--r--XMonad/Layout/IndependentScreens.hs6
-rw-r--r--XMonad/Layout/LayoutBuilder.hs2
-rw-r--r--XMonad/Layout/LayoutCombinators.hs2
-rw-r--r--XMonad/Layout/LayoutHints.hs6
-rw-r--r--XMonad/Layout/LimitWindows.hs2
-rw-r--r--XMonad/Layout/MagicFocus.hs4
-rw-r--r--XMonad/Layout/Magnifier.hs2
-rw-r--r--XMonad/Layout/Maximize.hs2
-rw-r--r--XMonad/Layout/Minimize.hs2
-rw-r--r--XMonad/Layout/Mosaic.hs2
-rw-r--r--XMonad/Layout/MosaicAlt.hs2
-rw-r--r--XMonad/Layout/MouseResizableTile.hs2
-rw-r--r--XMonad/Layout/MultiColumns.hs4
-rw-r--r--XMonad/Layout/Named.hs2
-rw-r--r--XMonad/Layout/NoFrillsDecoration.hs4
-rw-r--r--XMonad/Layout/PositionStoreFloat.hs2
-rw-r--r--XMonad/Layout/ResizableTile.hs2
-rw-r--r--XMonad/Layout/Roledex.hs2
-rw-r--r--XMonad/Layout/ShowWName.hs4
-rw-r--r--XMonad/Layout/SimpleDecoration.hs4
-rw-r--r--XMonad/Layout/SimpleFloat.hs2
-rw-r--r--XMonad/Layout/Simplest.hs2
-rw-r--r--XMonad/Layout/SimplestFloat.hs2
-rw-r--r--XMonad/Layout/Spiral.hs2
-rw-r--r--XMonad/Layout/StackTile.hs2
-rw-r--r--XMonad/Layout/SubLayouts.hs2
-rw-r--r--XMonad/Layout/TabBarDecoration.hs2
-rw-r--r--XMonad/Layout/Tabbed.hs4
-rw-r--r--XMonad/Layout/ThreeColumns.hs2
-rw-r--r--XMonad/Layout/ToggleLayouts.hs2
-rw-r--r--XMonad/Layout/TrackFloating.hs2
-rw-r--r--XMonad/Layout/TwoPane.hs2
-rw-r--r--XMonad/Layout/WindowArranger.hs6
-rw-r--r--XMonad/Layout/WindowNavigation.hs2
-rw-r--r--XMonad/Layout/WindowSwitcherDecoration.hs12
-rw-r--r--XMonad/Layout/WorkspaceDir.hs2
-rw-r--r--XMonad/Util/CustomKeys.hs8
-rw-r--r--XMonad/Util/EZConfig.hs12
-rw-r--r--XMonad/Util/NamedActions.hs6
-rw-r--r--XMonad/Util/Replace.hs4
-rw-r--r--XMonad/Util/Run.hs2
-rw-r--r--XMonad/Util/Themes.hs2
98 files changed, 182 insertions, 181 deletions
diff --git a/XMonad/Actions/BluetileCommands.hs b/XMonad/Actions/BluetileCommands.hs
index a8e0f2b..b410015 100644
--- a/XMonad/Actions/BluetileCommands.hs
+++ b/XMonad/Actions/BluetileCommands.hs
@@ -36,7 +36,7 @@ import System.Exit
--
-- Then edit your @handleEventHook@:
--
--- > main = xmonad defaultConfig { handleEventHook = serverModeEventHook' bluetileCommands }
+-- > main = xmonad def { handleEventHook = serverModeEventHook' bluetileCommands }
--
-- See the documentation of "XMonad.Hooks.ServerMode" for details on
-- how to actually invoke the commands from external programs.
diff --git a/XMonad/Actions/CopyWindow.hs b/XMonad/Actions/CopyWindow.hs
index 191c17f..7db7bc1 100644
--- a/XMonad/Actions/CopyWindow.hs
+++ b/XMonad/Actions/CopyWindow.hs
@@ -87,7 +87,7 @@ import qualified XMonad.StackSet as W
-- >
-- > main = do
-- > h <- spawnPipe "xmobar"
--- > xmonad defaultConfig { logHook = sampleLogHook h }
+-- > xmonad def { logHook = sampleLogHook h }
-- | Copy the focused window to a workspace.
copy :: (Eq s, Eq i, Eq a) => i -> W.StackSet i l a s sd -> W.StackSet i l a s sd
diff --git a/XMonad/Actions/GroupNavigation.hs b/XMonad/Actions/GroupNavigation.hs
index 639876b..408a5cd 100644
--- a/XMonad/Actions/GroupNavigation.hs
+++ b/XMonad/Actions/GroupNavigation.hs
@@ -73,7 +73,7 @@ Finally, you can define keybindings to jump to the most recent window
matching a certain Boolean query. To do this, you need to add
'historyHook' to your logHook:
-> main = xmonad $ defaultConfig { logHook = historyHook }
+> main = xmonad $ def { logHook = historyHook }
Then the following keybindings, for example, allow you to return to
the most recent xterm or emacs window or to simply to the most recent
diff --git a/XMonad/Actions/MouseResize.hs b/XMonad/Actions/MouseResize.hs
index 5441644..fd04fb0 100644
--- a/XMonad/Actions/MouseResize.hs
+++ b/XMonad/Actions/MouseResize.hs
@@ -43,11 +43,11 @@ import XMonad.Util.XUtils
--
-- Then edit your @layoutHook@ by modifying a given layout:
--
--- > myLayout = mouseResize $ windowArrange $ layoutHook defaultConfig
+-- > myLayout = mouseResize $ windowArrange $ layoutHook def
--
-- and then:
--
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Actions/Navigation2D.hs b/XMonad/Actions/Navigation2D.hs
index 27d772b..379180d 100644
--- a/XMonad/Actions/Navigation2D.hs
+++ b/XMonad/Actions/Navigation2D.hs
@@ -115,7 +115,7 @@ import XMonad.Util.Types
-- and add the configuration of the module to your main function:
--
-- > main = xmonad $ withNavigation2DConfig defaultNavigation2DConfig
--- > $ defaultConfig
+-- > $ def
--
-- For detailed instruction on editing the key binding see:
--
@@ -150,7 +150,7 @@ import XMonad.Util.Types
-- > myNavigation2DConfig = defaultNavigation2DConfig { layoutNavigation = [("Full", centerNavigation)] }
-- >
-- > main = xmonad $ withNavigation2DConfig myNavigation2DConfig
--- > $ defaultConfig
+-- > $ def
--
-- The navigation between windows is based on their screen rectangles, which are
-- available /and meaningful/ only for mapped windows. Thus, as already said,
@@ -169,7 +169,7 @@ import XMonad.Util.Types
-- > }
-- >
-- > main = xmonad $ withNavigation2DConfig myNavigation2DConfig
--- > $ defaultConfig
+-- > $ def
--
-- With this setup, Left/Up navigation behaves like standard
-- 'XMonad.StackSet.focusUp' and Right/Down navigation behaves like
diff --git a/XMonad/Actions/Plane.hs b/XMonad/Actions/Plane.hs
index 3037719..fee41bc 100644
--- a/XMonad/Actions/Plane.hs
+++ b/XMonad/Actions/Plane.hs
@@ -52,9 +52,9 @@ import XMonad.Util.Run
--
-- > import XMonad.Actions.Plane
-- >
--- > main = xmonad defaultConfig {keys = myKeys}
+-- > main = xmonad def {keys = myKeys}
-- >
--- > myKeys conf = union (keys defaultConfig conf) $ myNewKeys conf
+-- > myKeys conf = union (keys def conf) $ myNewKeys conf
-- >
-- > myNewkeys (XConfig {modMask = modm}) = planeKeys modm (Lines 3) Finite
--
@@ -226,4 +226,4 @@ gconftool :: String
gconftool = "gconftool-2"
parameters :: [String]
-parameters = ["--get", "/apps/panel/applets/workspace_switcher_screen0/prefs/num_rows"] \ No newline at end of file
+parameters = ["--get", "/apps/panel/applets/workspace_switcher_screen0/prefs/num_rows"]
diff --git a/XMonad/Actions/SpawnOn.hs b/XMonad/Actions/SpawnOn.hs
index 1154ce5..df37c9d 100644
--- a/XMonad/Actions/SpawnOn.hs
+++ b/XMonad/Actions/SpawnOn.hs
@@ -45,9 +45,9 @@ import qualified XMonad.Util.ExtensibleState as XS
-- > import XMonad.Actions.SpawnOn
--
-- > main = do
--- > xmonad defaultConfig {
+-- > xmonad def {
-- > ...
--- > manageHook = manageSpawn <+> manageHook defaultConfig
+-- > manageHook = manageSpawn <+> manageHook def
-- > ...
-- > }
--
diff --git a/XMonad/Actions/TopicSpace.hs b/XMonad/Actions/TopicSpace.hs
index d081439..cf4fb0d 100644
--- a/XMonad/Actions/TopicSpace.hs
+++ b/XMonad/Actions/TopicSpace.hs
@@ -161,7 +161,7 @@ import qualified XMonad.Util.ExtensibleState as XS
-- > myConfig = do
-- > checkTopicConfig myTopics myTopicConfig
-- > myLogHook <- makeMyLogHook
--- > return $ defaultConfig
+-- > return $ def
-- > { borderWidth = 1 -- Width of the window border in pixels.
-- > , workspaces = myTopics
-- > , layoutHook = myModifiers myLayout
diff --git a/XMonad/Actions/UpdateFocus.hs b/XMonad/Actions/UpdateFocus.hs
index ead23d8..46d36b0 100644
--- a/XMonad/Actions/UpdateFocus.hs
+++ b/XMonad/Actions/UpdateFocus.hs
@@ -29,7 +29,7 @@ import Data.Monoid
-- following to your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Actions.UpdateFocus
--- > xmonad $ defaultConfig {
+-- > xmonad $ def {
-- > ..
-- > startupHook = adjustEventInput
-- > handleEventHook = focusOnMouseMove
@@ -57,4 +57,4 @@ adjustEventInput = withDisplay $ \dpy -> do
rootw <- asks theRoot
io $ selectInput dpy rootw $ substructureRedirectMask .|. substructureNotifyMask
.|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask
- .|. buttonPressMask .|. pointerMotionMask \ No newline at end of file
+ .|. buttonPressMask .|. pointerMotionMask
diff --git a/XMonad/Actions/WindowNavigation.hs b/XMonad/Actions/WindowNavigation.hs
index c607dd2..af27733 100644
--- a/XMonad/Actions/WindowNavigation.hs
+++ b/XMonad/Actions/WindowNavigation.hs
@@ -62,7 +62,7 @@ import qualified Data.Set as S
--
-- > main = do
-- > config <- withWindowNavigation (xK_w, xK_a, xK_s, xK_d)
--- > $ defaultConfig { ... }
+-- > $ def { ... }
-- > xmonad config
--
-- Here, we pass in the keys for navigation in counter-clockwise order from up.
diff --git a/XMonad/Actions/WorkspaceCursors.hs b/XMonad/Actions/WorkspaceCursors.hs
index c33d998..eb7d7d7 100644
--- a/XMonad/Actions/WorkspaceCursors.hs
+++ b/XMonad/Actions/WorkspaceCursors.hs
@@ -69,8 +69,8 @@ import Data.Traversable(sequenceA)
-- > x <- xmobar conf
-- > xmonad x
-- >
--- > conf = additionalKeysP defaultConfig
--- > { layoutHook = workspaceCursors myCursors $ layoutHook defaultConfig
+-- > conf = additionalKeysP def
+-- > { layoutHook = workspaceCursors myCursors $ layoutHook def
-- > , workspaces = toList myCursors } $
-- > [("M-"++shift++control++[k], f direction depth)
-- > | (f,shift) <- zip [modifyLayer,shiftModifyLayer] ["","S-"]
diff --git a/XMonad/Config/Arossato.hs b/XMonad/Config/Arossato.hs
index fb4b5f2..319e2a1 100644
--- a/XMonad/Config/Arossato.hs
+++ b/XMonad/Config/Arossato.hs
@@ -86,7 +86,7 @@ import XMonad.Util.Themes
arossatoConfig = do
xmobar <- spawnPipe "xmobar" -- REMOVE this line if you do not have xmobar installed!
- return $ defaultConfig
+ return $ def
{ workspaces = ["home","var","dev","mail","web","doc"] ++
map show [7 .. 9 :: Int]
, logHook = myDynLog xmobar -- REMOVE this line if you do not have xmobar installed!
@@ -128,7 +128,7 @@ arossatoConfig = do
}
-- key bindings stuff
- defKeys = keys defaultConfig
+ defKeys = keys def
delKeys x = foldr M.delete (defKeys x) (toRemove x)
newKeys x = foldr (uncurry M.insert) (delKeys x) (toAdd x)
-- remove some of the default key bindings
diff --git a/XMonad/Config/Azerty.hs b/XMonad/Config/Azerty.hs
index 2d6c3d1..a642998 100644
--- a/XMonad/Config/Azerty.hs
+++ b/XMonad/Config/Azerty.hs
@@ -38,7 +38,7 @@ import qualified Data.Map as M
-- > import qualified Data.Map as M
-- > main = xmonad someConfig { keys = \c -> azertyKeys c `M.union` keys someConfig c }
-azertyConfig = defaultConfig { keys = azertyKeys <+> keys defaultConfig }
+azertyConfig = def { keys = azertyKeys <+> keys def }
azertyKeys conf@(XConfig {modMask = modm}) = M.fromList $
[((modm, xK_semicolon), sendMessage (IncMasterN (-1)))]
diff --git a/XMonad/Config/Bluetile.hs b/XMonad/Config/Bluetile.hs
index d80e70c..7796de5 100644
--- a/XMonad/Config/Bluetile.hs
+++ b/XMonad/Config/Bluetile.hs
@@ -198,7 +198,7 @@ bluetileLayoutHook = avoidStruts $ minimize $ boringWindows $ (
floatingDeco l = buttonDeco shrinkText defaultThemeWithButtons l
bluetileConfig =
- defaultConfig
+ def
{ modMask = mod4Mask, -- logo key
manageHook = bluetileManageHook,
layoutHook = bluetileLayoutHook,
diff --git a/XMonad/Config/Desktop.hs b/XMonad/Config/Desktop.hs
index e05c577..add5548 100644
--- a/XMonad/Config/Desktop.hs
+++ b/XMonad/Config/Desktop.hs
@@ -22,7 +22,8 @@ module XMonad.Config.Desktop (
-- the DE via a subset of the Extended Window Manager Hints (EWMH)
-- specification. Extra xmonad settings unique to specific DE's are
-- added by overriding or modifying @desktopConfig@ fields in the
- -- same way that @defaultConfig@ is customized in @~\/.xmonad/xmonad.hs@.
+ -- same way that the default configuration is customized in
+ -- @~\/.xmonad/xmonad.hs@.
--
-- For more information about EWMH see:
--
@@ -69,7 +70,7 @@ import qualified Data.Map as M
-- <http://haskell.org/haskellwiki/Xmonad>
--
-- To configure xmonad for use with a DE or with DE tools like panels
--- and pagers, in place of @defaultConfig@ in your @~\/.xmonad/xmonad.hs@,
+-- and pagers, in place of @def@ in your @~\/.xmonad/xmonad.hs@,
-- use @desktopConfig@ or one of the other desktop configs from the
-- @XMonad.Config@ namespace. The following setup and customization examples
-- work the same way for the other desktop configs as for @desktopConfig@.
@@ -88,7 +89,7 @@ import qualified Data.Map as M
-- $customizing
-- To customize a desktop config, modify its fields as is illustrated with
--- @defaultConfig@ in "XMonad.Doc.Extending#Extending xmonad".
+-- the default configuration @def@ in "XMonad.Doc.Extending#Extending xmonad".
-- $layouts
-- See also "XMonad.Util.EZConfig" for more options for modifying key bindings.
@@ -163,11 +164,11 @@ import qualified Data.Map as M
-- > adjustEventInput
--
-desktopConfig = ewmh defaultConfig
+desktopConfig = ewmh def
{ startupHook = setDefaultCursor xC_left_ptr
- , layoutHook = desktopLayoutModifiers $ layoutHook defaultConfig
- , manageHook = manageHook defaultConfig <+> manageDocks
- , keys = desktopKeys <+> keys defaultConfig }
+ , layoutHook = desktopLayoutModifiers $ layoutHook def
+ , manageHook = manageHook def <+> manageDocks
+ , keys = desktopKeys <+> keys def }
desktopKeys (XConfig {modMask = modm}) = M.fromList $
[ ((modm, xK_b), sendMessage ToggleStruts) ]
diff --git a/XMonad/Config/Dmwit.hs b/XMonad/Config/Dmwit.hs
index f899b59..08c0b04 100644
--- a/XMonad/Config/Dmwit.hs
+++ b/XMonad/Config/Dmwit.hs
@@ -206,7 +206,7 @@ instance PPrint ScreenId
instance (Show a, Show b) => PPrint (Map a b)
-- }}}
-- main {{{
-dmwitConfig nScreens = defaultConfig {
+dmwitConfig nScreens = def {
borderWidth = 2,
workspaces = withScreens nScreens (map show [1..5]),
terminal = "urxvt",
diff --git a/XMonad/Config/Droundy.hs b/XMonad/Config/Droundy.hs
index 5e0c9c8..8fe7f2d 100644
--- a/XMonad/Config/Droundy.hs
+++ b/XMonad/Config/Droundy.hs
@@ -117,7 +117,7 @@ keys x = M.fromList $
++
zip (zip (repeat (modMask x .|. shiftMask)) [xK_F1..xK_F12]) (map (withNthWorkspace copy) [0..])
-config = ewmh defaultConfig
+config = ewmh def
{ borderWidth = 1 -- Width of the window border in pixels.
, XMonad.workspaces = ["mutt","iceweasel"]
, layoutHook = showWName $ workspaceDir "~" $
@@ -129,7 +129,7 @@ config = ewmh defaultConfig
named "widescreen" ((mytab *||* mytab)
****//* combineTwo Square mytab mytab) -- |||
--mosaic 0.25 0.5
- , manageHook = manageHook defaultConfig <+> manageDocks -- add panel-handling
+ , manageHook = manageHook def <+> manageDocks -- add panel-handling
, terminal = "xterm" -- The preferred terminal program.
, normalBorderColor = "#222222" -- Border color for unfocused windows.
, focusedBorderColor = "#00ff00" -- Border color for focused windows.
diff --git a/XMonad/Config/Sjanssen.hs b/XMonad/Config/Sjanssen.hs
index d941c59..cc9c536 100644
--- a/XMonad/Config/Sjanssen.hs
+++ b/XMonad/Config/Sjanssen.hs
@@ -21,21 +21,21 @@ import XMonad.Layout.TwoPane
import qualified Data.Map as M
sjanssenConfig =
- ewmh $ defaultConfig
+ ewmh $ def
{ terminal = "exec urxvt"
, workspaces = ["irc", "web"] ++ map show [3 .. 9 :: Int]
, mouseBindings = \(XConfig {modMask = modm}) -> M.fromList $
[ ((modm, button1), (\w -> focus w >> mouseMoveWindow w))
, ((modm, button2), (\w -> focus w >> windows W.swapMaster))
, ((modm.|. shiftMask, button1), (\w -> focus w >> mouseResizeWindow w)) ]
- , keys = \c -> mykeys c `M.union` keys defaultConfig c
+ , keys = \c -> mykeys c `M.union` keys def c
, logHook = dynamicLogString sjanssenPP >>= xmonadPropLog
, layoutHook = modifiers layouts
, manageHook = composeAll [className =? x --> doShift w
| (x, w) <- [ ("Firefox", "web")
, ("Ktorrent", "7")
, ("Amarokapp", "7")]]
- <+> manageHook defaultConfig <+> manageDocks <+> manageSpawn
+ <+> manageHook def <+> manageDocks <+> manageSpawn
<+> (isFullscreen --> doFullFloat)
, startupHook = mapM_ spawnOnce spawns
}
diff --git a/XMonad/Doc/Configuring.hs b/XMonad/Doc/Configuring.hs
index 4e3486d..363a4c3 100644
--- a/XMonad/Doc/Configuring.hs
+++ b/XMonad/Doc/Configuring.hs
@@ -84,7 +84,7 @@ some colours:
>
> import XMonad
>
-> main = xmonad $ defaultConfig
+> main = xmonad $ def
> { borderWidth = 2
> , terminal = "urxvt"
> , normalBorderColor = "#cccccc"
diff --git a/XMonad/Doc/Extending.hs b/XMonad/Doc/Extending.hs
index 00d9834..f766962 100644
--- a/XMonad/Doc/Extending.hs
+++ b/XMonad/Doc/Extending.hs
@@ -932,7 +932,7 @@ example, you could write:
> import XMonad
>
-> main = xmonad $ defaultConfig { keys = myKeys }
+> main = xmonad $ def { keys = myKeys }
and provide an appropriate definition of @myKeys@, such as:
@@ -991,18 +991,18 @@ these:
then you can create a new key bindings map by joining the default one
with yours:
-> newKeys x = myKeys x `M.union` keys defaultConfig x
+> newKeys x = myKeys x `M.union` keys def x
Finally, you can use @newKeys@ in the 'XMonad.Core.XConfig.keys' field
of the configuration:
-> main = xmonad $ defaultConfig { keys = newKeys }
+> main = xmonad $ def { keys = newKeys }
Alternatively, the '<+>' operator can be used which in this usage does exactly
the same as the explicit usage of 'M.union' and propagation of the config
argument, thanks to appropriate instances in "Data.Monoid".
-> main = xmonad $ defaultConfig { keys = myKeys <+> keys defaultConfig }
+> main = xmonad $ def { keys = myKeys <+> keys def }
All together, your @~\/.xmonad\/xmonad.hs@ would now look like this:
@@ -1018,7 +1018,7 @@ All together, your @~\/.xmonad\/xmonad.hs@ would now look like this:
> import XMonad.Prompt.XMonad
>
> main :: IO ()
-> main = xmonad $ defaultConfig { keys = myKeys <+> keys defaultConfig }
+> main = xmonad $ def { keys = myKeys <+> keys def }
>
> myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList
> [ ((modm, xK_F12), xmonadPrompt defaultXPConfig)
@@ -1044,7 +1044,7 @@ For example, suppose you want to get rid of @mod-q@ and @mod-shift-q@
to define @newKeys@ as a 'Data.Map.difference' between the default
map and the map of the key bindings you want to remove. Like so:
-> newKeys x = keys defaultConfig x `M.difference` keysToRemove x
+> newKeys x = keys def x `M.difference` keysToRemove x
>
> keysToRemove :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
> keysToRemove x = M.fromList
@@ -1060,7 +1060,7 @@ It is also possible to simply define a list of keys we want to unbind
and then use 'Data.Map.delete' to remove them. In that case we would
write something like:
-> newKeys x = foldr M.delete (keys defaultConfig x) (keysToRemove x)
+> newKeys x = foldr M.delete (keys def x) (keysToRemove x)
>
> keysToRemove :: XConfig Layout -> [(KeyMask, KeySym)]
> keysToRemove x =
@@ -1081,7 +1081,7 @@ Adding and removing key bindings requires simply combining the steps
for removing and adding. Here is an example from
"XMonad.Config.Arossato":
-> defKeys = keys defaultConfig
+> defKeys = keys def
> delKeys x = foldr M.delete (defKeys x) (toRemove x)
> newKeys x = foldr (uncurry M.insert) (delKeys x) (toAdd x)
> -- remove some of the default key bindings
@@ -1125,9 +1125,9 @@ the window you click on like so:
>
> myMouse x = [ (0, button4), (\w -> focus w >> kill) ]
>
-> newMouse x = M.union (mouseBindings defaultConfig x) (M.fromList (myMouse x))
+> newMouse x = M.union (mouseBindings def x) (M.fromList (myMouse x))
>
-> main = xmonad $ defaultConfig { ..., mouseBindings = newMouse, ... }
+> main = xmonad $ def { ..., mouseBindings = newMouse, ... }
Overriding or deleting mouse bindings works similarly. You can also
configure mouse bindings much more easily using the
@@ -1180,7 +1180,7 @@ Then we create the combination of layouts we need:
Now, all we need to do is change the 'XMonad.Core.layoutHook'
field of the 'XMonad.Core.XConfig' record, like so:
-> main = xmonad $ defaultConfig { layoutHook = mylayoutHook }
+> main = xmonad $ def { layoutHook = mylayoutHook }
Thanks to the new combinator, we can apply a layout modifier to a
whole combination of layouts, instead of applying it to each one. For
@@ -1204,7 +1204,7 @@ Our @~\/.xmonad\/xmonad.hs@ will now look like this:
>
> mylayoutHook = Full ||| noBorders (tabbed shrinkText defaultTheme) ||| Accordion
>
-> main = xmonad $ defaultConfig { layoutHook = mylayoutHook }
+> main = xmonad $ def { layoutHook = mylayoutHook }
That's it!
@@ -1256,7 +1256,7 @@ This is another example of 'XMonad.Config.manageHook', taken from
> , resource =? "win" --> doF (W.shift "doc") -- xpdf
> , resource =? "firefox-bin" --> doF (W.shift "web")
> ]
-> newManageHook = myManageHook <+> manageHook defaultConfig
+> newManageHook = myManageHook <+> manageHook def
Again we use 'XMonad.ManageHook.composeAll' to compose a list of
@@ -1318,14 +1318,14 @@ Then we create our own 'XMonad.Config.manageHook':
We can now use the 'XMonad.ManageHook.<+>' combinator to add our
'XMonad.Config.manageHook' to the default one:
-> newManageHook = myManageHook <+> manageHook defaultConfig
+> newManageHook = myManageHook <+> manageHook def
(Of course, if we wanted to completely replace the default
'XMonad.Config.manageHook', this step would not be necessary.) Now,
all we need to do is change the 'XMonad.Core.manageHook' field of the
'XMonad.Core.XConfig' record, like so:
-> main = xmonad defaultConfig { ..., manageHook = newManageHook, ... }
+> main = xmonad def { ..., manageHook = newManageHook, ... }
And we are done.
@@ -1387,7 +1387,7 @@ Then you just need to update the 'XMonad.Core.logHook' field of the
'XMonad.Core.XConfig' record with one of the provided functions. For
example:
-> main = xmonad defaultConfig { logHook = dynamicLog }
+> main = xmonad def { logHook = dynamicLog }
More interesting configurations are also possible; see the
"XMonad.Hooks.DynamicLog" module for more possibilities.
diff --git a/XMonad/Hooks/CurrentWorkspaceOnTop.hs b/XMonad/Hooks/CurrentWorkspaceOnTop.hs
index 2c42413..5b94a8d 100644
--- a/XMonad/Hooks/CurrentWorkspaceOnTop.hs
+++ b/XMonad/Hooks/CurrentWorkspaceOnTop.hs
@@ -33,7 +33,7 @@ import qualified Data.Map as M
--
-- > import XMonad.Hooks.CurrentWorkspaceOnTop
-- >
--- > main = xmonad $ defaultConfig {
+-- > main = xmonad $ def {
-- > ...
-- > logHook = currentWorkspaceOnTop
-- > ...
diff --git a/XMonad/Hooks/DynamicLog.hs b/XMonad/Hooks/DynamicLog.hs
index 0547c80..3bdf5f1 100644
--- a/XMonad/Hooks/DynamicLog.hs
+++ b/XMonad/Hooks/DynamicLog.hs
@@ -88,7 +88,7 @@ import XMonad.Hooks.ManageDocks
--
-- > main = xmonad =<< xmobar myConfig
-- >
--- > myConfig = defaultConfig { ... }
+-- > myConfig = def { ... }
--
-- There is also 'statusBar' if you'd like to use another status bar, or would
-- like to use different formatting options. The 'xmobar', 'dzen', and
@@ -99,7 +99,7 @@ import XMonad.Hooks.ManageDocks
-- ('dynamicLog' or 'dynamicLogXinerama') by simply setting your logHook to the
-- appropriate function, for instance:
--
--- > main = xmonad $ defaultConfig {
+-- > main = xmonad $ def {
-- > ...
-- > logHook = dynamicLog
-- > ...
@@ -124,7 +124,7 @@ import XMonad.Hooks.ManageDocks
-- >
-- > main = do
-- > h <- spawnPipe "xmobar -options -foo -bar"
--- > xmonad $ defaultConfig {
+-- > xmonad $ def {
-- > ...
-- > logHook = dynamicLogWithPP $ defaultPP { ppOutput = hPutStrLn h }
--
@@ -153,7 +153,7 @@ import XMonad.Hooks.ManageDocks
--
-- > main = xmonad =<< dzen myConfig
-- >
--- > myConfig = defaultConfig { ... }
+-- > myConfig = def { ... }
--
-- The intent is that the above config file should provide a nice
-- status bar with minimal effort.
@@ -178,7 +178,7 @@ dzen conf = statusBar ("dzen2 " ++ flags) dzenPP toggleStrutsKey conf
--
-- > main = xmonad =<< xmobar myConfig
-- >
--- > myConfig = defaultConfig { ... }
+-- > myConfig = def { ... }
--
-- This works pretty much the same as 'dzen' function above.
--
diff --git a/XMonad/Hooks/EwmhDesktops.hs b/XMonad/Hooks/EwmhDesktops.hs
index f7f19c3..8b3a644 100644
--- a/XMonad/Hooks/EwmhDesktops.hs
+++ b/XMonad/Hooks/EwmhDesktops.hs
@@ -44,8 +44,8 @@ import XMonad.Util.WindowProperties (getProp32)
-- > import XMonad
-- > import XMonad.Hooks.EwmhDesktops
-- >
--- > main = xmonad $ ewmh defaultConfig{ handleEventHook =
--- > handleEventHook defaultConfig <+> fullscreenEventHook }
+-- > main = xmonad $ ewmh def{ handleEventHook =
+-- > handleEventHook def <+> fullscreenEventHook }
--
-- You may also be interested in 'avoidStruts' from "XMonad.Hooks.ManageDocks".
diff --git a/XMonad/Hooks/FadeInactive.hs b/XMonad/Hooks/FadeInactive.hs
index 71a6fcd..d1e64a6 100644
--- a/XMonad/Hooks/FadeInactive.hs
+++ b/XMonad/Hooks/FadeInactive.hs
@@ -40,7 +40,7 @@ import Control.Monad
-- > myLogHook = fadeInactiveLogHook fadeAmount
-- > where fadeAmount = 0.8
-- >
--- > main = xmonad defaultConfig { logHook = myLogHook }
+-- > main = xmonad def { logHook = myLogHook }
--
-- fadeAmount can be any rational between 0 and 1.
-- you will need to have xcompmgr <http://freedesktop.org/wiki/Software/xapps>
diff --git a/XMonad/Hooks/FadeWindows.hs b/XMonad/Hooks/FadeWindows.hs
index 30e1de4..4b8e62b 100644
--- a/XMonad/Hooks/FadeWindows.hs
+++ b/XMonad/Hooks/FadeWindows.hs
@@ -115,7 +115,7 @@ import Graphics.X11.Xlib.Extras (Event(..))
-- a tight loop trying to fade the popup in). I find it useful to
-- have a key binding to restart the compositing manager; for example,
--
--- main = xmonad $ defaultConfig {
+-- main = xmonad $ def {
-- {- ... -}
-- }
-- `additionalKeysP`
diff --git a/XMonad/Hooks/FloatNext.hs b/XMonad/Hooks/FloatNext.hs
index 93d0eda..f98ea15 100644
--- a/XMonad/Hooks/FloatNext.hs
+++ b/XMonad/Hooks/FloatNext.hs
@@ -53,7 +53,7 @@ hookName = "__float"
--
-- and adding 'floatNextHook' to your 'ManageHook':
--
--- > myManageHook = floatNextHook <+> manageHook defaultConfig
+-- > myManageHook = floatNextHook <+> manageHook def
--
-- The 'floatNext' and 'toggleFloatNext' functions can be used in key
-- bindings to float the next spawned window:
diff --git a/XMonad/Hooks/InsertPosition.hs b/XMonad/Hooks/InsertPosition.hs
index 722c48a..0c6230c 100644
--- a/XMonad/Hooks/InsertPosition.hs
+++ b/XMonad/Hooks/InsertPosition.hs
@@ -31,7 +31,7 @@ import Data.Monoid(Endo(Endo))
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Hooks.InsertPosition
--- > xmonad defaultConfig { manageHook = insertPosition Master Newer <+> myManageHook }
+-- > xmonad def { manageHook = insertPosition Master Newer <+> myManageHook }
--
-- You should you put the manageHooks that use 'doShift' to take effect
-- /before/ 'insertPosition', so that the window order will be consistent.
diff --git a/XMonad/Hooks/ManageHelpers.hs b/XMonad/Hooks/ManageHelpers.hs
index 093e0cb..de03b55 100644
--- a/XMonad/Hooks/ManageHelpers.hs
+++ b/XMonad/Hooks/ManageHelpers.hs
@@ -13,7 +13,7 @@
--
-- > import XMonad.Hooks.ManageHelpers
-- > main =
--- > xmonad defaultConfig{
+-- > xmonad def{
-- > ...
-- > manageHook = composeOne [
-- > isKDETrayWindow -?> doIgnore,
diff --git a/XMonad/Hooks/Minimize.hs b/XMonad/Hooks/Minimize.hs
index dd9567c..5e2ab03 100644
--- a/XMonad/Hooks/Minimize.hs
+++ b/XMonad/Hooks/Minimize.hs
@@ -33,8 +33,8 @@ import XMonad.Layout.Minimize
-- >
-- > myHandleEventHook = minimizeEventHook
-- > myLayout = minimize (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout
--- > , handleEventHook = myHandleEventHook }
+-- > main = xmonad def { layoutHook = myLayout
+-- > , handleEventHook = myHandleEventHook }
minimizeEventHook :: Event -> X All
minimizeEventHook (ClientMessageEvent {ev_window = w,
diff --git a/XMonad/Hooks/Place.hs b/XMonad/Hooks/Place.hs
index 65d3e49..e1138ce 100644
--- a/XMonad/Hooks/Place.hs
+++ b/XMonad/Hooks/Place.hs
@@ -59,8 +59,8 @@ import Control.Monad.Trans (lift)
--
-- and adding 'placeHook' to your 'manageHook', for example:
--
--- > main = xmonad $ defaultConfig { manageHook = placeHook simpleSmart
--- > <+> manageHook defaultConfig }
+-- > main = xmonad $ def { manageHook = placeHook simpleSmart
+-- > <+> manageHook def }
--
-- Note that 'placeHook' should be applied after most other hooks, especially hooks
-- such as 'doFloat' and 'doShift'. Since hooks combined with '<+>' are applied from
diff --git a/XMonad/Hooks/PositionStoreHooks.hs b/XMonad/Hooks/PositionStoreHooks.hs
index 9ebcbb4..0818b1c 100644
--- a/XMonad/Hooks/PositionStoreHooks.hs
+++ b/XMonad/Hooks/PositionStoreHooks.hs
@@ -58,12 +58,12 @@ import qualified Data.Set as S
-- otherwise use 'Just defaultTheme' or similar to inform the module about the
-- decoration theme used.
--
--- > myManageHook = positionStoreManageHook Nothing <+> manageHook defaultConfig
+-- > myManageHook = positionStoreManageHook Nothing <+> manageHook def
-- > myHandleEventHook = positionStoreEventHook
-- >
--- > main = xmonad defaultConfig { manageHook = myManageHook
--- > , handleEventHook = myHandleEventHook
--- > }
+-- > main = xmonad def { manageHook = myManageHook
+-- > , handleEventHook = myHandleEventHook
+-- > }
--
positionStoreManageHook :: Maybe Theme -> ManageHook
diff --git a/XMonad/Hooks/RestoreMinimized.hs b/XMonad/Hooks/RestoreMinimized.hs
index 3759ce5..05aa846 100644
--- a/XMonad/Hooks/RestoreMinimized.hs
+++ b/XMonad/Hooks/RestoreMinimized.hs
@@ -34,7 +34,7 @@ import XMonad.Layout.Minimize
-- >
-- > myHandleEventHook = restoreMinimizedEventHook
-- >
--- > main = xmonad defaultConfig { handleEventHook = myHandleEventHook }
+-- > main = xmonad def { handleEventHook = myHandleEventHook }
data RestoreMinimized = RestoreMinimized deriving ( Show, Read )
diff --git a/XMonad/Hooks/Script.hs b/XMonad/Hooks/Script.hs
index 82e4868..b298920 100644
--- a/XMonad/Hooks/Script.hs
+++ b/XMonad/Hooks/Script.hs
@@ -34,7 +34,7 @@ import XMonad
-- For example, if you wanted to run the hook "startup" in your script every
-- time your startup hook ran, you could modify your xmonad config as such:
--
--- > main = xmonad $ defaultConfig {
+-- > main = xmonad $ def {
-- > ...
-- > startupHook = execScriptHook "startup"
-- > ...
diff --git a/XMonad/Hooks/ServerMode.hs b/XMonad/Hooks/ServerMode.hs
index c072f53..bbe1097 100644
--- a/XMonad/Hooks/ServerMode.hs
+++ b/XMonad/Hooks/ServerMode.hs
@@ -79,7 +79,7 @@ import XMonad.Actions.Commands
--
-- Then edit your @handleEventHook@ by adding the 'serverModeEventHook':
--
--- > main = xmonad defaultConfig { handleEventHook = serverModeEventHook }
+-- > main = xmonad def { handleEventHook = serverModeEventHook }
--
data ServerMode = ServerMode deriving ( Show, Read )
diff --git a/XMonad/Hooks/ToggleHook.hs b/XMonad/Hooks/ToggleHook.hs
index 2b1e611..a497678 100644
--- a/XMonad/Hooks/ToggleHook.hs
+++ b/XMonad/Hooks/ToggleHook.hs
@@ -85,12 +85,12 @@ modify' n f = XS.modify (HookState . setter . hooks)
-- and adding 'toggleHook name hook' to your 'ManageHook' where @name@ is the
-- name of the hook and @hook@ is the hook to execute based on the state.
--
--- > myManageHook = toggleHook "float" doFloat <+> manageHook defaultConfig
+-- > myManageHook = toggleHook "float" doFloat <+> manageHook def
--
-- Additionally, toggleHook' is provided to toggle between two hooks (rather
-- than on/off).
--
--- > myManageHook = toggleHook' "oldfocus" (const id) W.focusWindow <+> manageHook defaultConfig
+-- > myManageHook = toggleHook' "oldfocus" (const id) W.focusWindow <+> manageHook def
--
-- The 'hookNext' and 'toggleHookNext' functions can be used in key
-- bindings to set whether the hook is applied or not.
diff --git a/XMonad/Hooks/UrgencyHook.hs b/XMonad/Hooks/UrgencyHook.hs
index 7ef09b5..06a4910 100644
--- a/XMonad/Hooks/UrgencyHook.hs
+++ b/XMonad/Hooks/UrgencyHook.hs
@@ -106,7 +106,7 @@ import Foreign.C.Types (CLong)
-- 'withUrgencyHook'. For example:
--
-- > main = xmonad $ withUrgencyHook dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] }
--- > $ defaultConfig
+-- > $ def
--
-- This will pop up a dzen bar for five seconds telling you you've got an
-- urgent window.
@@ -118,7 +118,7 @@ import Foreign.C.Types (CLong)
-- extra popup, install NoUrgencyHook, as so:
--
-- > main = xmonad $ withUrgencyHook NoUrgencyHook
--- > $ defaultConfig
+-- > $ def
--
-- Now, your "XMonad.Hooks.DynamicLog" must be set up to display the urgent
-- windows. If you're using the 'dzen' or 'dzenPP' functions from that module,
@@ -259,7 +259,7 @@ minutes secs = secs * 60
-- | The default 'UrgencyConfig'. suppressWhen = Visible, remindWhen = Dont.
-- Use a variation of this in your config just as you use a variation of
--- defaultConfig for your xmonad definition.
+-- 'def' for your xmonad definition.
urgencyConfig :: UrgencyConfig
urgencyConfig = UrgencyConfig { suppressWhen = Visible, remindWhen = Dont }
diff --git a/XMonad/Hooks/WorkspaceByPos.hs b/XMonad/Hooks/WorkspaceByPos.hs
index b7f1323..9d577f5 100644
--- a/XMonad/Hooks/WorkspaceByPos.hs
+++ b/XMonad/Hooks/WorkspaceByPos.hs
@@ -33,9 +33,9 @@ import Control.Monad.Error ((<=<),guard,lift,runErrorT,throwError)
--
-- > import XMonad.Hooks.WorkspaceByPos
-- >
--- > myManageHook = workspaceByPos <+> manageHook defaultConfig
+-- > myManageHook = workspaceByPos <+> manageHook def
-- >
--- > main = xmonad defaultConfig { manageHook = myManageHook }
+-- > main = xmonad def { manageHook = myManageHook }
workspaceByPos :: ManageHook
workspaceByPos = (maybe idHook doShift <=< liftX . needsMoving) =<< ask
diff --git a/XMonad/Hooks/WorkspaceHistory.hs b/XMonad/Hooks/WorkspaceHistory.hs
index ed41f42..8080619 100644
--- a/XMonad/Hooks/WorkspaceHistory.hs
+++ b/XMonad/Hooks/WorkspaceHistory.hs
@@ -38,7 +38,7 @@ import qualified XMonad.Util.ExtensibleState as XS
--
-- Then add the hook to your 'logHook':
--
--- > main = xmonad $ defaultConfig
+-- > main = xmonad $ def
-- > { ...
-- > , logHook = ... >> workspaceHistoryHook >> ...
-- > , ...
diff --git a/XMonad/Layout/Accordion.hs b/XMonad/Layout/Accordion.hs
index 90268c8..dc75c93 100644
--- a/XMonad/Layout/Accordion.hs
+++ b/XMonad/Layout/Accordion.hs
@@ -31,7 +31,7 @@ import Data.Ratio
-- Then edit your @layoutHook@ by adding the Accordion layout:
--
-- > myLayout = Accordion ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/BorderResize.hs b/XMonad/Layout/BorderResize.hs
index d67d022..21e7e92 100644
--- a/XMonad/Layout/BorderResize.hs
+++ b/XMonad/Layout/BorderResize.hs
@@ -40,7 +40,7 @@ import qualified Data.Map as M
--
-- > import XMonad.Layout.BorderResize
-- > myLayout = borderResize (... layout setup that reacts to SetGeometry ...)
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
type BorderBlueprint = (Rectangle, Glyph, BorderType)
diff --git a/XMonad/Layout/BoringWindows.hs b/XMonad/Layout/BoringWindows.hs
index 22517ee..cbea6a2 100644
--- a/XMonad/Layout/BoringWindows.hs
+++ b/XMonad/Layout/BoringWindows.hs
@@ -49,7 +49,7 @@ import qualified XMonad.StackSet as W
-- Then edit your @layoutHook@ by adding the layout modifier:
--
-- > myLayout = boringWindows (Full ||| etc..)
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- Then to your keybindings, add:
--
diff --git a/XMonad/Layout/ButtonDecoration.hs b/XMonad/Layout/ButtonDecoration.hs
index 8385c07..c37d6ce 100644
--- a/XMonad/Layout/ButtonDecoration.hs
+++ b/XMonad/Layout/ButtonDecoration.hs
@@ -40,8 +40,8 @@ import XMonad.Layout.DecorationAddons
-- Then edit your @layoutHook@ by adding the ButtonDecoration to
-- your layout:
--
--- > myL = buttonDeco shrinkText defaultThemeWithButtons (layoutHook defaultConfig)
--- > main = xmonad defaultConfig { layoutHook = myL }
+-- > myL = buttonDeco shrinkText defaultThemeWithButtons (layoutHook def)
+-- > main = xmonad def { layoutHook = myL }
--
buttonDeco :: (Eq a, Shrinker s) => s -> Theme
diff --git a/XMonad/Layout/Circle.hs b/XMonad/Layout/Circle.hs
index 5bd10d2..f9f09fe 100644
--- a/XMonad/Layout/Circle.hs
+++ b/XMonad/Layout/Circle.hs
@@ -32,7 +32,7 @@ import XMonad.StackSet (integrate, peek)
-- Then edit your @layoutHook@ by adding the Circle layout:
--
-- > myLayout = Circle ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Cross.hs b/XMonad/Layout/Cross.hs
index 9f37b06..b1f1112 100644
--- a/XMonad/Layout/Cross.hs
+++ b/XMonad/Layout/Cross.hs
@@ -29,7 +29,7 @@ import Control.Monad( msum )
-- Then edit your @layoutHook@ by adding one of the Cross layouts:
--
-- > myLayout = simpleCross ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- apply a factor to a Rectangle Dimension
diff --git a/XMonad/Layout/DecorationMadness.hs b/XMonad/Layout/DecorationMadness.hs
index 0ad373b..c463636 100644
--- a/XMonad/Layout/DecorationMadness.hs
+++ b/XMonad/Layout/DecorationMadness.hs
@@ -105,7 +105,7 @@ import XMonad.Layout.SimpleFloat
--
-- Then edit your @layoutHook@ by adding the layout you want:
--
--- > main = xmonad defaultConfig { layoutHook = someMadLayout }
+-- > main = xmonad def { layoutHook = someMadLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Dishes.hs b/XMonad/Layout/Dishes.hs
index 89723b5..805cc72 100644
--- a/XMonad/Layout/Dishes.hs
+++ b/XMonad/Layout/Dishes.hs
@@ -33,7 +33,7 @@ import Control.Monad (ap)
-- Then edit your @layoutHook@ by adding the Dishes layout:
--
-- > myLayout = Dishes 2 (1/6) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/DragPane.hs b/XMonad/Layout/DragPane.hs
index 37d70b5..720eaee 100644
--- a/XMonad/Layout/DragPane.hs
+++ b/XMonad/Layout/DragPane.hs
@@ -41,7 +41,7 @@ import XMonad.Util.XUtils
-- Then edit your @layoutHook@ by adding the DragPane layout:
--
-- > myLayout = dragPane Horizontal 0.1 0.5 ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Drawer.hs b/XMonad/Layout/Drawer.hs
index 9ced1a2..1dc0975 100644
--- a/XMonad/Layout/Drawer.hs
+++ b/XMonad/Layout/Drawer.hs
@@ -48,7 +48,7 @@ import XMonad.Layout.Reflect
-- > where
-- > drawer = simpleDrawer 0.01 0.3 (ClassName "Rhythmbox" `Or` ClassName "Xchat")
-- >
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- This will place the Rhythmbox and Xchat windows in at the top of the screen
-- only when using the 'Tall' layout. See "XMonad.Util.WindowProperties" for
diff --git a/XMonad/Layout/DwmStyle.hs b/XMonad/Layout/DwmStyle.hs
index b6c8196..6bba823 100644
--- a/XMonad/Layout/DwmStyle.hs
+++ b/XMonad/Layout/DwmStyle.hs
@@ -36,8 +36,8 @@ import XMonad.Layout.Decoration
-- Then edit your @layoutHook@ by adding the DwmStyle decoration to
-- your layout:
--
--- > myL = dwmStyle shrinkText defaultTheme (layoutHook defaultConfig)
--- > main = xmonad defaultConfig { layoutHook = myL }
+-- > myL = dwmStyle shrinkText defaultTheme (layoutHook def)
+-- > main = xmonad def { layoutHook = myL }
--
-- For more detailed instructions on editing the layoutHook see:
--
@@ -50,17 +50,17 @@ import XMonad.Layout.Decoration
--
-- and
--
--- > myL = dwmStyle shrinkText myDWConfig (layoutHook defaultConfig)
+-- > myL = dwmStyle shrinkText myDWConfig (layoutHook def)
--
-- A complete xmonad.hs file for this would therefore be:
--
-- > import XMonad
-- > import XMonad.Layout.DwmStyle
-- >
--- > main = xmonad defaultConfig {
+-- > main = xmonad def {
-- > layoutHook =
-- > dwmStyle shrinkText defaultTheme
--- > (layoutHook defaultConfig)
+-- > (layoutHook def)
-- > }
--
diff --git a/XMonad/Layout/FixedColumn.hs b/XMonad/Layout/FixedColumn.hs
index ad0c004..97bb36b 100644
--- a/XMonad/Layout/FixedColumn.hs
+++ b/XMonad/Layout/FixedColumn.hs
@@ -43,7 +43,7 @@ import XMonad.StackSet as W
-- Then edit your @layoutHook@ by adding the FixedColumn layout:
--
-- > myLayout = FixedColumn 1 20 80 10 ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Fullscreen.hs b/XMonad/Layout/Fullscreen.hs
index a60a742..386baab 100644
--- a/XMonad/Layout/Fullscreen.hs
+++ b/XMonad/Layout/Fullscreen.hs
@@ -53,9 +53,9 @@ import Control.Arrow (second)
-- To use this module, add 'fullscreenEventHook' and 'fullscreenManageHook'
-- to your config, i.e.
--
--- > xmonad defaultconfig { handleEventHook = fullscreenEventHook,
--- > manageHook = fullscreenManageHook,
--- > layoutHook = myLayouts }
+-- > xmonad def { handleEventHook = fullscreenEventHook,
+-- > manageHook = fullscreenManageHook,
+-- > layoutHook = myLayouts }
--
-- Now you can use layouts that respect fullscreen, for example the
-- provided 'fullscreenFull':
diff --git a/XMonad/Layout/Grid.hs b/XMonad/Layout/Grid.hs
index a2d39e0..845fa80 100644
--- a/XMonad/Layout/Grid.hs
+++ b/XMonad/Layout/Grid.hs
@@ -31,7 +31,7 @@ import XMonad.StackSet
-- Then edit your @layoutHook@ by adding the Grid layout:
--
-- > myLayout = Grid ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- You can also specify an aspect ratio for Grid to strive for with the
-- GridRatio constructor. For example, if you want Grid to try to make a grid
diff --git a/XMonad/Layout/HintedGrid.hs b/XMonad/Layout/HintedGrid.hs
index e7e09d5..5575d73 100644
--- a/XMonad/Layout/HintedGrid.hs
+++ b/XMonad/Layout/HintedGrid.hs
@@ -42,7 +42,7 @@ infixr 9 .
-- Then edit your @layoutHook@ by adding the 'Grid' layout:
--
-- > myLayout = Grid False ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- You can also specify an aspect ratio for Grid to strive for with the
-- GridRatio constructor:
diff --git a/XMonad/Layout/HintedTile.hs b/XMonad/Layout/HintedTile.hs
index c005889..fc3a856 100644
--- a/XMonad/Layout/HintedTile.hs
+++ b/XMonad/Layout/HintedTile.hs
@@ -38,7 +38,7 @@ import Control.Monad
-- > nmaster = 1
-- > ratio = 1/2
-- > delta = 3/100
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- Because both Xmonad and Xmonad.Layout.HintedTile define Tall,
-- you need to disambiguate Tall. If you are replacing the
diff --git a/XMonad/Layout/IM.hs b/XMonad/Layout/IM.hs
index e45fe2a..1414f1a 100644
--- a/XMonad/Layout/IM.hs
+++ b/XMonad/Layout/IM.hs
@@ -45,7 +45,7 @@ import XMonad.Util.WindowProperties
-- to consider is Tabbed layout).
--
-- > myLayout = withIM (1%7) (ClassName "Tkabber") Grid ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- Here @1%7@ is the part of the screen which your roster will occupy,
-- @ClassName \"Tkabber\"@ tells xmonad which window is actually your roster.
diff --git a/XMonad/Layout/ImageButtonDecoration.hs b/XMonad/Layout/ImageButtonDecoration.hs
index 0a44fe7..1737964 100644
--- a/XMonad/Layout/ImageButtonDecoration.hs
+++ b/XMonad/Layout/ImageButtonDecoration.hs
@@ -50,8 +50,8 @@ import XMonad.Layout.Maximize
-- Then edit your @layoutHook@ by adding the ImageButtonDecoration to
-- your layout:
--
--- > myL = imageButtonDeco shrinkText defaultThemeWithImageButtons (layoutHook defaultConfig)
--- > main = xmonad defaultConfig { layoutHook = myL }
+-- > myL = imageButtonDeco shrinkText defaultThemeWithImageButtons (layoutHook def)
+-- > main = xmonad def { layoutHook = myL }
--
-- The buttons' dimension and placements
diff --git a/XMonad/Layout/IndependentScreens.hs b/XMonad/Layout/IndependentScreens.hs
index b240f29..37be05b 100644
--- a/XMonad/Layout/IndependentScreens.hs
+++ b/XMonad/Layout/IndependentScreens.hs
@@ -45,7 +45,7 @@ import XMonad.Hooks.DynamicLog
--
-- You can define your workspaces by calling @withScreens@:
--
--- > myConfig = defaultConfig { workspaces = withScreens 2 ["web", "email", "irc"] }
+-- > myConfig = def { workspaces = withScreens 2 ["web", "email", "irc"] }
--
-- This will create \"physical\" workspaces with distinct internal names for
-- each (screen, virtual workspace) pair.
@@ -114,9 +114,9 @@ onCurrentScreen f vws = screen . current >>= f . flip marshall vws
--
-- > main = do
-- > nScreens <- countScreens
--- > xmonad $ defaultConfig {
+-- > xmonad $ def {
-- > ...
--- > workspaces = withScreens nScreens (workspaces defaultConfig),
+-- > workspaces = withScreens nScreens (workspaces def),
-- > ...
-- > }
--
diff --git a/XMonad/Layout/LayoutBuilder.hs b/XMonad/Layout/LayoutBuilder.hs
index 7ac2b80..016eabd 100644
--- a/XMonad/Layout/LayoutBuilder.hs
+++ b/XMonad/Layout/LayoutBuilder.hs
@@ -50,7 +50,7 @@ import Data.Maybe (isJust)
-- > $ (layoutN 1 (absBox (-200) 0 0 0) Nothing $ simpleTabbed)
-- > $ (layoutAll (absBox 0 0 (-512-200) 0) $ simpleTabbed)
-- > ) ||| Full ||| etc...
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- This will produce a layout similar to DragPane, but with the possibility to have multiple windows in the left half
-- and tabs that show the available windows. It will also produce a layout similar to ThreeColMid and a special layout
diff --git a/XMonad/Layout/LayoutCombinators.hs b/XMonad/Layout/LayoutCombinators.hs
index c8f19df..b0dce28 100644
--- a/XMonad/Layout/LayoutCombinators.hs
+++ b/XMonad/Layout/LayoutCombinators.hs
@@ -68,7 +68,7 @@ import XMonad.Layout.DragPane
-- example:
--
-- > myLayout = (Tall 1 (3/100) (1/2) *//* Full) ||| (Tall 1 (3/100) (1/2) ***||** Full) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the @layoutHook@ see:
--
diff --git a/XMonad/Layout/LayoutHints.hs b/XMonad/Layout/LayoutHints.hs
index c93b054..864cf6c 100644
--- a/XMonad/Layout/LayoutHints.hs
+++ b/XMonad/Layout/LayoutHints.hs
@@ -54,7 +54,7 @@ import qualified Data.Set as Set
-- to some layout:
--
-- > myLayout = layoutHints (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- Or, to center the adapted window in its available area:
--
@@ -74,8 +74,8 @@ import qualified Data.Set as Set
--
-- > myHandleEventHook = hintsEventHook <+> ...
-- >
--- > main = xmonad defaultConfig { handleEventHook = myHandleEventHook
--- > , ... }
+-- > main = xmonad def { handleEventHook = myHandleEventHook
+-- > , ... }
layoutHints :: (LayoutClass l a) => l a -> ModifiedLayout LayoutHints l a
layoutHints = ModifiedLayout (LayoutHints (0, 0))
diff --git a/XMonad/Layout/LimitWindows.hs b/XMonad/Layout/LimitWindows.hs
index 025a021..b0f89f8 100644
--- a/XMonad/Layout/LimitWindows.hs
+++ b/XMonad/Layout/LimitWindows.hs
@@ -47,7 +47,7 @@ import Data.Maybe(fromJust)
-- > import XMonad.Layout.LimitWindows
--
-- > myLayout = limitWindows 6 $ Tall 1 0.03 0.5 ||| Full ||| RandomOtherLayout...
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- You may also be interested in dynamically changing the number dynamically,
-- by binding keys to the 'increaseLimit', 'decreaseLimit', or 'setLimit'
diff --git a/XMonad/Layout/MagicFocus.hs b/XMonad/Layout/MagicFocus.hs
index 5e45d71..bc9cbcd 100644
--- a/XMonad/Layout/MagicFocus.hs
+++ b/XMonad/Layout/MagicFocus.hs
@@ -41,8 +41,8 @@ import qualified Data.Map as M
-- modifier:
--
-- > myLayout = magicFocus (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout,
--- > handleEventHook = promoteWarp }
+-- > main = xmonad def { layoutHook = myLayout,
+-- > handleEventHook = promoteWarp }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Magnifier.hs b/XMonad/Layout/Magnifier.hs
index 685830e..90a577b 100644
--- a/XMonad/Layout/Magnifier.hs
+++ b/XMonad/Layout/Magnifier.hs
@@ -44,7 +44,7 @@ import XMonad.Util.XUtils
-- to some layout:
--
-- > myLayout = magnifier (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- By default magnifier increases the focused window's size by 1.5.
-- You can also use:
diff --git a/XMonad/Layout/Maximize.hs b/XMonad/Layout/Maximize.hs
index f56bf07..589b962 100644
--- a/XMonad/Layout/Maximize.hs
+++ b/XMonad/Layout/Maximize.hs
@@ -36,7 +36,7 @@ import Data.List ( partition )
-- Then edit your @layoutHook@ by adding the Maximize layout modifier:
--
-- > myLayout = maximize (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Minimize.hs b/XMonad/Layout/Minimize.hs
index 28202c0..8f80090 100644
--- a/XMonad/Layout/Minimize.hs
+++ b/XMonad/Layout/Minimize.hs
@@ -41,7 +41,7 @@ import Foreign.C.Types (CLong)
-- Then edit your @layoutHook@ by adding the Minimize layout modifier:
--
-- > myLayout = minimize (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Mosaic.hs b/XMonad/Layout/Mosaic.hs
index f993c7d..05655d4 100644
--- a/XMonad/Layout/Mosaic.hs
+++ b/XMonad/Layout/Mosaic.hs
@@ -49,7 +49,7 @@ import Data.Monoid(Monoid,mempty, mappend)
-- Then edit your @layoutHook@ by adding the Mosaic layout:
--
-- > myLayout = mosaic 2 [3,2] ||| Full ||| etc..
--- > main = xmonad $ defaultConfig { layoutHook = myLayout }
+-- > main = xmonad $ def { layoutHook = myLayout }
--
-- Unfortunately, infinite lists break serialization, so don't use them. And if
-- the list is too short, it is extended with @++ repeat 1@, which covers the
diff --git a/XMonad/Layout/MosaicAlt.hs b/XMonad/Layout/MosaicAlt.hs
index 5f9753e..b0bc1b4 100644
--- a/XMonad/Layout/MosaicAlt.hs
+++ b/XMonad/Layout/MosaicAlt.hs
@@ -45,7 +45,7 @@ import Data.Ratio
-- Then edit your @layoutHook@ by adding the MosaicAlt layout:
--
-- > myLayout = MosaicAlt M.empty ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/MouseResizableTile.hs b/XMonad/Layout/MouseResizableTile.hs
index 1b6e558..277dfde 100644
--- a/XMonad/Layout/MouseResizableTile.hs
+++ b/XMonad/Layout/MouseResizableTile.hs
@@ -48,7 +48,7 @@ import Control.Applicative((<$>))
-- will not work correctly here because of the use of the mouse.)
--
-- > myLayout = mouseResizableTile ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
--
-- For more detailed instructions on editing the layoutHook see:
diff --git a/XMonad/Layout/MultiColumns.hs b/XMonad/Layout/MultiColumns.hs
index c68f57b..bea4be3 100644
--- a/XMonad/Layout/MultiColumns.hs
+++ b/XMonad/Layout/MultiColumns.hs
@@ -35,12 +35,12 @@ import Control.Monad
-- Then edit your @layoutHook@ by adding the multiCol layout:
--
-- > myLayouts = multiCol [1] 4 0.01 0.5 ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayouts }
+-- > main = xmonad def { layoutHook = myLayouts }
--
-- Or alternatively:
--
-- > myLayouts = Mirror (multiCol [1] 2 0.01 (-0.25)) ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayouts }
+-- > main = xmonad def { layoutHook = myLayouts }
--
-- The maximum number of windows in a column can be controlled using the
-- IncMasterN messages and the column containing the focused window will be
diff --git a/XMonad/Layout/Named.hs b/XMonad/Layout/Named.hs
index 25ae437..57b0f33 100644
--- a/XMonad/Layout/Named.hs
+++ b/XMonad/Layout/Named.hs
@@ -34,7 +34,7 @@ import XMonad.Layout.Renamed
-- to some layout:
--
-- > myLayout = named "real big" Full ||| (nameTail $ named "real big" $ Full) ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/NoFrillsDecoration.hs b/XMonad/Layout/NoFrillsDecoration.hs
index c6cf122..722c13c 100644
--- a/XMonad/Layout/NoFrillsDecoration.hs
+++ b/XMonad/Layout/NoFrillsDecoration.hs
@@ -37,8 +37,8 @@ import XMonad.Layout.SimpleDecoration
-- Then edit your @layoutHook@ by adding the NoFrillsDecoration to
-- your layout:
--
--- > myL = noFrillsDeco shrinkText defaultTheme (layoutHook defaultConfig)
--- > main = xmonad defaultConfig { layoutHook = myL }
+-- > myL = noFrillsDeco shrinkText defaultTheme (layoutHook def)
+-- > main = xmonad def { layoutHook = myL }
--
-- | Add very simple decorations to windows of a layout.
diff --git a/XMonad/Layout/PositionStoreFloat.hs b/XMonad/Layout/PositionStoreFloat.hs
index ea38a00..d793178 100644
--- a/XMonad/Layout/PositionStoreFloat.hs
+++ b/XMonad/Layout/PositionStoreFloat.hs
@@ -46,7 +46,7 @@ import Data.List(nub)
--
-- > myLayouts = floatingDeco $ borderResize $ positionStoreFloat ||| etc..
-- > where floatingDeco l = noFrillsDeco shrinkText defaultTheme l
--- > main = xmonad defaultConfig { layoutHook = myLayouts }
+-- > main = xmonad def { layoutHook = myLayouts }
--
-- See the documentation of "XMonad.Hooks.PositionStoreHooks" on how
-- to add the support hooks.
diff --git a/XMonad/Layout/ResizableTile.hs b/XMonad/Layout/ResizableTile.hs
index 20a5ea4..325779c 100644
--- a/XMonad/Layout/ResizableTile.hs
+++ b/XMonad/Layout/ResizableTile.hs
@@ -34,7 +34,7 @@ import Data.List ((\\))
-- Then edit your @layoutHook@ by adding the ResizableTile layout:
--
-- > myLayout = ResizableTall 1 (3/100) (1/2) [] ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Roledex.hs b/XMonad/Layout/Roledex.hs
index cc1ca50..5d82d5f 100644
--- a/XMonad/Layout/Roledex.hs
+++ b/XMonad/Layout/Roledex.hs
@@ -33,7 +33,7 @@ import Data.Ratio
-- Then edit your @layoutHook@ by adding the Roledex layout:
--
-- > myLayout = Roledex ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/ShowWName.hs b/XMonad/Layout/ShowWName.hs
index 59b0d70..827dc59 100644
--- a/XMonad/Layout/ShowWName.hs
+++ b/XMonad/Layout/ShowWName.hs
@@ -34,8 +34,8 @@ import XMonad.Util.XUtils
-- @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.ShowWName
--- > myLayout = layoutHook defaultConfig
--- > main = xmonad defaultConfig { layoutHook = showWName myLayout }
+-- > myLayout = layoutHook def
+-- > main = xmonad def { layoutHook = showWName myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/SimpleDecoration.hs b/XMonad/Layout/SimpleDecoration.hs
index c969744..2006b21 100644
--- a/XMonad/Layout/SimpleDecoration.hs
+++ b/XMonad/Layout/SimpleDecoration.hs
@@ -38,8 +38,8 @@ import XMonad.Layout.Decoration
-- Then edit your @layoutHook@ by adding the SimpleDecoration decoration to
-- your layout:
--
--- > myL = simpleDeco shrinkText defaultTheme (layoutHook defaultConfig)
--- > main = xmonad defaultConfig { layoutHook = myL }
+-- > myL = simpleDeco shrinkText defaultTheme (layoutHook def)
+-- > main = xmonad def { layoutHook = myL }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/SimpleFloat.hs b/XMonad/Layout/SimpleFloat.hs
index e536e40..f12840e 100644
--- a/XMonad/Layout/SimpleFloat.hs
+++ b/XMonad/Layout/SimpleFloat.hs
@@ -39,7 +39,7 @@ import XMonad.Layout.WindowArranger
-- Then edit your @layoutHook@ by adding the SimpleFloat layout:
--
-- > myLayout = simpleFloat ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Simplest.hs b/XMonad/Layout/Simplest.hs
index a167c68..77b5f1f 100644
--- a/XMonad/Layout/Simplest.hs
+++ b/XMonad/Layout/Simplest.hs
@@ -30,7 +30,7 @@ import qualified XMonad.StackSet as S
-- Then edit your @layoutHook@ by adding the Simplest layout:
--
-- > myLayout = Simplest ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/SimplestFloat.hs b/XMonad/Layout/SimplestFloat.hs
index f9433ee..8e98342 100644
--- a/XMonad/Layout/SimplestFloat.hs
+++ b/XMonad/Layout/SimplestFloat.hs
@@ -34,7 +34,7 @@ import XMonad.Util.XUtils (fi)
-- Then edit your @layoutHook@ by adding the SimplestFloat layout:
--
-- > myLayout = simplestFloat ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Spiral.hs b/XMonad/Layout/Spiral.hs
index a57d5f8..1527abc 100644
--- a/XMonad/Layout/Spiral.hs
+++ b/XMonad/Layout/Spiral.hs
@@ -37,7 +37,7 @@ import XMonad.StackSet ( integrate )
-- Then edit your @layoutHook@ by adding the Spiral layout:
--
-- > myLayout = spiral (6/7) ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/StackTile.hs b/XMonad/Layout/StackTile.hs
index a86cc0e..518f855 100644
--- a/XMonad/Layout/StackTile.hs
+++ b/XMonad/Layout/StackTile.hs
@@ -33,7 +33,7 @@ import Control.Monad
-- Then edit your @layoutHook@ by adding the StackTile layout:
--
-- > myLayout = StackTile 1 (3/100) (1/2) ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/SubLayouts.hs b/XMonad/Layout/SubLayouts.hs
index 5fd1375..73cea67 100644
--- a/XMonad/Layout/SubLayouts.hs
+++ b/XMonad/Layout/SubLayouts.hs
@@ -123,7 +123,7 @@ import Data.Map(Map)
--
-- > myLayout = windowNavigation $ subTabbed $ boringWindows $
-- > Tall 1 (3/100) (1/2) ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- "XMonad.Layout.WindowNavigation" is used to specify which windows to merge,
-- and it is not integrated into the modifier because it can be configured, and
diff --git a/XMonad/Layout/TabBarDecoration.hs b/XMonad/Layout/TabBarDecoration.hs
index f8be09c..3a61996 100644
--- a/XMonad/Layout/TabBarDecoration.hs
+++ b/XMonad/Layout/TabBarDecoration.hs
@@ -36,7 +36,7 @@ import XMonad.Prompt ( XPPosition (..) )
--
-- Then edit your @layoutHook@ by adding the layout you want:
--
--- > main = xmonad defaultConfig { layoutHook = simpleTabBar $ layoutHook defaultConfig}
+-- > main = xmonad def { layoutHook = simpleTabBar $ layoutHook def}
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Tabbed.hs b/XMonad/Layout/Tabbed.hs
index e8455ed..c140984 100644
--- a/XMonad/Layout/Tabbed.hs
+++ b/XMonad/Layout/Tabbed.hs
@@ -51,7 +51,7 @@ import XMonad.Layout.Simplest ( Simplest(Simplest) )
--
-- and then:
--
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- This layout has hardcoded behaviour for mouse clicks on tab decorations:
-- Left click on the tab switches focus to that window.
@@ -82,7 +82,7 @@ import XMonad.Layout.Simplest ( Simplest(Simplest) )
--
-- > import XMonad
-- > import XMonad.Layout.Tabbed
--- > main = xmonad defaultConfig { layoutHook = simpleTabbed }
+-- > main = xmonad def { layoutHook = simpleTabbed }
simpleTabbed :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbed = tabbed shrinkText defaultTheme
diff --git a/XMonad/Layout/ThreeColumns.hs b/XMonad/Layout/ThreeColumns.hs
index 58a625a..0a353f9 100644
--- a/XMonad/Layout/ThreeColumns.hs
+++ b/XMonad/Layout/ThreeColumns.hs
@@ -39,7 +39,7 @@ import Control.Monad
-- Then edit your @layoutHook@ by adding the ThreeCol layout:
--
-- > myLayout = ThreeCol 1 (3/100) (1/2) ||| ThreeColMid 1 (3/100) (1/2) ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- The first argument specifies how many windows initially appear in the main
-- window. The second argument argument specifies the amount to resize while
diff --git a/XMonad/Layout/ToggleLayouts.hs b/XMonad/Layout/ToggleLayouts.hs
index a0193ff..af4953f 100644
--- a/XMonad/Layout/ToggleLayouts.hs
+++ b/XMonad/Layout/ToggleLayouts.hs
@@ -30,7 +30,7 @@ import XMonad.StackSet (Workspace (..))
-- Then edit your @layoutHook@ by adding the ToggleLayouts layout:
--
-- > myLayout = toggleLayouts Full (Tall 1 (3/100) (1/2)) ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/TrackFloating.hs b/XMonad/Layout/TrackFloating.hs
index b0e35e4..83936a8 100644
--- a/XMonad/Layout/TrackFloating.hs
+++ b/XMonad/Layout/TrackFloating.hs
@@ -126,7 +126,7 @@ focusWin st@(W.Stack f u d) w
Apply to your layout in a config like:
-> main = xmonad (defaultConfig{
+> main = xmonad (def{
> layoutHook = trackFloating (useTransientFor
> (noBorders Full ||| Tall 1 0.3 0.5)),
> ...
diff --git a/XMonad/Layout/TwoPane.hs b/XMonad/Layout/TwoPane.hs
index 3736e4d..b83f6d2 100644
--- a/XMonad/Layout/TwoPane.hs
+++ b/XMonad/Layout/TwoPane.hs
@@ -33,7 +33,7 @@ import XMonad.StackSet ( focus, up, down)
-- Then edit your @layoutHook@ by adding the TwoPane layout:
--
-- > myLayout = TwoPane (3/100) (1/2) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/WindowArranger.hs b/XMonad/Layout/WindowArranger.hs
index a74e7d3..1c2a270 100644
--- a/XMonad/Layout/WindowArranger.hs
+++ b/XMonad/Layout/WindowArranger.hs
@@ -38,12 +38,12 @@ import Data.List
-- @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.WindowArranger
--- > myLayout = layoutHook defaultConfig
--- > main = xmonad defaultConfig { layoutHook = windowArrange myLayout }
+-- > myLayout = layoutHook def
+-- > main = xmonad def { layoutHook = windowArrange myLayout }
--
-- or
--
--- > main = xmonad defaultConfig { layoutHook = windowArrangeAll myLayout }
+-- > main = xmonad def { layoutHook = windowArrangeAll myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/WindowNavigation.hs b/XMonad/Layout/WindowNavigation.hs
index 0244532..ebfa553 100644
--- a/XMonad/Layout/WindowNavigation.hs
+++ b/XMonad/Layout/WindowNavigation.hs
@@ -42,7 +42,7 @@ import XMonad.Util.XUtils
-- to some layout:
--
-- > myLayout = windowNavigation (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/WindowSwitcherDecoration.hs b/XMonad/Layout/WindowSwitcherDecoration.hs
index 4778314..07cb022 100644
--- a/XMonad/Layout/WindowSwitcherDecoration.hs
+++ b/XMonad/Layout/WindowSwitcherDecoration.hs
@@ -43,8 +43,8 @@ import Foreign.C.Types(CInt)
-- Then edit your @layoutHook@ by adding the WindowSwitcherDecoration to
-- your layout:
--
--- > myL = windowSwitcherDecoration shrinkText defaultTheme (draggingVisualizer $ layoutHook defaultConfig)
--- > main = xmonad defaultConfig { layoutHook = myL }
+-- > myL = windowSwitcherDecoration shrinkText defaultTheme (draggingVisualizer $ layoutHook def)
+-- > main = xmonad def { layoutHook = myL }
--
-- There is also a version of the decoration that contains buttons like
-- "XMonad.Layout.ButtonDecoration". To use that version, you will need to
@@ -53,8 +53,8 @@ import Foreign.C.Types(CInt)
--
-- > import XMonad.Layout.DecorationAddons
-- >
--- > myL = windowSwitcherDecorationWithButtons shrinkText defaultThemeWithButtons (draggingVisualizer $ layoutHook defaultConfig)
--- > main = xmonad defaultConfig { layoutHook = myL }
+-- > myL = windowSwitcherDecorationWithButtons shrinkText defaultThemeWithButtons (draggingVisualizer $ layoutHook def)
+-- > main = xmonad def { layoutHook = myL }
--
-- Additionaly, there is a version of the decoration that contains image buttons like
-- "XMonad.Layout.ImageButtonDecoration". To use that version, you will need to
@@ -63,8 +63,8 @@ import Foreign.C.Types(CInt)
--
-- > import XMonad.Layout.ImageButtonDecoration
-- >
--- > myL = windowSwitcherDecorationWithImageButtons shrinkText defaultThemeWithImageButtons (draggingVisualizer $ layoutHook defaultConfig)
--- > main = xmonad defaultConfig { layoutHook = myL }
+-- > myL = windowSwitcherDecorationWithImageButtons shrinkText defaultThemeWithImageButtons (draggingVisualizer $ layoutHook def)
+-- > main = xmonad def { layoutHook = myL }
--
windowSwitcherDecoration :: (Eq a, Shrinker s) => s -> Theme
diff --git a/XMonad/Layout/WorkspaceDir.hs b/XMonad/Layout/WorkspaceDir.hs
index b844cf0..ae39d4b 100644
--- a/XMonad/Layout/WorkspaceDir.hs
+++ b/XMonad/Layout/WorkspaceDir.hs
@@ -47,7 +47,7 @@ import XMonad.StackSet ( tag, currentTag )
-- to some layout:
--
-- > myLayout = workspaceDir "~" (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
--- > main = xmonad defaultConfig { layoutHook = myLayout }
+-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Util/CustomKeys.hs b/XMonad/Util/CustomKeys.hs
index e2e73ef..49c33d9 100644
--- a/XMonad/Util/CustomKeys.hs
+++ b/XMonad/Util/CustomKeys.hs
@@ -31,7 +31,7 @@ import qualified Data.Map as M
--
-- 2. Set key bindings with 'customKeys':
--
--- > main = xmonad defaultConfig { keys = customKeys delkeys inskeys }
+-- > main = xmonad def { keys = customKeys delkeys inskeys }
-- > where
-- > delkeys :: XConfig l -> [(KeyMask, KeySym)]
-- > delkeys XConfig {modMask = modm} =
@@ -53,17 +53,17 @@ import qualified Data.Map as M
-- > import System.Exit
-- > import qualified Data.Map as M
-- >
--- > main = xmonad defaultConfig {
+-- > main = xmonad def {
-- > keys = \_ -> M.fromList [
-- > -- Let me out of here! I want my KDE back! Help! Help!
-- > ( (0, xK_Escape), io (exitWith ExitSuccess) ) ] }
--- | Customize 'XMonad.Config.defaultConfig' -- delete needless
+-- | Customize 'XMonad.Config.def' -- delete needless
-- shortcuts and insert those you will use.
customKeys :: (XConfig Layout -> [(KeyMask, KeySym)]) -- ^ shortcuts to delete
-> (XConfig Layout -> [((KeyMask, KeySym), X ())]) -- ^ key bindings to insert
-> XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
-customKeys = customKeysFrom defaultConfig
+customKeys = customKeysFrom def
-- | General variant of 'customKeys': customize key bindings of
-- third-party configuration.
diff --git a/XMonad/Util/EZConfig.hs b/XMonad/Util/EZConfig.hs
index 53f893a..f24d9d6 100644
--- a/XMonad/Util/EZConfig.hs
+++ b/XMonad/Util/EZConfig.hs
@@ -7,7 +7,7 @@
--
-- Maintainer : Devin Mullins <me@twifkak.com>
--
--- Useful helper functions for amending the defaultConfig, and for
+-- Useful helper functions for amending the default configuration, and for
-- parsing keybindings specified in a special (emacs-like) format.
--
-- (See also "XMonad.Util.CustomKeys" in xmonad-contrib.)
@@ -69,7 +69,7 @@ import Text.ParserCombinators.ReadP
-- |
-- Add or override keybindings from the existing set. Example use:
--
--- > main = xmonad $ defaultConfig { terminal = "urxvt" }
+-- > main = xmonad $ def { terminal = "urxvt" }
-- > `additionalKeys`
-- > [ ((mod1Mask, xK_m ), spawn "echo 'Hi, mom!' | dzen2 -p 4")
-- > , ((mod1Mask, xK_BackSpace), withFocused hide) -- N.B. this is an absurd thing to do
@@ -88,7 +88,7 @@ additionalKeys conf keyList =
-- descriptors like @\"M-m\"@ instead of @(modMask, xK_m)@, as
-- described in the documentation for 'mkKeymap'. For example:
--
--- > main = xmonad $ defaultConfig { terminal = "urxvt" }
+-- > main = xmonad $ def { terminal = "urxvt" }
-- > `additionalKeysP`
-- > [ ("M-m", spawn "echo 'Hi, mom!' | dzen2 -p 4")
-- > , ("M-<Backspace>", withFocused hide) -- N.B. this is an absurd thing to do
@@ -101,7 +101,7 @@ additionalKeysP conf keyList =
-- |
-- Remove standard keybindings you're not using. Example use:
--
--- > main = xmonad $ defaultConfig { terminal = "urxvt" }
+-- > main = xmonad $ def { terminal = "urxvt" }
-- > `removeKeys` [(mod1Mask .|. shiftMask, n) | n <- [xK_1 .. xK_9]]
removeKeys :: XConfig a -> [(ButtonMask, KeySym)] -> XConfig a
removeKeys conf keyList =
@@ -111,7 +111,7 @@ removeKeys conf keyList =
-- like @\"M-m\"@ instead of @(modMask, xK_m)@, as described in the
-- documentation for 'mkKeymap'. For example:
--
--- > main = xmonad $ defaultConfig { terminal = "urxvt" }
+-- > main = xmonad $ def { terminal = "urxvt" }
-- > `removeKeysP` ["M-S-" ++ [n] | n <- ['1'..'9']]
removeKeysP :: XConfig l -> [String] -> XConfig l
@@ -682,7 +682,7 @@ multimediaKeys = filter ((/= noSymbol) . snd) . map (id &&& stringToKeysym) $
-- > main = xmonad $ myConfig
-- >
-- > myKeymap = [("S-M-c", kill), ...]
--- > myConfig = defaultConfig {
+-- > myConfig = def {
-- > ...
-- > keys = \c -> mkKeymap c myKeymap
-- > startupHook = return () >> checkKeymap myConfig myKeymap
diff --git a/XMonad/Util/NamedActions.hs b/XMonad/Util/NamedActions.hs
index 6ea4b82..7b8012c 100644
--- a/XMonad/Util/NamedActions.hs
+++ b/XMonad/Util/NamedActions.hs
@@ -67,7 +67,7 @@ import qualified XMonad.StackSet as W
-- > import XMonad.Util.EZConfig
-- >
-- > main = xmonad $ addDescrKeys ((mod4Mask, xK_F1), xMessage) myKeys
--- > defaultConfig { modMask = mod4Mask }
+-- > def { modMask = mod4Mask }
-- >
-- > myKeys c = (subtitle "Custom Keys":) $ mkNamedKeymap c $
-- > [("M-x a", addName "useless message" $ spawn "xmessage foo"),
@@ -191,7 +191,7 @@ smartSpace [] = []
smartSpace xs = ' ':xs
_test :: String
-_test = unlines $ showKm $ defaultKeysDescr XMonad.defaultConfig { XMonad.layoutHook = XMonad.Layout $ XMonad.layoutHook XMonad.defaultConfig }
+_test = unlines $ showKm $ defaultKeysDescr XMonad.def { XMonad.layoutHook = XMonad.Layout $ XMonad.layoutHook XMonad.def }
showKm :: [((KeyMask, KeySym), NamedAction)] -> [String]
showKm keybindings = padding $ do
@@ -227,7 +227,7 @@ addDescrKeys' (k,f) ks conf =
keylist l = M.map getAction $ M.fromList $ ks l ^++^ [(k, shk l)]
in conf { keys = keylist }
--- | A version of the default keys from 'XMonad.Config.defaultConfig', but with
+-- | A version of the default keys from the default configuration, but with
-- 'NamedAction' instead of @X ()@
defaultKeysDescr :: XConfig Layout -> [((KeyMask, KeySym), NamedAction)]
defaultKeysDescr conf@(XConfig {XMonad.modMask = modm}) =
diff --git a/XMonad/Util/Replace.hs b/XMonad/Util/Replace.hs
index 110f701..49eda82 100644
--- a/XMonad/Util/Replace.hs
+++ b/XMonad/Util/Replace.hs
@@ -40,7 +40,7 @@ import Control.Monad
-- > import XMonad.Util.Replace
-- > main = do
-- > replace
--- > xmonad $ defaultConfig { .... }
+-- > xmonad $ def { .... }
--
-- $shortcomings
@@ -61,7 +61,7 @@ import Control.Monad
-- > main = do
-- > args <- getArgs
-- > when ("--replace" `elem` args) replace
--- > xmonad $ defaultConfig { .... }
+-- > xmonad $ def { .... }
--
--
-- Note that your @~\/.xmonad/xmonad-$arch-$os@ binary is not run with the same
diff --git a/XMonad/Util/Run.hs b/XMonad/Util/Run.hs
index 796193d..bd18a6a 100644
--- a/XMonad/Util/Run.hs
+++ b/XMonad/Util/Run.hs
@@ -134,7 +134,7 @@ safeSpawnProg = flip safeSpawn []
unsafeSpawn :: MonadIO m => String -> m ()
unsafeSpawn = spawn
--- | Open a terminal emulator. The terminal emulator is specified in @defaultConfig@ as xterm by default. It is then
+-- | Open a terminal emulator. The terminal emulator is specified in the default configuration as xterm by default. It is then
-- asked to pass the shell a command with certain options. This is unsafe in the sense of 'unsafeSpawn'
unsafeRunInTerm, runInTerm :: String -> String -> X ()
unsafeRunInTerm options command = asks (terminal . config) >>= \t -> unsafeSpawn $ t ++ " " ++ options ++ " -e " ++ command
diff --git a/XMonad/Util/Themes.hs b/XMonad/Util/Themes.hs
index 576f84c..61352d6 100644
--- a/XMonad/Util/Themes.hs
+++ b/XMonad/Util/Themes.hs
@@ -56,7 +56,7 @@ import XMonad.Layout.Decoration
-- >
-- > myLayout = tabbed shrinkText (theme smallClean)
-- >
--- > main = xmonad defaultConfig {layoutHook = myLayout}
+-- > main = xmonad def {layoutHook = myLayout}
--
-- If you have a theme you would like to share, adding it to this
-- module is very easy.