Remove things deprecated by Data.Default

This commit is contained in:
slotThe 2020-11-16 10:01:30 +01:00
parent cd1c1d1d69
commit 5140f5b5d0
20 changed files with 18 additions and 68 deletions

View File

@ -28,7 +28,6 @@ module XMonad.Actions.GridSelect (
-- * Configuration -- * Configuration
GSConfig(..), GSConfig(..),
def, def,
defaultGSConfig,
TwoDPosition, TwoDPosition,
buildDefaultGSConfig, buildDefaultGSConfig,
@ -107,13 +106,13 @@ import Data.Word (Word8)
-- --
-- Then add a keybinding, e.g. -- 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 -- 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 -- the user select from it. E.g. to spawn an application from a given list, you
-- can use the following: -- can use the following:
-- --
-- > , ((modm, xK_s), spawnSelected defaultGSConfig ["xterm","gmplayer","gvim"]) -- > , ((modm, xK_s), spawnSelected def ["xterm","gmplayer","gvim"])
-- $commonGSConfig -- $commonGSConfig
-- --
@ -123,7 +122,7 @@ import Data.Word (Word8)
-- > {-# LANGUAGE NoMonomorphismRestriction #-} -- > {-# LANGUAGE NoMonomorphismRestriction #-}
-- > import XMonad -- > 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' -- An example where 'buildDefaultGSConfig' is used instead of 'defaultGSConfig'
-- in order to specify a custom colorizer is @gsconfig2@ (found in -- 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 instance HasColorizer a => Default (GSConfig a) where
def = buildDefaultGSConfig defaultColorizer 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 TwoDPosition = (Integer, Integer)
type TwoDElementMap a = [(TwoDPosition,(String,a))] type TwoDElementMap a = [(TwoDPosition,(String,a))]
@ -770,7 +765,7 @@ gridselectWorkspace' conf func = withWindowSet $ \ws -> do
-- --
-- > import XMonad.Actions.DynamicWorkspaces (addWorkspace) -- > import XMonad.Actions.DynamicWorkspaces (addWorkspace)
-- > -- >
-- > gridselectWorkspace' defaultGSConfig -- > gridselectWorkspace' def
-- > { gs_navigate = navNSearch -- > { gs_navigate = navNSearch
-- > , gs_rearranger = searchStringRearrangerGenerator id -- > , gs_rearranger = searchStringRearrangerGenerator id
-- > } -- > }

View File

@ -39,7 +39,6 @@ module XMonad.Actions.Navigation2D ( -- * Usage
, withNavigation2DConfig , withNavigation2DConfig
, Navigation2DConfig(..) , Navigation2DConfig(..)
, def , def
, defaultNavigation2DConfig
, Navigation2D , Navigation2D
, lineNavigation , lineNavigation
, centerNavigation , centerNavigation
@ -451,10 +450,6 @@ withNavigation2DConfig conf2d xconf = xconf { startupHook = startupHook xconf
>> XS.put conf2d >> 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 instance Default Navigation2DConfig where
def = Navigation2DConfig { defaultTiledNavigation = lineNavigation def = Navigation2DConfig { defaultTiledNavigation = lineNavigation
, floatNavigation = centerNavigation , floatNavigation = centerNavigation

View File

@ -17,7 +17,6 @@ module XMonad.Actions.ShowText
( -- * Usage ( -- * Usage
-- $usage -- $usage
def def
, defaultSTConfig
, handleTimerEvent , handleTimerEvent
, flashText , flashText
, ShowTextConfig(..) , ShowTextConfig(..)
@ -80,10 +79,6 @@ instance Default ShowTextConfig where
, st_fg = "white" , 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 -- | Handles timer events that notify when a window should be removed
handleTimerEvent :: Event -> X All handleTimerEvent :: Event -> X All
handleTimerEvent (ClientMessageEvent _ _ _ dis _ mtyp d) = do handleTimerEvent (ClientMessageEvent _ _ _ dis _ mtyp d) = do

View File

@ -23,7 +23,6 @@ module XMonad.Actions.TopicSpace
, Dir , Dir
, TopicConfig(..) , TopicConfig(..)
, def , def
, defaultTopicConfig
, getLastFocusedTopics , getLastFocusedTopics
, setLastFocusedTopic , setLastFocusedTopic
, reverseLastFocusedTopics , reverseLastFocusedTopics
@ -216,10 +215,6 @@ instance Default TopicConfig where
, maxTopicHistory = 10 , 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) newtype PrevTopics = PrevTopics { getPrevTopics :: [String] } deriving (Read,Show,Typeable)
instance ExtensionClass PrevTopics where instance ExtensionClass PrevTopics where
initialValue = PrevTopics [] initialValue = PrevTopics []

View File

@ -37,7 +37,7 @@ module XMonad.Hooks.DynamicLog (
-- * Build your own formatter -- * Build your own formatter
dynamicLogWithPP, dynamicLogWithPP,
dynamicLogString, dynamicLogString,
PP(..), defaultPP, def, PP(..), def,
-- * Example formatters -- * Example formatters
dzenPP, xmobarPP, sjanssenPP, byorgeyPP, dzenPP, xmobarPP, sjanssenPP, byorgeyPP,
@ -566,10 +566,6 @@ data PP = PP { ppCurrent :: WorkspaceId -> String
} }
-- | The default pretty printing options, as seen in 'dynamicLog'. -- | 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 instance Default PP where
def = PP { ppCurrent = wrap "[" "]" def = PP { ppCurrent = wrap "[" "]"
, ppVisible = wrap "<" ">" , ppVisible = wrap "<" ">"

View File

@ -179,7 +179,7 @@ screenCornerLayoutHook = ModifiedLayout ScreenCornerLayout
-- --
-- > myStartupHook = do -- > myStartupHook = do
-- > ... -- > ...
-- > addScreenCorner SCUpperRight (goToSelected defaultGSConfig { gs_cellwidth = 200}) -- > addScreenCorner SCUpperRight (goToSelected def { gs_cellwidth = 200})
-- > addScreenCorners [ (SCLowerRight, nextWS) -- > addScreenCorners [ (SCLowerRight, nextWS)
-- > , (SCLowerLeft, prevWS) -- > , (SCLowerLeft, prevWS)
-- > ] -- > ]

View File

@ -17,7 +17,7 @@ module XMonad.Layout.Decoration
( -- * Usage: ( -- * Usage:
-- $usage -- $usage
decoration decoration
, Theme (..), defaultTheme, def , Theme (..), def
, Decoration , Decoration
, DecorationMsg (..) , DecorationMsg (..)
, DecorationStyle (..) , DecorationStyle (..)
@ -89,6 +89,7 @@ data Theme =
-- Inner @[Bool]@ is a row in a icon bitmap. -- Inner @[Bool]@ is a row in a icon bitmap.
} deriving (Show, Read) } deriving (Show, Read)
-- | The default xmonad 'Theme'.
instance Default Theme where instance Default Theme where
def = def =
Theme { activeColor = "#999999" Theme { activeColor = "#999999"
@ -110,11 +111,6 @@ instance Default Theme where
, windowTitleIcons = [] , 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 -- | A 'Decoration' layout modifier will handle 'SetTheme', a message
-- to dynamically change the decoration 'Theme'. -- to dynamically change the decoration 'Theme'.
data DecorationMsg = SetTheme Theme deriving ( Typeable ) data DecorationMsg = SetTheme Theme deriving ( Typeable )

View File

@ -82,7 +82,7 @@ module XMonad.Layout.DecorationMadness
, floatDwmStyle , floatDwmStyle
, floatSimpleTabbed , floatSimpleTabbed
, floatTabbed , floatTabbed
, def, defaultTheme, shrinkText , def, shrinkText
) where ) where
import XMonad import XMonad

View File

@ -18,7 +18,6 @@ module XMonad.Layout.DwmStyle
dwmStyle dwmStyle
, Theme (..) , Theme (..)
, def , def
, defaultTheme
, DwmStyle (..) , DwmStyle (..)
, shrinkText, CustomShrink(CustomShrink) , shrinkText, CustomShrink(CustomShrink)
, Shrinker(..) , Shrinker(..)

View File

@ -37,7 +37,6 @@ module XMonad.Layout.Groups.Examples ( -- * Usage
, fullTabs , fullTabs
, TiledTabsConfig(..) , TiledTabsConfig(..)
, def , def
, defaultTiledTabsConfig
, increaseNMasterGroups , increaseNMasterGroups
, decreaseNMasterGroups , decreaseNMasterGroups
, shrinkMasterGroups , shrinkMasterGroups
@ -48,7 +47,6 @@ module XMonad.Layout.Groups.Examples ( -- * Usage
-- * Useful re-exports and utils -- * Useful re-exports and utils
, module XMonad.Layout.Groups.Helpers , module XMonad.Layout.Groups.Helpers
, shrinkText , shrinkText
, defaultTheme
, GroupEQ(..) , GroupEQ(..)
, zoomRowG , zoomRowG
) where ) where
@ -205,10 +203,6 @@ data TiledTabsConfig s = TTC { vNMaster :: Int
instance s ~ DefaultShrinker => Default (TiledTabsConfig s) where instance s ~ DefaultShrinker => Default (TiledTabsConfig s) where
def = TTC 1 0.5 (3/100) 1 0.5 (3/100) shrinkText def 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 fullTabs c = _tab c $ G.group _tabs $ Full ||| _vert c ||| _horiz c
tallTabs c = _tab c $ G.group _tabs $ _vert c ||| _horiz c ||| Full tallTabs c = _tab c $ G.group _tabs $ _vert c ||| _horiz c ||| Full

View File

@ -31,7 +31,6 @@ module XMonad.Layout.Groups.Wmii ( -- * Usage
-- * Useful re-exports -- * Useful re-exports
, shrinkText , shrinkText
, def , def
, defaultTheme
, module XMonad.Layout.Groups.Helpers ) where , module XMonad.Layout.Groups.Helpers ) where
import XMonad hiding ((|||)) import XMonad hiding ((|||))

View File

@ -18,7 +18,6 @@ module XMonad.Layout.ShowWName
showWName showWName
, showWName' , showWName'
, def , def
, defaultSWNConfig
, SWNConfig(..) , SWNConfig(..)
, ShowWName , ShowWName
) where ) where
@ -69,10 +68,6 @@ instance Default SWNConfig where
, swn_fade = 1 , 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 instance LayoutModifier ShowWName a where
redoLayout sn r _ wrs = doShow sn r wrs redoLayout sn r _ wrs = doShow sn r wrs

View File

@ -21,7 +21,6 @@ module XMonad.Layout.SimpleDecoration
simpleDeco simpleDeco
, Theme (..) , Theme (..)
, def , def
, defaultTheme
, SimpleDecoration (..) , SimpleDecoration (..)
, shrinkText, CustomShrink(CustomShrink) , shrinkText, CustomShrink(CustomShrink)
, Shrinker(..) , Shrinker(..)

View File

@ -16,7 +16,7 @@ module XMonad.Layout.TabBarDecoration
( -- * Usage ( -- * Usage
-- $usage -- $usage
simpleTabBar, tabBar simpleTabBar, tabBar
, def, defaultTheme, shrinkText , def, shrinkText
, TabBarDecoration (..), XPPosition (..) , TabBarDecoration (..), XPPosition (..)
, module XMonad.Layout.ResizeScreen , module XMonad.Layout.ResizeScreen
) where ) where

View File

@ -27,7 +27,6 @@ module XMonad.Layout.Tabbed
, simpleTabbedRightAlways, tabbedRightAlways, addTabsRightAlways , simpleTabbedRightAlways, tabbedRightAlways, addTabsRightAlways
, Theme (..) , Theme (..)
, def , def
, defaultTheme
, TabbedDecoration (..) , TabbedDecoration (..)
, shrinkText, CustomShrink(CustomShrink) , shrinkText, CustomShrink(CustomShrink)
, Shrinker(..) , Shrinker(..)

View File

@ -21,8 +21,8 @@ module XMonad.Layout.WindowNavigation (
Navigate(..), Direction2D(..), Navigate(..), Direction2D(..),
MoveWindowToWindow(..), MoveWindowToWindow(..),
navigateColor, navigateBrightness, navigateColor, navigateBrightness,
noNavigateBorders, defaultWNConfig, def, noNavigateBorders, def, WNConfig,
WNConfig, WindowNavigation, WindowNavigation,
) where ) where
import Data.List ( nub, sortBy, (\\) ) 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" 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 NavigationState a = NS Point [(a,Rectangle)]
data WindowNavigation a = WindowNavigation WNConfig (Invisible Maybe (NavigationState a)) deriving ( Read, Show ) data WindowNavigation a = WindowNavigation WNConfig (Invisible Maybe (NavigationState a)) deriving ( Read, Show )

View File

@ -34,7 +34,6 @@ module XMonad.Prompt
, mkXPromptWithModes , mkXPromptWithModes
, def , def
, amberXPConfig , amberXPConfig
, defaultXPConfig
, greenXPConfig , greenXPConfig
, XPMode , XPMode
, XPType (..) , XPType (..)
@ -294,7 +293,7 @@ data XPColor =
, border :: String -- ^ Border color , border :: String -- ^ Border color
} }
amberXPConfig, defaultXPConfig, greenXPConfig :: XPConfig amberXPConfig, greenXPConfig :: XPConfig
instance Default XPColor where instance Default XPColor where
def = def =
@ -331,8 +330,6 @@ instance Default XPConfig where
, defaultPrompter = id , defaultPrompter = id
, sorter = const id , sorter = const id
} }
{-# DEPRECATED defaultXPConfig "Use def (from Data.Default, and re-exported from XMonad.Prompt) instead." #-}
defaultXPConfig = def
greenXPConfig = def { bgColor = "black" greenXPConfig = def { bgColor = "black"
, fgColor = "green" , fgColor = "green"
, promptBorderWidth = 0 , promptBorderWidth = 0

View File

@ -35,7 +35,7 @@ will then run normally if the user confirms.
This should be used something like this: 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))
> ... > ...
-} -}

View File

@ -49,12 +49,12 @@ import XMonad.Prompt
-- @fireEmployee@ action, like so: -- @fireEmployee@ action, like so:
-- --
-- > firingPrompt :: X () -- > firingPrompt :: X ()
-- > firingPrompt = inputPrompt defaultXPConfig "Fire" ?+ fireEmployee -- > firingPrompt = inputPrompt def "Fire" ?+ fireEmployee
-- --
-- If @employees@ contains a list of all his employees, he could also -- If @employees@ contains a list of all his employees, he could also
-- create an autocompleting version, like this: -- create an autocompleting version, like this:
-- --
-- > firingPrompt' = inputPromptWithCompl defaultXPConfig "Fire" -- > firingPrompt' = inputPromptWithCompl def "Fire"
-- > (mkComplFunFromList employees) ?+ fireEmployee -- > (mkComplFunFromList employees) ?+ fireEmployee
-- --
-- Now all he has to do is add a keybinding to @firingPrompt@ (or -- Now all he has to do is add a keybinding to @firingPrompt@ (or

View File

@ -41,8 +41,8 @@ import qualified Data.Map as Map
-- > -- >
-- > -- LogHook -- > -- LogHook
-- > logHook' = do -- > logHook' = do
-- > mh <- getNamedPipeHandle "dzenPipe" -- > mh <- getNamedPipeHandle "dzenPipe"
-- > dynamicLogWithPP $ defaultPP { -- > dynamicLogWithPP $ def {
-- > ppOutput = maybe (\s -> return ()) (hPutStrLn) mh} -- > ppOutput = maybe (\s -> return ()) (hPutStrLn) mh}
-- > -- >
-- > -- Main -- > -- Main