mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 03:20:21 -07:00
Remove things deprecated by Data.Default
This commit is contained in:
parent
cd1c1d1d69
commit
5140f5b5d0
@ -28,7 +28,6 @@ module XMonad.Actions.GridSelect (
|
||||
-- * Configuration
|
||||
GSConfig(..),
|
||||
def,
|
||||
defaultGSConfig,
|
||||
TwoDPosition,
|
||||
buildDefaultGSConfig,
|
||||
|
||||
@ -107,13 +106,13 @@ import Data.Word (Word8)
|
||||
--
|
||||
-- Then add a keybinding, e.g.
|
||||
--
|
||||
-- > , ((modm, xK_g), goToSelected defaultGSConfig)
|
||||
-- > , ((modm, xK_g), goToSelected def)
|
||||
--
|
||||
-- This module also supports displaying arbitrary information in a grid and letting
|
||||
-- the user select from it. E.g. to spawn an application from a given list, you
|
||||
-- can use the following:
|
||||
--
|
||||
-- > , ((modm, xK_s), spawnSelected defaultGSConfig ["xterm","gmplayer","gvim"])
|
||||
-- > , ((modm, xK_s), spawnSelected def ["xterm","gmplayer","gvim"])
|
||||
|
||||
-- $commonGSConfig
|
||||
--
|
||||
@ -123,7 +122,7 @@ import Data.Word (Word8)
|
||||
-- > {-# LANGUAGE NoMonomorphismRestriction #-}
|
||||
-- > import XMonad
|
||||
-- > ...
|
||||
-- > gsconfig1 = defaultGSConfig { gs_cellheight = 30, gs_cellwidth = 100 }
|
||||
-- > gsconfig1 = def { gs_cellheight = 30, gs_cellwidth = 100 }
|
||||
--
|
||||
-- An example where 'buildDefaultGSConfig' is used instead of 'defaultGSConfig'
|
||||
-- in order to specify a custom colorizer is @gsconfig2@ (found in
|
||||
@ -230,10 +229,6 @@ instance HasColorizer a where
|
||||
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 = def
|
||||
|
||||
type TwoDPosition = (Integer, Integer)
|
||||
|
||||
type TwoDElementMap a = [(TwoDPosition,(String,a))]
|
||||
@ -770,7 +765,7 @@ gridselectWorkspace' conf func = withWindowSet $ \ws -> do
|
||||
--
|
||||
-- > import XMonad.Actions.DynamicWorkspaces (addWorkspace)
|
||||
-- >
|
||||
-- > gridselectWorkspace' defaultGSConfig
|
||||
-- > gridselectWorkspace' def
|
||||
-- > { gs_navigate = navNSearch
|
||||
-- > , gs_rearranger = searchStringRearrangerGenerator id
|
||||
-- > }
|
||||
|
@ -39,7 +39,6 @@ module XMonad.Actions.Navigation2D ( -- * Usage
|
||||
, withNavigation2DConfig
|
||||
, Navigation2DConfig(..)
|
||||
, def
|
||||
, defaultNavigation2DConfig
|
||||
, Navigation2D
|
||||
, lineNavigation
|
||||
, centerNavigation
|
||||
@ -451,10 +450,6 @@ withNavigation2DConfig conf2d xconf = xconf { startupHook = startupHook xconf
|
||||
>> XS.put conf2d
|
||||
}
|
||||
|
||||
{-# DEPRECATED defaultNavigation2DConfig "Use def (from Data.Default, and re-exported from XMonad.Actions.Navigation2D) instead." #-}
|
||||
defaultNavigation2DConfig :: Navigation2DConfig
|
||||
defaultNavigation2DConfig = def
|
||||
|
||||
instance Default Navigation2DConfig where
|
||||
def = Navigation2DConfig { defaultTiledNavigation = lineNavigation
|
||||
, floatNavigation = centerNavigation
|
||||
|
@ -17,7 +17,6 @@ module XMonad.Actions.ShowText
|
||||
( -- * Usage
|
||||
-- $usage
|
||||
def
|
||||
, defaultSTConfig
|
||||
, handleTimerEvent
|
||||
, flashText
|
||||
, ShowTextConfig(..)
|
||||
@ -80,10 +79,6 @@ instance Default ShowTextConfig where
|
||||
, 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
|
||||
|
@ -23,7 +23,6 @@ module XMonad.Actions.TopicSpace
|
||||
, Dir
|
||||
, TopicConfig(..)
|
||||
, def
|
||||
, defaultTopicConfig
|
||||
, getLastFocusedTopics
|
||||
, setLastFocusedTopic
|
||||
, reverseLastFocusedTopics
|
||||
@ -216,10 +215,6 @@ instance Default TopicConfig where
|
||||
, 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 []
|
||||
|
@ -37,7 +37,7 @@ module XMonad.Hooks.DynamicLog (
|
||||
-- * Build your own formatter
|
||||
dynamicLogWithPP,
|
||||
dynamicLogString,
|
||||
PP(..), defaultPP, def,
|
||||
PP(..), def,
|
||||
|
||||
-- * Example formatters
|
||||
dzenPP, xmobarPP, sjanssenPP, byorgeyPP,
|
||||
@ -566,10 +566,6 @@ data PP = PP { ppCurrent :: WorkspaceId -> String
|
||||
}
|
||||
|
||||
-- | The default pretty printing options, as seen in 'dynamicLog'.
|
||||
{-# DEPRECATED defaultPP "Use def (from Data.Default, and re-exported by XMonad.Hooks.DynamicLog) instead." #-}
|
||||
defaultPP :: PP
|
||||
defaultPP = def
|
||||
|
||||
instance Default PP where
|
||||
def = PP { ppCurrent = wrap "[" "]"
|
||||
, ppVisible = wrap "<" ">"
|
||||
|
@ -179,7 +179,7 @@ screenCornerLayoutHook = ModifiedLayout ScreenCornerLayout
|
||||
--
|
||||
-- > myStartupHook = do
|
||||
-- > ...
|
||||
-- > addScreenCorner SCUpperRight (goToSelected defaultGSConfig { gs_cellwidth = 200})
|
||||
-- > addScreenCorner SCUpperRight (goToSelected def { gs_cellwidth = 200})
|
||||
-- > addScreenCorners [ (SCLowerRight, nextWS)
|
||||
-- > , (SCLowerLeft, prevWS)
|
||||
-- > ]
|
||||
|
@ -17,7 +17,7 @@ module XMonad.Layout.Decoration
|
||||
( -- * Usage:
|
||||
-- $usage
|
||||
decoration
|
||||
, Theme (..), defaultTheme, def
|
||||
, Theme (..), def
|
||||
, Decoration
|
||||
, DecorationMsg (..)
|
||||
, DecorationStyle (..)
|
||||
@ -89,6 +89,7 @@ data Theme =
|
||||
-- Inner @[Bool]@ is a row in a icon bitmap.
|
||||
} deriving (Show, Read)
|
||||
|
||||
-- | The default xmonad 'Theme'.
|
||||
instance Default Theme where
|
||||
def =
|
||||
Theme { activeColor = "#999999"
|
||||
@ -110,11 +111,6 @@ instance Default Theme where
|
||||
, windowTitleIcons = []
|
||||
}
|
||||
|
||||
{-# DEPRECATED defaultTheme "Use def (from Data.Default, and re-exported by XMonad.Layout.Decoration) instead." #-}
|
||||
-- | The default xmonad 'Theme'.
|
||||
defaultTheme :: Theme
|
||||
defaultTheme = def
|
||||
|
||||
-- | A 'Decoration' layout modifier will handle 'SetTheme', a message
|
||||
-- to dynamically change the decoration 'Theme'.
|
||||
data DecorationMsg = SetTheme Theme deriving ( Typeable )
|
||||
|
@ -82,7 +82,7 @@ module XMonad.Layout.DecorationMadness
|
||||
, floatDwmStyle
|
||||
, floatSimpleTabbed
|
||||
, floatTabbed
|
||||
, def, defaultTheme, shrinkText
|
||||
, def, shrinkText
|
||||
) where
|
||||
|
||||
import XMonad
|
||||
|
@ -18,7 +18,6 @@ module XMonad.Layout.DwmStyle
|
||||
dwmStyle
|
||||
, Theme (..)
|
||||
, def
|
||||
, defaultTheme
|
||||
, DwmStyle (..)
|
||||
, shrinkText, CustomShrink(CustomShrink)
|
||||
, Shrinker(..)
|
||||
|
@ -37,7 +37,6 @@ module XMonad.Layout.Groups.Examples ( -- * Usage
|
||||
, fullTabs
|
||||
, TiledTabsConfig(..)
|
||||
, def
|
||||
, defaultTiledTabsConfig
|
||||
, increaseNMasterGroups
|
||||
, decreaseNMasterGroups
|
||||
, shrinkMasterGroups
|
||||
@ -48,7 +47,6 @@ module XMonad.Layout.Groups.Examples ( -- * Usage
|
||||
-- * Useful re-exports and utils
|
||||
, module XMonad.Layout.Groups.Helpers
|
||||
, shrinkText
|
||||
, defaultTheme
|
||||
, GroupEQ(..)
|
||||
, zoomRowG
|
||||
) where
|
||||
@ -205,10 +203,6 @@ data TiledTabsConfig s = TTC { vNMaster :: Int
|
||||
instance s ~ DefaultShrinker => Default (TiledTabsConfig s) where
|
||||
def = TTC 1 0.5 (3/100) 1 0.5 (3/100) shrinkText def
|
||||
|
||||
{-# DEPRECATED defaultTiledTabsConfig "Use def (from Data.Default, and re-exported by XMonad.Layout.Groups) instead." #-}
|
||||
defaultTiledTabsConfig :: TiledTabsConfig DefaultShrinker
|
||||
defaultTiledTabsConfig = def
|
||||
|
||||
fullTabs c = _tab c $ G.group _tabs $ Full ||| _vert c ||| _horiz c
|
||||
|
||||
tallTabs c = _tab c $ G.group _tabs $ _vert c ||| _horiz c ||| Full
|
||||
|
@ -31,7 +31,6 @@ module XMonad.Layout.Groups.Wmii ( -- * Usage
|
||||
-- * Useful re-exports
|
||||
, shrinkText
|
||||
, def
|
||||
, defaultTheme
|
||||
, module XMonad.Layout.Groups.Helpers ) where
|
||||
|
||||
import XMonad hiding ((|||))
|
||||
|
@ -18,7 +18,6 @@ module XMonad.Layout.ShowWName
|
||||
showWName
|
||||
, showWName'
|
||||
, def
|
||||
, defaultSWNConfig
|
||||
, SWNConfig(..)
|
||||
, ShowWName
|
||||
) where
|
||||
@ -69,10 +68,6 @@ instance Default SWNConfig where
|
||||
, swn_fade = 1
|
||||
}
|
||||
|
||||
{-# DEPRECATED defaultSWNConfig "Use def (from Data.Default, and re-exported from XMonad.Layout.ShowWName) instead." #-}
|
||||
defaultSWNConfig :: SWNConfig
|
||||
defaultSWNConfig = def
|
||||
|
||||
instance LayoutModifier ShowWName a where
|
||||
redoLayout sn r _ wrs = doShow sn r wrs
|
||||
|
||||
|
@ -21,7 +21,6 @@ module XMonad.Layout.SimpleDecoration
|
||||
simpleDeco
|
||||
, Theme (..)
|
||||
, def
|
||||
, defaultTheme
|
||||
, SimpleDecoration (..)
|
||||
, shrinkText, CustomShrink(CustomShrink)
|
||||
, Shrinker(..)
|
||||
|
@ -16,7 +16,7 @@ module XMonad.Layout.TabBarDecoration
|
||||
( -- * Usage
|
||||
-- $usage
|
||||
simpleTabBar, tabBar
|
||||
, def, defaultTheme, shrinkText
|
||||
, def, shrinkText
|
||||
, TabBarDecoration (..), XPPosition (..)
|
||||
, module XMonad.Layout.ResizeScreen
|
||||
) where
|
||||
|
@ -27,7 +27,6 @@ module XMonad.Layout.Tabbed
|
||||
, simpleTabbedRightAlways, tabbedRightAlways, addTabsRightAlways
|
||||
, Theme (..)
|
||||
, def
|
||||
, defaultTheme
|
||||
, TabbedDecoration (..)
|
||||
, shrinkText, CustomShrink(CustomShrink)
|
||||
, Shrinker(..)
|
||||
|
@ -21,8 +21,8 @@ module XMonad.Layout.WindowNavigation (
|
||||
Navigate(..), Direction2D(..),
|
||||
MoveWindowToWindow(..),
|
||||
navigateColor, navigateBrightness,
|
||||
noNavigateBorders, defaultWNConfig, def,
|
||||
WNConfig, WindowNavigation,
|
||||
noNavigateBorders, def, WNConfig,
|
||||
WindowNavigation,
|
||||
) where
|
||||
|
||||
import Data.List ( nub, sortBy, (\\) )
|
||||
@ -93,10 +93,6 @@ navigateBrightness f = def { brightness = Just $ max 0 $ min 1 f }
|
||||
|
||||
instance Default WNConfig where def = WNC (Just 0.4) "#0000FF" "#00FFFF" "#FF0000" "#FF00FF"
|
||||
|
||||
{-# DEPRECATED defaultWNConfig "Use def (from Data.Default, and re-exported by XMonad.Layout.WindowNavigation) instead." #-}
|
||||
defaultWNConfig :: WNConfig
|
||||
defaultWNConfig = def
|
||||
|
||||
data NavigationState a = NS Point [(a,Rectangle)]
|
||||
|
||||
data WindowNavigation a = WindowNavigation WNConfig (Invisible Maybe (NavigationState a)) deriving ( Read, Show )
|
||||
|
@ -34,7 +34,6 @@ module XMonad.Prompt
|
||||
, mkXPromptWithModes
|
||||
, def
|
||||
, amberXPConfig
|
||||
, defaultXPConfig
|
||||
, greenXPConfig
|
||||
, XPMode
|
||||
, XPType (..)
|
||||
@ -294,7 +293,7 @@ data XPColor =
|
||||
, border :: String -- ^ Border color
|
||||
}
|
||||
|
||||
amberXPConfig, defaultXPConfig, greenXPConfig :: XPConfig
|
||||
amberXPConfig, greenXPConfig :: XPConfig
|
||||
|
||||
instance Default XPColor where
|
||||
def =
|
||||
@ -331,8 +330,6 @@ instance Default XPConfig where
|
||||
, defaultPrompter = id
|
||||
, sorter = const id
|
||||
}
|
||||
{-# DEPRECATED defaultXPConfig "Use def (from Data.Default, and re-exported from XMonad.Prompt) instead." #-}
|
||||
defaultXPConfig = def
|
||||
greenXPConfig = def { bgColor = "black"
|
||||
, fgColor = "green"
|
||||
, promptBorderWidth = 0
|
||||
|
@ -35,7 +35,7 @@ will then run normally if the user confirms.
|
||||
This should be used something like this:
|
||||
|
||||
> ...
|
||||
> , ((modm , xK_l), confirmPrompt defaultXPConfig "exit" $ io (exitWith ExitSuccess))
|
||||
> , ((modm , xK_l), confirmPrompt def "exit" $ io (exitWith ExitSuccess))
|
||||
> ...
|
||||
-}
|
||||
|
||||
|
@ -49,12 +49,12 @@ import XMonad.Prompt
|
||||
-- @fireEmployee@ action, like so:
|
||||
--
|
||||
-- > firingPrompt :: X ()
|
||||
-- > firingPrompt = inputPrompt defaultXPConfig "Fire" ?+ fireEmployee
|
||||
-- > firingPrompt = inputPrompt def "Fire" ?+ fireEmployee
|
||||
--
|
||||
-- If @employees@ contains a list of all his employees, he could also
|
||||
-- create an autocompleting version, like this:
|
||||
--
|
||||
-- > firingPrompt' = inputPromptWithCompl defaultXPConfig "Fire"
|
||||
-- > firingPrompt' = inputPromptWithCompl def "Fire"
|
||||
-- > (mkComplFunFromList employees) ?+ fireEmployee
|
||||
--
|
||||
-- Now all he has to do is add a keybinding to @firingPrompt@ (or
|
||||
|
@ -42,7 +42,7 @@ import qualified Data.Map as Map
|
||||
-- > -- LogHook
|
||||
-- > logHook' = do
|
||||
-- > mh <- getNamedPipeHandle "dzenPipe"
|
||||
-- > dynamicLogWithPP $ defaultPP {
|
||||
-- > dynamicLogWithPP $ def {
|
||||
-- > ppOutput = maybe (\s -> return ()) (hPutStrLn) mh}
|
||||
-- >
|
||||
-- > -- Main
|
||||
|
Loading…
x
Reference in New Issue
Block a user