aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Actions')
-rw-r--r--XMonad/Actions/DynamicWorkspaces.hs10
-rw-r--r--XMonad/Actions/GridSelect.hs18
-rw-r--r--XMonad/Actions/Launcher.hs6
-rw-r--r--XMonad/Actions/Navigation2D.hs29
-rw-r--r--XMonad/Actions/Search.hs4
-rw-r--r--XMonad/Actions/ShowText.hs13
-rw-r--r--XMonad/Actions/SpawnOn.hs2
-rw-r--r--XMonad/Actions/Submap.hs4
-rw-r--r--XMonad/Actions/TagWindows.hs12
-rw-r--r--XMonad/Actions/TopicSpace.hs11
-rw-r--r--XMonad/Actions/WorkspaceNames.hs2
11 files changed, 65 insertions, 46 deletions
diff --git a/XMonad/Actions/DynamicWorkspaces.hs b/XMonad/Actions/DynamicWorkspaces.hs
index c7c0d5b..fc73542 100644
--- a/XMonad/Actions/DynamicWorkspaces.hs
+++ b/XMonad/Actions/DynamicWorkspaces.hs
@@ -46,10 +46,10 @@ import Control.Monad (when)
-- Then add keybindings like the following:
--
-- > , ((modm .|. shiftMask, xK_BackSpace), removeWorkspace)
--- > , ((modm .|. shiftMask, xK_v ), selectWorkspace defaultXPConfig)
--- > , ((modm, xK_m ), withWorkspace defaultXPConfig (windows . W.shift))
--- > , ((modm .|. shiftMask, xK_m ), withWorkspace defaultXPConfig (windows . copy))
--- > , ((modm .|. shiftMask, xK_r ), renameWorkspace defaultXPConfig)
+-- > , ((modm .|. shiftMask, xK_v ), selectWorkspace def)
+-- > , ((modm, xK_m ), withWorkspace def (windows . W.shift))
+-- > , ((modm .|. shiftMask, xK_m ), withWorkspace def (windows . copy))
+-- > , ((modm .|. shiftMask, xK_r ), renameWorkspace def)
--
-- > -- mod-[1..9] %! Switch to workspace N
-- > -- mod-shift-[1..9] %! Move client to workspace N
@@ -60,7 +60,7 @@ import Control.Monad (when)
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings". See also the documentation for
--- "XMonad.Actions.CopyWindow", 'windows', 'shift', and 'defaultXPConfig'.
+-- "XMonad.Actions.CopyWindow", 'windows', 'shift', and 'XPConfig'.
mkCompl :: [String] -> String -> IO [String]
diff --git a/XMonad/Actions/GridSelect.hs b/XMonad/Actions/GridSelect.hs
index e7ba0b7..1543644 100644
--- a/XMonad/Actions/GridSelect.hs
+++ b/XMonad/Actions/GridSelect.hs
@@ -27,6 +27,7 @@ module XMonad.Actions.GridSelect (
-- * Configuration
GSConfig(..),
+ def,
defaultGSConfig,
TwoDPosition,
buildDefaultGSConfig,
@@ -167,7 +168,7 @@ import Data.Word (Word8)
--
-- You can then define @gsconfig3@ which may be used in exactly the same manner as @gsconfig1@:
--
--- > gsconfig3 = defaultGSConfig
+-- > gsconfig3 = def
-- > { gs_cellheight = 30
-- > , gs_cellwidth = 100
-- > , gs_navigate = myNavigation
@@ -183,6 +184,11 @@ import Data.Word (Word8)
--
-- <<http://haskell.org/wikiupload/3/35/Xmonad-gridselect-window-aavogt.png>>
+-- | The 'Default' instance gives a basic configuration for 'gridselect', with
+-- the colorizer chosen based on the type.
+--
+-- If you want to replace the 'gs_colorizer' field, use 'buildDefaultGSConfig'
+-- instead of 'def' to avoid ambiguous type variables.
data GSConfig a = GSConfig {
gs_cellheight :: Integer,
gs_cellwidth :: Integer,
@@ -212,12 +218,12 @@ instance HasColorizer a where
let getColor = if isFg then focusedBorderColor else normalBorderColor
in asks $ flip (,) "black" . getColor . config
--- | A basic configuration for 'gridselect', with the colorizer chosen based on the type.
---
--- If you want to replace the 'gs_colorizer' field, use 'buildDefaultGSConfig'
--- instead, to avoid ambiguous type variables.
+instance HasColorizer a => Default (GSConfig a) where
+ def = buildDefaultGSConfig defaultColorizer
+
+{-# DEPRECATED defaultGSConfig "Use def (from Data.Default, and re-exported from XMonad.Actions.GridSelect) instead." #-}
defaultGSConfig :: HasColorizer a => GSConfig a
-defaultGSConfig = buildDefaultGSConfig defaultColorizer
+defaultGSConfig = def
type TwoDPosition = (Integer, Integer)
diff --git a/XMonad/Actions/Launcher.hs b/XMonad/Actions/Launcher.hs
index 9056bf4..025fb34 100644
--- a/XMonad/Actions/Launcher.hs
+++ b/XMonad/Actions/Launcher.hs
@@ -34,10 +34,10 @@ import XMonad.Util.Run
To test it, modify your local .xmonad:
- > import XMonad.Prompt(defaultXPConfig)
+ > import XMonad.Prompt(def)
> import XMonad.Actions.Launcher
- > ((modm .|. controlMask, xK_l), launcherPrompt defaultXPConfig $ defaultLauncherModes launcherConfig)
+ > ((modm .|. controlMask, xK_l), launcherPrompt def $ defaultLauncherModes launcherConfig)
A LauncherConfig contains settings for the default modes, modify them accordingly.
@@ -45,7 +45,7 @@ import XMonad.Util.Run
Restart xmonad. Press Ctrl + Your_Modkey + L and the first prompt should pop up.
- If you used 'defaultXPConfig', you can change mode with 'xK_grave'. If you are using your own 'XPConfig', define the value for 'changeModeKey'.
+ If you used the default 'XPConfig', you can change mode with 'xK_grave'. If you are using your own 'XPConfig', define the value for 'changeModeKey'.
-}
data HoogleMode = HMode FilePath String --path to hoogle and browser
diff --git a/XMonad/Actions/Navigation2D.hs b/XMonad/Actions/Navigation2D.hs
index 379180d..dda42ff 100644
--- a/XMonad/Actions/Navigation2D.hs
+++ b/XMonad/Actions/Navigation2D.hs
@@ -34,6 +34,7 @@ module XMonad.Actions.Navigation2D ( -- * Usage
withNavigation2DConfig
, Navigation2DConfig(..)
+ , def
, defaultNavigation2DConfig
, Navigation2D
, lineNavigation
@@ -114,8 +115,7 @@ import XMonad.Util.Types
--
-- and add the configuration of the module to your main function:
--
--- > main = xmonad $ withNavigation2DConfig defaultNavigation2DConfig
--- > $ def
+-- > main = xmonad $ withNavigation2DConfig def $ def
--
-- For detailed instruction on editing the key binding see:
--
@@ -147,7 +147,7 @@ import XMonad.Util.Types
-- example, for the Full layout, is to switch to center navigation for the Full
-- layout:
--
--- > myNavigation2DConfig = defaultNavigation2DConfig { layoutNavigation = [("Full", centerNavigation)] }
+-- > myNavigation2DConfig = def { layoutNavigation = [("Full", centerNavigation)] }
-- >
-- > main = xmonad $ withNavigation2DConfig myNavigation2DConfig
-- > $ def
@@ -164,9 +164,9 @@ import XMonad.Util.Types
-- on top of each other so that only the frontmost one is visible. This can be
-- done as follows:
--
--- > myNavigation2DConfig = defaultNavigation2DConfig { layoutNavigation = [("Full", centerNavigation)]
--- > , unmappedWindowRect = [("Full", singleWindowRect)]
--- > }
+-- > myNavigation2DConfig = def { layoutNavigation = [("Full", centerNavigation)]
+-- > , unmappedWindowRect = [("Full", singleWindowRect)]
+-- > }
-- >
-- > main = xmonad $ withNavigation2DConfig myNavigation2DConfig
-- > $ def
@@ -279,7 +279,10 @@ lineNavigation = N 1 doLineNavigation
centerNavigation :: Navigation2D
centerNavigation = N 2 doCenterNavigation
--- | Stores the configuration of directional navigation
+-- | Stores the configuration of directional navigation. The 'Default' instance
+-- uses line navigation for the tiled layer and for navigation between screens,
+-- and center navigation for the float layer. No custom navigation strategies
+-- or rectangles for unmapped windows are defined for individual layouts.
data Navigation2DConfig = Navigation2DConfig
{ defaultTiledNavigation :: Navigation2D -- ^ default navigation strategy for the tiled layer
, floatNavigation :: Navigation2D -- ^ navigation strategy for the float layer
@@ -305,7 +308,7 @@ type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-- So we can store the configuration in extensible state
instance ExtensionClass Navigation2DConfig where
- initialValue = defaultNavigation2DConfig
+ initialValue = def
-- | Modifies the xmonad configuration to store the Navigation2D configuration
withNavigation2DConfig :: Navigation2DConfig -> XConfig a -> XConfig a
@@ -313,12 +316,12 @@ withNavigation2DConfig conf2d xconf = xconf { startupHook = startupHook xconf
>> XS.put conf2d
}
--- | Default navigation configuration. It uses line navigation for the tiled
--- layer and for navigation between screens, and center navigation for the float
--- layer. No custom navigation strategies or rectangles for unmapped windows are
--- defined for individual layouts.
+{-# DEPRECATED defaultNavigation2DConfig "Use def (from Data.Default, and re-exported from XMonad.Actions.Navigation2D) instead." #-}
defaultNavigation2DConfig :: Navigation2DConfig
-defaultNavigation2DConfig = Navigation2DConfig { defaultTiledNavigation = lineNavigation
+defaultNavigation2DConfig = def
+
+instance Default Navigation2DConfig where
+ def = Navigation2DConfig { defaultTiledNavigation = lineNavigation
, floatNavigation = centerNavigation
, screenNavigation = lineNavigation
, layoutNavigation = []
diff --git a/XMonad/Actions/Search.hs b/XMonad/Actions/Search.hs
index cb15898..ab55ba4 100644
--- a/XMonad/Actions/Search.hs
+++ b/XMonad/Actions/Search.hs
@@ -157,7 +157,7 @@ Then add the following to your key bindings:
> ...
> -- Search commands
-> , ((modm, xK_s), SM.submap $ searchEngineMap $ S.promptSearch P.defaultXPConfig)
+> , ((modm, xK_s), SM.submap $ searchEngineMap $ S.promptSearch P.def)
> , ((modm .|. shiftMask, xK_s), SM.submap $ searchEngineMap $ S.selectSearch)
>
> ...
@@ -173,7 +173,7 @@ Or in combination with XMonad.Util.EZConfig:
> ...
> ] -- end of regular keybindings
> -- Search commands
-> ++ [("M-s " ++ k, S.promptSearch P.defaultXPConfig f) | (k,f) <- searchList ]
+> ++ [("M-s " ++ k, S.promptSearch P.def f) | (k,f) <- searchList ]
> ++ [("M-S-s " ++ k, S.selectSearch f) | (k,f) <- searchList ]
>
> ...
diff --git a/XMonad/Actions/ShowText.hs b/XMonad/Actions/ShowText.hs
index e0a64cb..77d7244 100644
--- a/XMonad/Actions/ShowText.hs
+++ b/XMonad/Actions/ShowText.hs
@@ -16,7 +16,8 @@
module XMonad.Actions.ShowText
( -- * Usage
-- $usage
- defaultSTConfig
+ def
+ , defaultSTConfig
, handleTimerEvent
, flashText
, ShowTextConfig(..)
@@ -52,7 +53,7 @@ import qualified XMonad.Util.ExtensibleState as ES
--
-- You can then use flashText in your keybindings:
--
--- > ((modMask, xK_Right), flashText defaultSTConfig 1 "->" >> nextWS)
+-- > ((modMask, xK_Right), flashText def 1 "->" >> nextWS)
--
-- | ShowText contains the map with timers as keys and created windows as values
@@ -72,13 +73,17 @@ data ShowTextConfig =
, st_fg :: String -- ^ Foreground color
}
-defaultSTConfig :: ShowTextConfig
-defaultSTConfig =
+instance Default ShowTextConfig where
+ def =
STC { st_font = "-misc-fixed-*-*-*-*-20-*-*-*-*-*-*-*"
, st_bg = "black"
, st_fg = "white"
}
+{-# DEPRECATED defaultSTConfig "Use def (from Data.Default, and re-exported by XMonad.Actions.ShowText) instead." #-}
+defaultSTConfig :: ShowTextConfig
+defaultSTConfig = def
+
-- | Handles timer events that notify when a window should be removed
handleTimerEvent :: Event -> X All
handleTimerEvent (ClientMessageEvent _ _ _ dis _ mtyp d) = do
diff --git a/XMonad/Actions/SpawnOn.hs b/XMonad/Actions/SpawnOn.hs
index df37c9d..d266492 100644
--- a/XMonad/Actions/SpawnOn.hs
+++ b/XMonad/Actions/SpawnOn.hs
@@ -54,7 +54,7 @@ import qualified XMonad.Util.ExtensibleState as XS
-- To ensure that application appears on a workspace it was launched at, add keybindings like:
--
-- > , ((mod1Mask,xK_o), spawnHere "urxvt")
--- > , ((mod1Mask,xK_s), shellPromptHere defaultXPConfig)
+-- > , ((mod1Mask,xK_s), shellPromptHere def)
--
-- The module can also be used to apply other manage hooks to the window of
-- the spawned application(e.g. float or resize it).
diff --git a/XMonad/Actions/Submap.hs b/XMonad/Actions/Submap.hs
index 17ab676..3a49d88 100644
--- a/XMonad/Actions/Submap.hs
+++ b/XMonad/Actions/Submap.hs
@@ -62,7 +62,7 @@ submap keys = submapDefault (return ()) keys
-- | Like 'submap', but executes a default action if the key did not match.
submapDefault :: X () -> M.Map (KeyMask, KeySym) (X ()) -> X ()
-submapDefault def keys = do
+submapDefault defAction keys = do
XConf { theRoot = root, display = d } <- ask
io $ grabKeyboard d root False grabModeAsync grabModeAsync currentTime
@@ -79,4 +79,4 @@ submapDefault def keys = do
io $ ungrabKeyboard d currentTime
- maybe def id (M.lookup (m', s) keys)
+ maybe defAction id (M.lookup (m', s) keys)
diff --git a/XMonad/Actions/TagWindows.hs b/XMonad/Actions/TagWindows.hs
index 86c2e9e..ac88045 100644
--- a/XMonad/Actions/TagWindows.hs
+++ b/XMonad/Actions/TagWindows.hs
@@ -53,12 +53,12 @@ econst = const . return
-- > , ((modm, xK_d ), withTaggedP "abc" (W.shiftWin "2"))
-- > , ((modm .|. shiftMask, xK_d ), withTaggedGlobalP "abc" shiftHere)
-- > , ((modm .|. controlMask, xK_d ), focusUpTaggedGlobal "abc")
--- > , ((modm, xK_g ), tagPrompt defaultXPConfig (\s -> withFocused (addTag s)))
--- > , ((modm .|. controlMask, xK_g ), tagDelPrompt defaultXPConfig)
--- > , ((modm .|. shiftMask, xK_g ), tagPrompt defaultXPConfig (\s -> withTaggedGlobal s float))
--- > , ((modWinMask, xK_g ), tagPrompt defaultXPConfig (\s -> withTaggedP s (W.shiftWin "2")))
--- > , ((modWinMask .|. shiftMask, xK_g ), tagPrompt defaultXPConfig (\s -> withTaggedGlobalP s shiftHere))
--- > , ((modWinMask .|. controlMask, xK_g ), tagPrompt defaultXPConfig (\s -> focusUpTaggedGlobal s))
+-- > , ((modm, xK_g ), tagPrompt def (\s -> withFocused (addTag s)))
+-- > , ((modm .|. controlMask, xK_g ), tagDelPrompt def)
+-- > , ((modm .|. shiftMask, xK_g ), tagPrompt def (\s -> withTaggedGlobal s float))
+-- > , ((modWinMask, xK_g ), tagPrompt def (\s -> withTaggedP s (W.shiftWin "2")))
+-- > , ((modWinMask .|. shiftMask, xK_g ), tagPrompt def (\s -> withTaggedGlobalP s shiftHere))
+-- > , ((modWinMask .|. controlMask, xK_g ), tagPrompt def (\s -> focusUpTaggedGlobal s))
--
-- NOTE: Tags are saved as space separated strings and split with
-- 'unwords'. Thus if you add a tag \"a b\" the window will have
diff --git a/XMonad/Actions/TopicSpace.hs b/XMonad/Actions/TopicSpace.hs
index cf4fb0d..4bef3c3 100644
--- a/XMonad/Actions/TopicSpace.hs
+++ b/XMonad/Actions/TopicSpace.hs
@@ -22,6 +22,7 @@ module XMonad.Actions.TopicSpace
Topic
, Dir
, TopicConfig(..)
+ , def
, defaultTopicConfig
, getLastFocusedTopics
, setLastFocusedTopic
@@ -89,7 +90,7 @@ import qualified XMonad.Util.ExtensibleState as XS
-- > ]
-- >
-- > myTopicConfig :: TopicConfig
--- > myTopicConfig = defaultTopicConfig
+-- > myTopicConfig = def
-- > { topicDirs = M.fromList $
-- > [ ("conf", "w/conf")
-- > , ("dashboard", "Desktop")
@@ -206,14 +207,18 @@ data TopicConfig = TopicConfig { topicDirs :: M.Map Topic Dir
-- numeric keypad.
}
-defaultTopicConfig :: TopicConfig
-defaultTopicConfig = TopicConfig { topicDirs = M.empty
+instance Default TopicConfig where
+ def = TopicConfig { topicDirs = M.empty
, topicActions = M.empty
, defaultTopicAction = const (ask >>= spawn . terminal . config)
, defaultTopic = "1"
, maxTopicHistory = 10
}
+{-# DEPRECATED defaultTopicConfig "Use def (from Data.Default, and re-exported by XMonad.Actions.TopicSpace) instead." #-}
+defaultTopicConfig :: TopicConfig
+defaultTopicConfig = def
+
newtype PrevTopics = PrevTopics { getPrevTopics :: [String] } deriving (Read,Show,Typeable)
instance ExtensionClass PrevTopics where
initialValue = PrevTopics []
diff --git a/XMonad/Actions/WorkspaceNames.hs b/XMonad/Actions/WorkspaceNames.hs
index 30d3d01..368e6e1 100644
--- a/XMonad/Actions/WorkspaceNames.hs
+++ b/XMonad/Actions/WorkspaceNames.hs
@@ -55,7 +55,7 @@ import Data.Maybe (fromMaybe)
--
-- Then add keybindings like the following:
--
--- > , ((modm .|. shiftMask, xK_r ), renameWorkspace defaultXPConfig)
+-- > , ((modm .|. shiftMask, xK_r ), renameWorkspace def)
--
-- and apply workspaceNamesPP to your DynamicLog pretty-printer:
--