diff --git a/XMonad/Actions/CycleWorkspaceByScreen.hs b/XMonad/Actions/CycleWorkspaceByScreen.hs index f8eedcb4..f05d887d 100644 --- a/XMonad/Actions/CycleWorkspaceByScreen.hs +++ b/XMonad/Actions/CycleWorkspaceByScreen.hs @@ -1,4 +1,3 @@ - ----------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.CycleWorkspaceByScreen diff --git a/XMonad/Actions/DynamicProjects.hs b/XMonad/Actions/DynamicProjects.hs index 0833d8b0..5d63841c 100644 --- a/XMonad/Actions/DynamicProjects.hs +++ b/XMonad/Actions/DynamicProjects.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - -------------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.DynamicProjects @@ -126,14 +124,14 @@ data Project = Project { projectName :: !ProjectName -- ^ Workspace name. , projectDirectory :: !FilePath -- ^ Working directory. , projectStartHook :: !(Maybe (X ())) -- ^ Optional start-up hook. - } deriving Typeable + } -------------------------------------------------------------------------------- -- | Internal project state. data ProjectState = ProjectState { projects :: !ProjectTable , previousProject :: !(Maybe WorkspaceId) - } deriving Typeable + } -------------------------------------------------------------------------------- instance ExtensionClass ProjectState where diff --git a/XMonad/Actions/DynamicWorkspaceGroups.hs b/XMonad/Actions/DynamicWorkspaceGroups.hs index 6740b24e..9ae2f0a7 100644 --- a/XMonad/Actions/DynamicWorkspaceGroups.hs +++ b/XMonad/Actions/DynamicWorkspaceGroups.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ----------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.DynamicWorkspaceGroups @@ -69,7 +67,7 @@ type WSGroup = [(ScreenId,WorkspaceId)] type WSGroupId = String newtype WSGroupStorage = WSG { unWSG :: M.Map WSGroupId WSGroup } - deriving (Typeable, Read, Show) + deriving (Read, Show) withWSG :: (M.Map WSGroupId WSGroup -> M.Map WSGroupId WSGroup) -> WSGroupStorage -> WSGroupStorage withWSG f = WSG . f . unWSG diff --git a/XMonad/Actions/DynamicWorkspaceOrder.hs b/XMonad/Actions/DynamicWorkspaceOrder.hs index 28b54b09..00b65c4f 100644 --- a/XMonad/Actions/DynamicWorkspaceOrder.hs +++ b/XMonad/Actions/DynamicWorkspaceOrder.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ----------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.DynamicWorkspaceOrder @@ -90,7 +88,7 @@ import Data.Ord (comparing) -- | Extensible state storage for the workspace order. newtype WSOrderStorage = WSO { unWSO :: Maybe (M.Map WorkspaceId Int) } - deriving (Typeable, Read, Show) + deriving (Read, Show) instance ExtensionClass WSOrderStorage where initialValue = WSO Nothing diff --git a/XMonad/Actions/DynamicWorkspaces.hs b/XMonad/Actions/DynamicWorkspaces.hs index 24332d40..d099657d 100644 --- a/XMonad/Actions/DynamicWorkspaces.hs +++ b/XMonad/Actions/DynamicWorkspaces.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ----------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.DynamicWorkspaces @@ -87,7 +85,7 @@ type WorkspaceIndex = Int -- | Internal dynamic project state that stores a mapping between -- workspace indexes and workspace tags. newtype DynamicWorkspaceState = DynamicWorkspaceState {workspaceIndexMap :: Map.Map WorkspaceIndex WorkspaceTag} - deriving (Typeable, Read, Show) + deriving (Read, Show) instance ExtensionClass DynamicWorkspaceState where initialValue = DynamicWorkspaceState Map.empty diff --git a/XMonad/Actions/FloatKeys.hs b/XMonad/Actions/FloatKeys.hs index 42d5fa06..da77fae3 100644 --- a/XMonad/Actions/FloatKeys.hs +++ b/XMonad/Actions/FloatKeys.hs @@ -117,4 +117,3 @@ keysMoveResize f move resize w = whenX (isClient w) $ withDisplay $ \d -> do io $ resizeWindow d w `uncurry` wn_dim io $ moveWindow d w `uncurry` wn_pos float w - diff --git a/XMonad/Actions/FocusNth.hs b/XMonad/Actions/FocusNth.hs index fd0b031c..bf02e721 100644 --- a/XMonad/Actions/FocusNth.hs +++ b/XMonad/Actions/FocusNth.hs @@ -57,5 +57,3 @@ listToStack n l = Stack t ls rs where (t:rs) = drop n l ls = reverse (take n l) - - diff --git a/XMonad/Actions/GroupNavigation.hs b/XMonad/Actions/GroupNavigation.hs index a1f25383..41592e6a 100644 --- a/XMonad/Actions/GroupNavigation.hs +++ b/XMonad/Actions/GroupNavigation.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ---------------------------------------------------------------------- -- | -- Module : XMonad.Actions.GroupNavigation @@ -157,7 +155,7 @@ orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs' -- The state extension that holds the history information data HistoryDB = HistoryDB (Maybe Window) -- currently focused window (Seq Window) -- previously focused windows - deriving (Read, Show, Typeable) + deriving (Read, Show) instance ExtensionClass HistoryDB where diff --git a/XMonad/Actions/KeyRemap.hs b/XMonad/Actions/KeyRemap.hs index cbf14140..0040af8f 100644 --- a/XMonad/Actions/KeyRemap.hs +++ b/XMonad/Actions/KeyRemap.hs @@ -1,4 +1,3 @@ - {-# LANGUAGE DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.KeyRemap @@ -33,7 +32,7 @@ import XMonad.Util.Paste import qualified XMonad.Util.ExtensibleState as XS -newtype KeymapTable = KeymapTable [((KeyMask, KeySym), (KeyMask, KeySym))] deriving (Typeable, Show) +newtype KeymapTable = KeymapTable [((KeyMask, KeySym), (KeyMask, KeySym))] deriving (Show) instance ExtensionClass KeymapTable where initialValue = KeymapTable [] diff --git a/XMonad/Actions/LinkWorkspaces.hs b/XMonad/Actions/LinkWorkspaces.hs index 7112144e..b4af18b3 100644 --- a/XMonad/Actions/LinkWorkspaces.hs +++ b/XMonad/Actions/LinkWorkspaces.hs @@ -14,7 +14,6 @@ -- ----------------------------------------------------------------------------- -{-# LANGUAGE DeriveDataTypeable #-} module XMonad.Actions.LinkWorkspaces ( -- * Usage -- $usage @@ -76,7 +75,7 @@ noMessageFn :: ScreenId -> [Char] -> [Char] -> [Char] -> X() noMessageFn _ _ _ _ = return () :: X () -- | Stuff for linking workspaces -newtype WorkspaceMap = WorkspaceMap (M.Map WorkspaceId WorkspaceId) deriving (Read, Show, Typeable) +newtype WorkspaceMap = WorkspaceMap (M.Map WorkspaceId WorkspaceId) deriving (Read, Show) instance ExtensionClass WorkspaceMap where initialValue = WorkspaceMap M.empty extensionType = PersistentExtension diff --git a/XMonad/Actions/Navigation2D.hs b/XMonad/Actions/Navigation2D.hs index a698f551..a8eb1136 100644 --- a/XMonad/Actions/Navigation2D.hs +++ b/XMonad/Actions/Navigation2D.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, MultiParamTypeClasses, PatternGuards, RankNTypes, TypeSynonymInstances #-} +{-# LANGUAGE MultiParamTypeClasses, PatternGuards, RankNTypes, TypeSynonymInstances #-} ----------------------------------------------------------------------------- -- | @@ -384,7 +384,7 @@ data Navigation2DConfig = Navigation2DConfig -- function calculates a rectangle for a given unmapped -- window from the screen it is on and its window ID. -- See <#Finer_Points> for how to use this. - } deriving Typeable + } -- | Shorthand for the tedious screen type type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail diff --git a/XMonad/Actions/PerWorkspaceKeys.hs b/XMonad/Actions/PerWorkspaceKeys.hs index 20705e1c..82d8626f 100644 --- a/XMonad/Actions/PerWorkspaceKeys.hs +++ b/XMonad/Actions/PerWorkspaceKeys.hs @@ -46,4 +46,3 @@ bindOn bindings = chooseAction chooser where Nothing -> case lookup "" bindings of Just action -> action Nothing -> return () - diff --git a/XMonad/Actions/Prefix.hs b/XMonad/Actions/Prefix.hs index fc3db78e..00d22348 100644 --- a/XMonad/Actions/Prefix.hs +++ b/XMonad/Actions/Prefix.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleContexts #-} +{-# LANGUAGE FlexibleContexts #-} ----------------------------------------------------------------------------- -- | @@ -110,7 +110,7 @@ implementation is the following: -} data PrefixArgument = Raw Int | Numeric Int | None - deriving (Typeable, Read, Show) + deriving (Read, Show) instance ExtensionClass PrefixArgument where initialValue = None extensionType = PersistentExtension diff --git a/XMonad/Actions/ShowText.hs b/XMonad/Actions/ShowText.hs index bbf8371b..dbd09b75 100644 --- a/XMonad/Actions/ShowText.hs +++ b/XMonad/Actions/ShowText.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable #-} -{-# LANGUAGE CPP #-} +{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.ShowText @@ -56,7 +55,7 @@ import qualified XMonad.Util.ExtensibleState as ES -- | ShowText contains the map with timers as keys and created windows as values newtype ShowText = ShowText (Map Atom Window) - deriving (Read,Show,Typeable) + deriving (Read,Show) instance ExtensionClass ShowText where initialValue = ShowText empty diff --git a/XMonad/Actions/SpawnOn.hs b/XMonad/Actions/SpawnOn.hs index f345203a..c0526bf5 100644 --- a/XMonad/Actions/SpawnOn.hs +++ b/XMonad/Actions/SpawnOn.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.SpawnOn @@ -66,7 +65,7 @@ import qualified XMonad.Util.ExtensibleState as XS -- For detailed instructions on editing your key bindings, see -- "XMonad.Doc.Extending#Editing_key_bindings". -newtype Spawner = Spawner {pidsRef :: [(ProcessID, ManageHook)]} deriving Typeable +newtype Spawner = Spawner {pidsRef :: [(ProcessID, ManageHook)]} instance ExtensionClass Spawner where initialValue = Spawner [] diff --git a/XMonad/Actions/SwapPromote.hs b/XMonad/Actions/SwapPromote.hs index 1cb34c3f..cb8b024b 100644 --- a/XMonad/Actions/SwapPromote.hs +++ b/XMonad/Actions/SwapPromote.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ----------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.SwapPromote @@ -115,7 +113,7 @@ import Control.Arrow -- Without history, the list is empty. newtype MasterHistory = MasterHistory { getMasterHistory :: M.Map WorkspaceId [Window] - } deriving (Read,Show,Typeable) + } deriving (Read,Show) instance ExtensionClass MasterHistory where initialValue = MasterHistory M.empty diff --git a/XMonad/Actions/WithAll.hs b/XMonad/Actions/WithAll.hs index ee3a26d0..ca360579 100644 --- a/XMonad/Actions/WithAll.hs +++ b/XMonad/Actions/WithAll.hs @@ -49,4 +49,4 @@ withAll f = withWindowSet $ \ws -> let all' = integrate' . stack . workspace . c -- | Kill all the windows on the current workspace. killAll :: X() -killAll = withAll killWindow \ No newline at end of file +killAll = withAll killWindow diff --git a/XMonad/Actions/Workscreen.hs b/XMonad/Actions/Workscreen.hs index 42b10dcd..56340e1f 100644 --- a/XMonad/Actions/Workscreen.hs +++ b/XMonad/Actions/Workscreen.hs @@ -20,7 +20,6 @@ -- This also permits to see all workspaces of a workscreen even if just -- one screen is present, and to move windows from workspace to workscreen. ----------------------------------------------------------------------------- -{-# LANGUAGE DeriveDataTypeable #-} module XMonad.Actions.Workscreen ( -- * Usage @@ -58,10 +57,10 @@ import XMonad.Actions.OnScreen -- "XMonad.Doc.Extending#Editing_key_bindings". -data Workscreen = Workscreen{workscreenId::Int,workspaces::[WorkspaceId]} deriving (Show,Typeable) +data Workscreen = Workscreen{workscreenId::Int,workspaces::[WorkspaceId]} deriving (Show) type WorkscreenId=Int -data WorkscreenStorage = WorkscreenStorage WorkscreenId [Workscreen] deriving (Show,Typeable) +data WorkscreenStorage = WorkscreenStorage WorkscreenId [Workscreen] deriving (Show) instance ExtensionClass WorkscreenStorage where initialValue = WorkscreenStorage 0 [] diff --git a/XMonad/Actions/WorkspaceCursors.hs b/XMonad/Actions/WorkspaceCursors.hs index 31a01bd3..89aebae0 100644 --- a/XMonad/Actions/WorkspaceCursors.hs +++ b/XMonad/Actions/WorkspaceCursors.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Actions.WorkspaceCursors @@ -46,7 +46,7 @@ import qualified XMonad.StackSet as W import XMonad.Actions.FocusNth(focusNth') import XMonad.Layout.LayoutModifier(ModifiedLayout(..), LayoutModifier(handleMess, redoLayout)) -import XMonad(Typeable, Message, WorkspaceId, X, XState(windowset), +import XMonad(Message, WorkspaceId, X, XState(windowset), fromMessage, sendMessage, windows, gets) import XMonad.Util.Stack (reverseS) import XMonad.Prelude (find, fromJust, guard, liftA2, toList, when, (<=<)) @@ -114,7 +114,7 @@ end = Cons . fromJust . W.differentiate . map End data Cursors a = Cons (W.Stack (Cursors a)) - | End a deriving (Eq,Show,Read,Typeable) + | End a deriving (Eq,Show,Read) instance Foldable Cursors where foldMap f (End x) = f x @@ -190,7 +190,7 @@ modifyCursors :: (Cursors String -> X (Cursors String)) -> X () modifyCursors = sendMessage . ChangeCursors . (liftA2 (>>) updateXMD return <=<) newtype WorkspaceCursors a = WorkspaceCursors (Cursors String) - deriving (Typeable,Read,Show) + deriving (Read,Show) -- | The state is stored in the 'WorkspaceCursors' layout modifier. Put this as -- your outermost modifier, unless you want different cursors at different @@ -199,7 +199,6 @@ workspaceCursors :: Cursors String -> l a -> ModifiedLayout WorkspaceCursors l a workspaceCursors = ModifiedLayout . WorkspaceCursors newtype ChangeCursors = ChangeCursors { unWrap :: Cursors String -> X (Cursors String) } - deriving (Typeable) instance Message ChangeCursors diff --git a/XMonad/Actions/WorkspaceNames.hs b/XMonad/Actions/WorkspaceNames.hs index 8114e8f4..cde4ce13 100644 --- a/XMonad/Actions/WorkspaceNames.hs +++ b/XMonad/Actions/WorkspaceNames.hs @@ -15,8 +15,6 @@ -- ----------------------------------------------------------------------------- -{-# LANGUAGE DeriveDataTypeable #-} - module XMonad.Actions.WorkspaceNames ( -- * Usage -- $usage @@ -87,7 +85,7 @@ import qualified Data.Map as M -- | Workspace names container. newtype WorkspaceNames = WorkspaceNames (M.Map WorkspaceId String) - deriving (Typeable, Read, Show) + deriving (Read, Show) instance ExtensionClass WorkspaceNames where initialValue = WorkspaceNames M.empty diff --git a/XMonad/Config/Saegesser.hs b/XMonad/Config/Saegesser.hs index b09f79be..53ead7a0 100755 --- a/XMonad/Config/Saegesser.hs +++ b/XMonad/Config/Saegesser.hs @@ -76,4 +76,3 @@ myLogHook p = do , ppTitle = xmobarColor "green" "" . shorten 180 } fadeInactiveLogHook 0.6 - diff --git a/XMonad/Doc/Configuring.hs b/XMonad/Doc/Configuring.hs index 363a4c3d..dfa7ff34 100644 --- a/XMonad/Doc/Configuring.hs +++ b/XMonad/Doc/Configuring.hs @@ -148,4 +148,3 @@ GHC and xmonad are in the @$PATH@ in the environment from which xmonad is started. -} - diff --git a/XMonad/Hooks/CurrentWorkspaceOnTop.hs b/XMonad/Hooks/CurrentWorkspaceOnTop.hs index d7e43bba..f26f83a6 100644 --- a/XMonad/Hooks/CurrentWorkspaceOnTop.hs +++ b/XMonad/Hooks/CurrentWorkspaceOnTop.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} ---------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.CurrentWorkspaceOnTop @@ -40,7 +39,7 @@ import qualified Data.Map as M -- > } -- -newtype CWOTState = CWOTS String deriving Typeable +newtype CWOTState = CWOTS String instance ExtensionClass CWOTState where initialValue = CWOTS "" diff --git a/XMonad/Hooks/DynamicBars.hs b/XMonad/Hooks/DynamicBars.hs index 0c130ea8..7202cfb8 100644 --- a/XMonad/Hooks/DynamicBars.hs +++ b/XMonad/Hooks/DynamicBars.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.DynamicBars @@ -81,7 +80,7 @@ import qualified XMonad.Util.ExtensibleState as XS newtype DynStatusBarInfo = DynStatusBarInfo { dsbInfo :: [(ScreenId, Handle)] - } deriving (Typeable) + } instance ExtensionClass DynStatusBarInfo where initialValue = DynStatusBarInfo [] diff --git a/XMonad/Hooks/DynamicHooks.hs b/XMonad/Hooks/DynamicHooks.hs index 5ddc8985..6b19d268 100644 --- a/XMonad/Hooks/DynamicHooks.hs +++ b/XMonad/Hooks/DynamicHooks.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.DynamicHooks @@ -48,7 +47,6 @@ import qualified XMonad.Util.ExtensibleState as XS data DynamicHooks = DynamicHooks { transients :: [(Query Bool, ManageHook)] , permanent :: ManageHook } - deriving Typeable instance ExtensionClass DynamicHooks where initialValue = DynamicHooks [] idHook diff --git a/XMonad/Hooks/EwmhDesktops.hs b/XMonad/Hooks/EwmhDesktops.hs index 74ceb542..69123303 100644 --- a/XMonad/Hooks/EwmhDesktops.hs +++ b/XMonad/Hooks/EwmhDesktops.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE PatternGuards #-} @@ -111,7 +110,7 @@ ewmhDesktopsLogHook = ewmhDesktopsLogHookCustom id -- Cached desktop names (e.g. @_NET_NUMBER_OF_DESKTOPS@ and -- @_NET_DESKTOP_NAMES@). newtype DesktopNames = DesktopNames [String] - deriving (Eq) + deriving Eq instance ExtensionClass DesktopNames where initialValue = DesktopNames [] @@ -119,7 +118,7 @@ instance ExtensionClass DesktopNames where -- | -- Cached client list (e.g. @_NET_CLIENT_LIST@). newtype ClientList = ClientList [Window] - deriving (Eq) + deriving Eq instance ExtensionClass ClientList where initialValue = ClientList [none] @@ -127,7 +126,7 @@ instance ExtensionClass ClientList where -- | -- Cached current desktop (e.g. @_NET_CURRENT_DESKTOP@). newtype CurrentDesktop = CurrentDesktop Int - deriving (Eq) + deriving Eq instance ExtensionClass CurrentDesktop where initialValue = CurrentDesktop (-1) @@ -135,7 +134,7 @@ instance ExtensionClass CurrentDesktop where -- | -- Cached window-desktop assignments (e.g. @_NET_CLIENT_LIST_STACKING@). newtype WindowDesktops = WindowDesktops (M.Map Window Int) - deriving (Eq) + deriving Eq instance ExtensionClass WindowDesktops where initialValue = WindowDesktops (M.singleton none (-1)) @@ -144,7 +143,7 @@ instance ExtensionClass WindowDesktops where -- The value of @_NET_ACTIVE_WINDOW@, cached to avoid unnecessary property -- updates. newtype ActiveWindow = ActiveWindow Window - deriving (Eq) + deriving Eq instance ExtensionClass ActiveWindow where initialValue = ActiveWindow (complement none) @@ -217,7 +216,7 @@ ewmhDesktopsEventHookCustom f e = handle f e >> return (All True) -- this value in global state, because i use 'logHook' for handling activated -- windows and i need a way to tell 'logHook' what window is activated. newtype NetActivated = NetActivated {netActivated :: Maybe Window} - deriving (Show, Typeable) + deriving Show instance ExtensionClass NetActivated where initialValue = NetActivated Nothing diff --git a/XMonad/Hooks/Focus.hs b/XMonad/Hooks/Focus.hs index 5e5fb578..b235cb44 100644 --- a/XMonad/Hooks/Focus.hs +++ b/XMonad/Hooks/Focus.hs @@ -1,6 +1,5 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable #-} {-# OPTIONS_HADDOCK show-extensions #-} -- | @@ -349,7 +348,7 @@ instance Default Focus where } newtype FocusLock = FocusLock {getFocusLock :: Bool} - deriving (Show, Typeable) + deriving (Show) instance ExtensionClass FocusLock where initialValue = FocusLock False diff --git a/XMonad/Hooks/ICCCMFocus.hs b/XMonad/Hooks/ICCCMFocus.hs index ad74f6aa..5395824c 100644 --- a/XMonad/Hooks/ICCCMFocus.hs +++ b/XMonad/Hooks/ICCCMFocus.hs @@ -39,4 +39,3 @@ takeTopFocus :: X () takeTopFocus = withWindowSet (maybe (setFocusX =<< asks theRoot) takeFocusX . W.peek) >> setWMName "LG3D" - diff --git a/XMonad/Hooks/ManageDebug.hs b/XMonad/Hooks/ManageDebug.hs index 98958e95..626f0a35 100644 --- a/XMonad/Hooks/ManageDebug.hs +++ b/XMonad/Hooks/ManageDebug.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ----------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.ManageDebug @@ -36,7 +34,7 @@ import XMonad.Util.EZConfig import qualified XMonad.Util.ExtensibleState as XS -- persistent state for manageHook debugging to trigger logHook debugging -newtype ManageStackDebug = MSD (Bool,Bool) deriving Typeable +newtype ManageStackDebug = MSD (Bool,Bool) instance ExtensionClass ManageStackDebug where initialValue = MSD (False,False) diff --git a/XMonad/Hooks/ManageDocks.hs b/XMonad/Hooks/ManageDocks.hs index cd3e9956..608b9682 100644 --- a/XMonad/Hooks/ManageDocks.hs +++ b/XMonad/Hooks/ManageDocks.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, PatternGuards, FlexibleInstances, MultiParamTypeClasses, CPP #-} +{-# LANGUAGE PatternGuards, FlexibleInstances, MultiParamTypeClasses, CPP #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.ManageDocks @@ -90,7 +90,7 @@ docks c = c { startupHook = docksStartupHook <+> startupHook c type WindowStruts = M.Map Window [Strut] -data UpdateDocks = UpdateDocks deriving Typeable +data UpdateDocks = UpdateDocks instance Message UpdateDocks refreshDocks :: X () @@ -98,7 +98,7 @@ refreshDocks = sendMessage UpdateDocks -- Nothing means cache hasn't been initialized yet newtype StrutCache = StrutCache { fromStrutCache :: Maybe WindowStruts } - deriving (Eq, Typeable) + deriving Eq instance ExtensionClass StrutCache where initialValue = StrutCache Nothing @@ -227,7 +227,7 @@ newtype AvoidStruts a = AvoidStruts (S.Set Direction2D) deriving ( Read, Show ) -- modifier to alter its behavior. data ToggleStruts = ToggleStruts | ToggleStrut Direction2D - deriving (Read,Show,Typeable) + deriving (Read,Show) instance Message ToggleStruts @@ -253,7 +253,7 @@ instance Message ToggleStruts data SetStruts = SetStruts { addedStruts :: [Direction2D] , removedStruts :: [Direction2D] -- ^ These are removed from the currently set struts before 'addedStruts' are added. } - deriving (Read,Show,Typeable) + deriving (Read,Show) instance Message SetStruts diff --git a/XMonad/Hooks/RefocusLast.hs b/XMonad/Hooks/RefocusLast.hs index c7a07243..886361cb 100644 --- a/XMonad/Hooks/RefocusLast.hs +++ b/XMonad/Hooks/RefocusLast.hs @@ -110,7 +110,7 @@ data RecentWins = Recent { previous :: !Window, current :: !Window } -- | Newtype wrapper for a @Map@ holding the @RecentWins@ for each workspace. -- Is an instance of @ExtensionClass@ with persistence of state. newtype RecentsMap = RecentsMap (M.Map WorkspaceId RecentWins) - deriving (Show, Read, Eq, Typeable) + deriving (Show, Read, Eq) instance ExtensionClass RecentsMap where initialValue = RecentsMap M.empty @@ -126,7 +126,7 @@ instance LayoutModifier RefocusLastLayoutHook a where -- | A newtype on @Bool@ to act as a universal toggle for refocusing. newtype RefocusLastToggle = RefocusLastToggle { refocusing :: Bool } - deriving (Show, Read, Eq, Typeable) + deriving (Show, Read, Eq) instance ExtensionClass RefocusLastToggle where initialValue = RefocusLastToggle { refocusing = True } diff --git a/XMonad/Hooks/ScreenCorners.hs b/XMonad/Hooks/ScreenCorners.hs index a9033646..d21f10bf 100644 --- a/XMonad/Hooks/ScreenCorners.hs +++ b/XMonad/Hooks/ScreenCorners.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, TupleSections #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TupleSections #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.ScreenCorners @@ -43,14 +43,11 @@ data ScreenCorner = SCUpperLeft | SCLowerRight deriving (Eq, Ord, Show) - - -------------------------------------------------------------------------------- -- ExtensibleState modifications -------------------------------------------------------------------------------- newtype ScreenCornerState = ScreenCornerState (M.Map Window (ScreenCorner, X ())) - deriving Typeable instance ExtensionClass ScreenCornerState where initialValue = ScreenCornerState M.empty diff --git a/XMonad/Hooks/ToggleHook.hs b/XMonad/Hooks/ToggleHook.hs index c22d2920..3dddf5df 100644 --- a/XMonad/Hooks/ToggleHook.hs +++ b/XMonad/Hooks/ToggleHook.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.ToggleHook @@ -62,7 +61,7 @@ _pp n f s st = (\b -> guard b >> Just (st s)) <$> _get n f {- The current state is kept here -} -newtype HookState = HookState { hooks :: Map String (Bool, Bool) } deriving (Typeable, Read, Show) +newtype HookState = HookState { hooks :: Map String (Bool, Bool) } deriving (Read, Show) instance ExtensionClass HookState where initialValue = HookState empty diff --git a/XMonad/Hooks/UrgencyHook.hs b/XMonad/Hooks/UrgencyHook.hs index 6b33f1e5..042c1a95 100644 --- a/XMonad/Hooks/UrgencyHook.hs +++ b/XMonad/Hooks/UrgencyHook.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, DeriveDataTypeable, FlexibleInstances #-} +{-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-} ----------------------------------------------------------------------------- -- | @@ -210,7 +210,7 @@ withUrgencyHookC hook urgConf conf = conf { startupHook = cleanupStaleUrgents >> startupHook conf } -newtype Urgents = Urgents { fromUrgents :: [Window] } deriving (Read,Show,Typeable) +newtype Urgents = Urgents { fromUrgents :: [Window] } deriving (Read,Show) onUrgents :: ([Window] -> [Window]) -> Urgents -> Urgents onUrgents f = Urgents . f . fromUrgents @@ -295,7 +295,7 @@ data Reminder = Reminder { timer :: TimerId , window :: Window , interval :: Interval , remaining :: Maybe Int - } deriving (Show,Read,Eq,Typeable) + } deriving (Show,Read,Eq) instance ExtensionClass [Reminder] where initialValue = [] diff --git a/XMonad/Hooks/WallpaperSetter.hs b/XMonad/Hooks/WallpaperSetter.hs index 4c448aff..784afbbd 100644 --- a/XMonad/Hooks/WallpaperSetter.hs +++ b/XMonad/Hooks/WallpaperSetter.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} ----------------------------------- -- | -- Module : XMonad.Hooks.WallpaperSetter @@ -62,7 +61,7 @@ import qualified Data.Map as M -- * find out how to merge multiple images from stdin to one (-> for caching all pictures in memory) -- | internal. to use XMonad state for memory in-between log-hook calls and remember PID of old external call -data WCState = WCState (Maybe [WorkspaceId]) (Maybe ProcessHandle) deriving Typeable +data WCState = WCState (Maybe [WorkspaceId]) (Maybe ProcessHandle) instance ExtensionClass WCState where initialValue = WCState Nothing Nothing diff --git a/XMonad/Hooks/WindowSwallowing.hs b/XMonad/Hooks/WindowSwallowing.hs index f7672d02..0567d1c9 100644 --- a/XMonad/Hooks/WindowSwallowing.hs +++ b/XMonad/Hooks/WindowSwallowing.hs @@ -208,7 +208,7 @@ data SwallowingState = { currentlySwallowed :: M.Map Window Window -- ^ mapping from child window window to the currently swallowed parent window , stackBeforeWindowClosing :: Maybe (W.Stack Window) -- ^ current stack state right before DestroyWindowEvent is sent , floatingBeforeClosing :: M.Map Window W.RationalRect -- ^ floating map of the stackset right before DestroyWindowEvent is sent - } deriving (Typeable, Show) + } deriving (Show) getSwallowedParent :: Window -> SwallowingState -> Maybe Window getSwallowedParent win SwallowingState { currentlySwallowed } = diff --git a/XMonad/Hooks/WorkspaceHistory.hs b/XMonad/Hooks/WorkspaceHistory.hs index 0cb2af9d..fdb9fc85 100644 --- a/XMonad/Hooks/WorkspaceHistory.hs +++ b/XMonad/Hooks/WorkspaceHistory.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ----------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.WorkspaceHistory @@ -64,7 +62,7 @@ import qualified XMonad.Util.ExtensibleState as XS newtype WorkspaceHistory = WorkspaceHistory { history :: [(ScreenId, WorkspaceId)] -- ^ Workspace Screens in -- reverse-chronological order. - } deriving (Typeable, Read, Show) + } deriving (Read, Show) instance ExtensionClass WorkspaceHistory where initialValue = WorkspaceHistory [] diff --git a/XMonad/Layout/AvoidFloats.hs b/XMonad/Layout/AvoidFloats.hs index ca906d63..0b820e44 100644 --- a/XMonad/Layout/AvoidFloats.hs +++ b/XMonad/Layout/AvoidFloats.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, TupleSections #-} +{-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, TupleSections #-} ----------------------------------------------------------------------------- -- | @@ -90,15 +90,12 @@ data AvoidFloatMsg = AvoidFloatToggle -- ^ Toggle between avoiding all or only selected. | AvoidFloatSet Bool -- ^ Set if all all floating windows should be avoided. | AvoidFloatClearItems -- ^ Clear the set of windows to specifically avoid. - deriving (Typeable) - -- | Change the state of the avoid float layout modifier conserning a specific window. data AvoidFloatItemMsg a = AvoidFloatAddItem a -- ^ Add a window to always avoid. | AvoidFloatRemoveItem a -- ^ Stop always avoiding selected window. | AvoidFloatToggleItem a -- ^ Toggle between always avoiding selected window. - deriving (Typeable) instance Message AvoidFloatMsg instance Typeable a => Message (AvoidFloatItemMsg a) diff --git a/XMonad/Layout/BinarySpacePartition.hs b/XMonad/Layout/BinarySpacePartition.hs index d243ef7a..2c392462 100644 --- a/XMonad/Layout/BinarySpacePartition.hs +++ b/XMonad/Layout/BinarySpacePartition.hs @@ -1,7 +1,7 @@ {-# LANGUAGE PatternGuards #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE DoAndIfThenElse #-} -{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.BinarySpacePartition @@ -112,18 +112,18 @@ import Data.Ratio ((%)) -- -- | Message for rotating the binary tree around the parent node of the window to the left or right -data TreeRotate = RotateL | RotateR deriving Typeable +data TreeRotate = RotateL | RotateR instance Message TreeRotate -- | Message to balance the tree in some way (Balance retiles the windows, Equalize changes ratios) -data TreeBalance = Balance | Equalize deriving Typeable +data TreeBalance = Balance | Equalize instance Message TreeBalance -- | Message for resizing one of the cells in the BSP data ResizeDirectional = ExpandTowardsBy Direction2D Rational | ShrinkFromBy Direction2D Rational - | MoveSplitBy Direction2D Rational deriving Typeable + | MoveSplitBy Direction2D Rational instance Message ResizeDirectional -- | @ExpandTowards x@ is now the equivalent of @ExpandTowardsBy x 0.05@ @@ -139,25 +139,25 @@ pattern MoveSplit :: Direction2D -> ResizeDirectional pattern MoveSplit d = MoveSplitBy d 0.05 -- | Message for rotating a split (horizontal/vertical) in the BSP -data Rotate = Rotate deriving Typeable +data Rotate = Rotate instance Message Rotate -- | Message for swapping the left child of a split with the right child of split -data Swap = Swap deriving Typeable +data Swap = Swap instance Message Swap -- | Message to cyclically select the parent node instead of the leaf -data FocusParent = FocusParent deriving Typeable +data FocusParent = FocusParent instance Message FocusParent -- | Message to move nodes inside the tree -data SelectMoveNode = SelectNode | MoveNode deriving Typeable +data SelectMoveNode = SelectNode | MoveNode instance Message SelectMoveNode data Axis = Horizontal | Vertical deriving (Show, Read, Eq) -- | Message for shifting window by splitting its neighbour -newtype SplitShiftDirectional = SplitShift Direction1D deriving Typeable +newtype SplitShiftDirectional = SplitShift Direction1D instance Message SplitShiftDirectional oppositeDirection :: Direction2D -> Direction2D diff --git a/XMonad/Layout/BoringWindows.hs b/XMonad/Layout/BoringWindows.hs index 1161edb8..2654905b 100644 --- a/XMonad/Layout/BoringWindows.hs +++ b/XMonad/Layout/BoringWindows.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE MultiParamTypeClasses, DeriveDataTypeable #-} +{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances #-} ----------------------------------------------------------------------------- -- | @@ -34,7 +34,7 @@ module XMonad.Layout.BoringWindows ( import XMonad.Layout.LayoutModifier(ModifiedLayout(..), LayoutModifier(handleMessOrMaybeModifyIt, redoLayout)) -import XMonad(Typeable, LayoutClass, Message, X, fromMessage, +import XMonad(LayoutClass, Message, X, fromMessage, broadcastMessage, sendMessage, windows, withFocused, Window) import XMonad.Prelude (find, fromMaybe, listToMaybe, maybeToList, union, (\\)) import XMonad.Util.Stack (reverseS) @@ -70,14 +70,13 @@ data BoringMessage = FocusUp | FocusDown | FocusMaster | IsBoring Window | Clear | SwapDown | SiftUp | SiftDown - deriving ( Read, Show, Typeable ) + deriving ( Read, Show ) instance Message BoringMessage -- | UpdateBoring is sent before attempting to view another boring window, so -- that layouts have a chance to mark boring windows. data UpdateBoring = UpdateBoring - deriving (Typeable) instance Message UpdateBoring markBoring, clearBoring, focusUp, focusDown, focusMaster, swapUp, swapDown, siftUp, siftDown :: X () @@ -100,7 +99,7 @@ data BoringWindows a = BoringWindows { namedBoring :: M.Map String [a] -- ^ store borings with a specific source , chosenBoring :: [a] -- ^ user-chosen borings , hiddenBoring :: Maybe [a] -- ^ maybe mark hidden windows - } deriving (Show,Read,Typeable) + } deriving (Show,Read) boringWindows :: (LayoutClass l a, Eq a) => l a -> ModifiedLayout BoringWindows l a boringWindows = ModifiedLayout (BoringWindows M.empty [] Nothing) diff --git a/XMonad/Layout/Circle.hs b/XMonad/Layout/Circle.hs index fdefb6cb..b072fa8d 100644 --- a/XMonad/Layout/Circle.hs +++ b/XMonad/Layout/Circle.hs @@ -72,4 +72,3 @@ satellite (Rectangle sx sy sw sh) a = Rectangle (sx + round (rx + rx * cos a)) ry = fromIntegral (sh - h) / 2 w = sw * 10 `div` 25 h = sh * 10 `div` 25 - diff --git a/XMonad/Layout/ComboP.hs b/XMonad/Layout/ComboP.hs index 01e072f7..681aa9b6 100644 --- a/XMonad/Layout/ComboP.hs +++ b/XMonad/Layout/ComboP.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, PatternGuards #-} +{-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.ComboP @@ -67,7 +67,7 @@ import qualified XMonad.StackSet as W data SwapWindow = SwapWindow -- ^ Swap window between panes | SwapWindowN Int -- ^ Swap window between panes in the N-th nested ComboP. @SwapWindowN 0@ equals to SwapWindow - deriving (Read, Show, Typeable) + deriving (Read, Show) instance Message SwapWindow data PartitionWins = PartitionWins -- ^ Reset the layout and @@ -77,7 +77,7 @@ data PartitionWins = PartitionWins -- ^ Reset the layout and -- changed and you want ComboP to -- update which layout a window -- belongs to. - deriving (Read, Show, Typeable) + deriving (Read, Show) instance Message PartitionWins data CombineTwoP l l1 l2 a = C2P [a] [a] [a] l (l1 a) (l2 a) Property diff --git a/XMonad/Layout/Cross.hs b/XMonad/Layout/Cross.hs index 974ea553..ed8fe4db 100644 --- a/XMonad/Layout/Cross.hs +++ b/XMonad/Layout/Cross.hs @@ -109,4 +109,3 @@ leftRectangle (Rectangle rx ry rw rh) f = Rectangle rx (ry + fromIntegral (rh <%> ((1-f)*(1/2)))) (rw <%> (1/2)) (rh <%> f) - diff --git a/XMonad/Layout/Decoration.hs b/XMonad/Layout/Decoration.hs index 4e46aecf..9eada9c1 100644 --- a/XMonad/Layout/Decoration.hs +++ b/XMonad/Layout/Decoration.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} @@ -120,7 +119,7 @@ instance Default Theme where -- | A 'Decoration' layout modifier will handle 'SetTheme', a message -- to dynamically change the decoration 'Theme'. -newtype DecorationMsg = SetTheme Theme deriving ( Typeable ) +newtype DecorationMsg = SetTheme Theme instance Message DecorationMsg -- | The 'Decoration' state component, where the list of decorated diff --git a/XMonad/Layout/DragPane.hs b/XMonad/Layout/DragPane.hs index b594b5ae..ea55adce 100644 --- a/XMonad/Layout/DragPane.hs +++ b/XMonad/Layout/DragPane.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} ----------------------------------------------------------------------------- -- | @@ -67,7 +67,7 @@ instance LayoutClass DragPane a where doLayout d@(DragPane _ Horizontal _ _) = doLay mirrorRect d handleMessage = handleMess -data SetFrac = SetFrac Int Double deriving ( Show, Read, Eq, Typeable ) +data SetFrac = SetFrac Int Double deriving ( Show, Read, Eq) instance Message SetFrac handleMess :: DragPane a -> SomeMessage -> X (Maybe (DragPane a)) diff --git a/XMonad/Layout/DraggingVisualizer.hs b/XMonad/Layout/DraggingVisualizer.hs index 19d6f279..d0237bb8 100644 --- a/XMonad/Layout/DraggingVisualizer.hs +++ b/XMonad/Layout/DraggingVisualizer.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, TypeSynonymInstances, MultiParamTypeClasses, FlexibleContexts #-} +{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, FlexibleContexts #-} ---------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.DraggingVisualizer @@ -30,7 +30,7 @@ draggingVisualizer = ModifiedLayout $ DraggingVisualizer Nothing data DraggingVisualizerMsg = DraggingWindow Window Rectangle | DraggingStopped - deriving ( Typeable, Eq ) + deriving Eq instance Message DraggingVisualizerMsg instance LayoutModifier DraggingVisualizer Window where diff --git a/XMonad/Layout/Dwindle.hs b/XMonad/Layout/Dwindle.hs index 6fae6c90..f934e350 100644 --- a/XMonad/Layout/Dwindle.hs +++ b/XMonad/Layout/Dwindle.hs @@ -110,7 +110,7 @@ import XMonad.Util.Types ( Direction2D(..) ) -- -- * First split chirality -- --- * Size ratio between rectangle allocated to current window and rectangle +-- * Size ratio between rectangle allocated to current window and rectangle -- allocated to remaining windows -- -- * Factor by which the size ratio is changed in response to 'Expand' or 'Shrink' diff --git a/XMonad/Layout/Fullscreen.hs b/XMonad/Layout/Fullscreen.hs index 1bbf64a2..34f77ef7 100644 --- a/XMonad/Layout/Fullscreen.hs +++ b/XMonad/Layout/Fullscreen.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-} +{-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.Fullscreen @@ -104,7 +104,6 @@ fullscreenSupportBorder c = data FullscreenMessage = AddFullscreen Window | RemoveFullscreen Window | FullscreenChanged - deriving (Typeable) instance Message FullscreenMessage diff --git a/XMonad/Layout/Gaps.hs b/XMonad/Layout/Gaps.hs index 309dd0af..6b56dcbf 100644 --- a/XMonad/Layout/Gaps.hs +++ b/XMonad/Layout/Gaps.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} ----------------------------------------------------------------------------- -- | @@ -107,7 +107,6 @@ data GapMessage = ToggleGaps -- ^ Toggle all gaps. | IncGap !Int !Direction2D -- ^ Increase a gap by a certain number of pixels. | DecGap !Int !Direction2D -- ^ Decrease a gap. | ModifyGaps (GapSpec -> GapSpec) -- ^ Modify arbitrarily. - deriving (Typeable) instance Message GapMessage diff --git a/XMonad/Layout/GridVariants.hs b/XMonad/Layout/GridVariants.hs index 173db078..2a2f63bf 100644 --- a/XMonad/Layout/GridVariants.hs +++ b/XMonad/Layout/GridVariants.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} ---------------------------------------------------------------------- -- | @@ -82,7 +82,6 @@ changeGridAspect (Grid aspect) (ChangeGridAspect delta) = data ChangeGridGeom = SetGridAspect !Rational | ChangeGridAspect !Rational - deriving Typeable instance Message ChangeGridGeom @@ -125,7 +124,6 @@ data ChangeMasterGridGeom | SetMasterRows !Int -- ^Set the number of master rows to absolute value | SetMasterCols !Int -- ^Set the number of master columns to absolute value | SetMasterFraction !Rational -- ^Set the fraction of the screen used by the master grid - deriving Typeable instance Message ChangeMasterGridGeom diff --git a/XMonad/Layout/Groups.hs b/XMonad/Layout/Groups.hs index 5ececcd7..01ac7b24 100644 --- a/XMonad/Layout/Groups.hs +++ b/XMonad/Layout/Groups.hs @@ -1,5 +1,5 @@ {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds #-} -{-# LANGUAGE StandaloneDeriving, FlexibleContexts, DeriveDataTypeable, UndecidableInstances, FlexibleInstances, MultiParamTypeClasses, PatternGuards, Rank2Types #-} +{-# LANGUAGE StandaloneDeriving, FlexibleContexts, UndecidableInstances, FlexibleInstances, MultiParamTypeClasses, PatternGuards, Rank2Types #-} ----------------------------------------------------------------------------- -- | @@ -182,7 +182,6 @@ data GroupsMessage = ToEnclosing SomeMessage -- ^ Send a message to the enclosin | Modify ModifySpec -- ^ Modify the ordering\/grouping\/focusing -- of windows according to a 'ModifySpec' | ModifyX ModifySpecX -- ^ Same as 'Modify', but within the 'X' monad - deriving Typeable instance Show GroupsMessage where show (ToEnclosing _) = "ToEnclosing {...}" diff --git a/XMonad/Layout/Hidden.hs b/XMonad/Layout/Hidden.hs index 7fbed52d..ca6d5b7f 100644 --- a/XMonad/Layout/Hidden.hs +++ b/XMonad/Layout/Hidden.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleContexts, MultiParamTypeClasses, TypeSynonymInstances, PatternGuards #-} +{-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, TypeSynonymInstances, PatternGuards #-} ---------------------------------------------------------------------------- -- | @@ -68,7 +68,7 @@ data HiddenMsg = HideWindow Window -- ^ Hide a window. | PopNewestHiddenWindow -- ^ Restore window (FILO). | PopOldestHiddenWindow -- ^ Restore window (FIFO). | PopSpecificHiddenWindow Window -- ^ Restore specific window. - deriving (Typeable, Eq) + deriving (Eq) instance Message HiddenMsg diff --git a/XMonad/Layout/LayoutBuilder.hs b/XMonad/Layout/LayoutBuilder.hs index 81a6fa05..1b839a88 100644 --- a/XMonad/Layout/LayoutBuilder.hs +++ b/XMonad/Layout/LayoutBuilder.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} @@ -222,7 +221,7 @@ layoutAll box sub = LayoutB Nothing Nothing (LimitR (0,1)) box Nothing sub Nothi -------------------------------------------------------------------------------- -- | Change the number of windows handled by the focused layout. -newtype IncLayoutN = IncLayoutN Int deriving Typeable +newtype IncLayoutN = IncLayoutN Int instance Message IncLayoutN -------------------------------------------------------------------------------- diff --git a/XMonad/Layout/LimitWindows.hs b/XMonad/Layout/LimitWindows.hs index 0296b430..82093d0a 100644 --- a/XMonad/Layout/LimitWindows.hs +++ b/XMonad/Layout/LimitWindows.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} +{-# LANGUAGE CPP, FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} #ifdef TESTING {-# OPTIONS_GHC -Wno-duplicate-exports #-} #endif @@ -88,7 +88,7 @@ data LimitWindows a = LimitWindows SliceStyle Int deriving (Read,Show) data SliceStyle = FirstN | Slice deriving (Read,Show) -newtype LimitChange = LimitChange { unLC :: Int -> Int } deriving (Typeable) +newtype LimitChange = LimitChange { unLC :: Int -> Int } instance Message LimitChange diff --git a/XMonad/Layout/Magnifier.hs b/XMonad/Layout/Magnifier.hs index 58de4e8a..be9c0775 100644 --- a/XMonad/Layout/Magnifier.hs +++ b/XMonad/Layout/Magnifier.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE TypeSynonymInstances #-} @@ -158,7 +157,7 @@ magnifierczOff' cz = magnify cz (NoMaster 1) False maximizeVertical :: l a -> ModifiedLayout Magnifier l a maximizeVertical = ModifiedLayout (Mag 1 (1, 1000) Off (AllWins 1)) -data MagnifyMsg = MagnifyMore | MagnifyLess | ToggleOn | ToggleOff | Toggle deriving ( Typeable ) +data MagnifyMsg = MagnifyMore | MagnifyLess | ToggleOn | ToggleOff | Toggle instance Message MagnifyMsg -- | The type for magnifying a given type; do note that the given type diff --git a/XMonad/Layout/Maximize.hs b/XMonad/Layout/Maximize.hs index 0ff80d67..395df96a 100644 --- a/XMonad/Layout/Maximize.hs +++ b/XMonad/Layout/Maximize.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} +{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | @@ -67,7 +67,7 @@ maximize = ModifiedLayout $ Maximize 25 Nothing maximizeWithPadding :: LayoutClass l Window => Dimension -> l Window -> ModifiedLayout Maximize l Window maximizeWithPadding padding = ModifiedLayout $ Maximize padding Nothing -newtype MaximizeRestore = MaximizeRestore Window deriving ( Typeable, Eq ) +newtype MaximizeRestore = MaximizeRestore Window deriving ( Eq ) instance Message MaximizeRestore maximizeRestore :: Window -> MaximizeRestore maximizeRestore = MaximizeRestore diff --git a/XMonad/Layout/MessageControl.hs b/XMonad/Layout/MessageControl.hs index 1b6b37da..a2a92c96 100644 --- a/XMonad/Layout/MessageControl.hs +++ b/XMonad/Layout/MessageControl.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | @@ -31,7 +31,6 @@ import XMonad.StackSet (Workspace(..)) import XMonad.Layout.LayoutModifier (LayoutModifier(..), ModifiedLayout(..)) -import Data.Typeable (Typeable) import Control.Arrow (second) -- $usage @@ -96,8 +95,6 @@ instance LayoutModifier UnEscape a where -- | Data type for an escaped message. Send with 'escape'. newtype EscapedMessage = Escape SomeMessage - deriving Typeable - instance Message EscapedMessage diff --git a/XMonad/Layout/Monitor.hs b/XMonad/Layout/Monitor.hs index bf78c2dc..331d3e14 100644 --- a/XMonad/Layout/Monitor.hs +++ b/XMonad/Layout/Monitor.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} +{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, PatternGuards #-} ----------------------------------------------------------------------------- -- | @@ -115,7 +115,7 @@ data MonitorMessage = ToggleMonitor | ShowMonitor | HideMonitor | ToggleMonitorNamed String | ShowMonitorNamed String | HideMonitorNamed String - deriving (Read,Show,Eq,Typeable) + deriving (Read,Show,Eq) instance Message MonitorMessage withMonitor :: Property -> a -> (Window -> X a) -> X a diff --git a/XMonad/Layout/Mosaic.hs b/XMonad/Layout/Mosaic.hs index 2fc1c250..426a91b0 100644 --- a/XMonad/Layout/Mosaic.hs +++ b/XMonad/Layout/Mosaic.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.Mosaic @@ -28,8 +28,7 @@ module XMonad.Layout.Mosaic ( import Prelude hiding (sum) -import XMonad(Typeable, - LayoutClass(doLayout, handleMessage, pureMessage, description), +import XMonad(LayoutClass(doLayout, handleMessage, pureMessage, description), Message, X, fromMessage, withWindowSet, Resize(..), splitHorizontallyBy, splitVerticallyBy, sendMessage, Rectangle) import XMonad.Prelude (mplus, on, sortBy, sum) @@ -67,7 +66,6 @@ data Aspect | Wider | Reset | SlopeMod ([Rational] -> [Rational]) - deriving (Typeable) instance Message Aspect diff --git a/XMonad/Layout/MosaicAlt.hs b/XMonad/Layout/MosaicAlt.hs index 152e82cd..8bc649a5 100644 --- a/XMonad/Layout/MosaicAlt.hs +++ b/XMonad/Layout/MosaicAlt.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, MultiParamTypeClasses, TypeSynonymInstances #-} +{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances #-} ----------------------------------------------------------------------------- -- | @@ -70,7 +70,7 @@ data HandleWindowAlt = | TallWindowAlt Window | WideWindowAlt Window | ResetAlt - deriving ( Typeable, Eq ) + deriving ( Eq ) instance Message HandleWindowAlt shrinkWindowAlt, expandWindowAlt :: Window -> HandleWindowAlt tallWindowAlt, wideWindowAlt :: Window -> HandleWindowAlt diff --git a/XMonad/Layout/MouseResizableTile.hs b/XMonad/Layout/MouseResizableTile.hs index 2b257ae1..d4998014 100644 --- a/XMonad/Layout/MouseResizableTile.hs +++ b/XMonad/Layout/MouseResizableTile.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} ---------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.MouseResizableTile @@ -80,7 +80,6 @@ data MRTMessage = SetMasterFraction Rational | SetRightSlaveFraction Int Rational | ShrinkSlave | ExpandSlave - deriving Typeable instance Message MRTMessage data DraggerInfo = MasterDragger Position Rational diff --git a/XMonad/Layout/MultiDishes.hs b/XMonad/Layout/MultiDishes.hs index 196d2ca1..f628e888 100644 --- a/XMonad/Layout/MultiDishes.hs +++ b/XMonad/Layout/MultiDishes.hs @@ -39,7 +39,7 @@ import XMonad.Prelude (ap) -- the maximum number of dishes allowed within a stack. -- -- > MultiDishes x 1 y --- is equivalent to +-- is equivalent to -- > Dishes x y -- -- The stack with the fewest dishes is always on top, so 4 windows diff --git a/XMonad/Layout/MultiToggle.hs b/XMonad/Layout/MultiToggle.hs index e73b9d4f..94857463 100644 --- a/XMonad/Layout/MultiToggle.hs +++ b/XMonad/Layout/MultiToggle.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, ExistentialQuantification, Rank2Types, FunctionalDependencies, FlexibleInstances, FlexibleContexts, PatternGuards #-} +{-# LANGUAGE ExistentialQuantification, Rank2Types, FunctionalDependencies, FlexibleInstances, FlexibleContexts, PatternGuards #-} ----------------------------------------------------------------------------- -- | @@ -86,11 +86,11 @@ import Data.Typeable -- which is an instance of the 'Transformer' class. For example, here -- is the definition of @MIRROR@: -- --- > data MIRROR = MIRROR deriving (Read, Show, Eq, Typeable) +-- > data MIRROR = MIRROR deriving (Read, Show, Eq) -- > instance Transformer MIRROR Window where -- > transform _ x k = k (Mirror x) (\(Mirror x') -> x') -- --- Note, you need to put @{-\# LANGUAGE DeriveDataTypeable, +-- Note, you need to put @{-\# LANGUAGE -- TypeSynonymInstances, MultiParamTypeClasses \#-}@ at the -- beginning of your file. @@ -113,7 +113,6 @@ transform' t (EL l det) = transform t l (\l' det' -> EL l' (det . det')) -- | Toggle the specified layout transformer. data Toggle a = forall t. (Transformer t a) => Toggle t - deriving (Typeable) instance (Typeable a) => Message (Toggle a) diff --git a/XMonad/Layout/MultiToggle/Instances.hs b/XMonad/Layout/MultiToggle/Instances.hs index b8112f17..ee819901 100644 --- a/XMonad/Layout/MultiToggle/Instances.hs +++ b/XMonad/Layout/MultiToggle/Instances.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeSynonymInstances, DeriveDataTypeable, MultiParamTypeClasses #-} +{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | @@ -29,7 +29,7 @@ data StdTransformers = FULL -- ^ switch to Full layout | MIRROR -- ^ Mirror the current layout. | NOBORDERS -- ^ Remove borders. | SMARTBORDERS -- ^ Apply smart borders. - deriving (Read, Show, Eq, Typeable) + deriving (Read, Show, Eq) instance Transformer StdTransformers Window where transform FULL x k = k Full (const x) diff --git a/XMonad/Layout/MultiToggle/TabBarDecoration.hs b/XMonad/Layout/MultiToggle/TabBarDecoration.hs index 867c5c30..5d4f01c7 100644 --- a/XMonad/Layout/MultiToggle/TabBarDecoration.hs +++ b/XMonad/Layout/MultiToggle/TabBarDecoration.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeSynonymInstances, DeriveDataTypeable, MultiParamTypeClasses #-} +{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | @@ -42,6 +42,6 @@ import XMonad.Layout.TabBarDecoration -- > ... -- | Transformer for "XMonad.Layout.TabBarDecoration". -data SimpleTabBar = SIMPLETABBAR deriving (Read, Show, Eq, Typeable) +data SimpleTabBar = SIMPLETABBAR deriving (Read, Show, Eq) instance Transformer SimpleTabBar Window where transform _ x k = k (simpleTabBar x) (\(ModifiedLayout _ (ModifiedLayout _ x')) -> x') diff --git a/XMonad/Layout/NoBorders.hs b/XMonad/Layout/NoBorders.hs index 6fc55fd6..f096c0fc 100644 --- a/XMonad/Layout/NoBorders.hs +++ b/XMonad/Layout/NoBorders.hs @@ -1,5 +1,5 @@ {-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} -{-# LANGUAGE PatternGuards, DeriveDataTypeable #-} +{-# LANGUAGE PatternGuards #-} {-# OPTIONS_GHC -Wno-dodgy-imports #-} -- singleton in Data.List since base 4.15 ----------------------------------------------------------------------------- @@ -122,7 +122,6 @@ data BorderMessage | ResetBorder Window -- ^ Reset the effects of any 'HasBorder' messages on the specified -- window. - deriving (Typeable) instance Message BorderMessage diff --git a/XMonad/Layout/OneBig.hs b/XMonad/Layout/OneBig.hs index 7bb31691..c42e08ab 100644 --- a/XMonad/Layout/OneBig.hs +++ b/XMonad/Layout/OneBig.hs @@ -129,5 +129,3 @@ shiftR s (Rectangle x y w h) = Rectangle (x+s) y w h -- | Shift rectangle bottom shiftB :: Position -> Rectangle -> Rectangle shiftB s (Rectangle x y w h) = Rectangle x (y+s) w h - - diff --git a/XMonad/Layout/PerWorkspace.hs b/XMonad/Layout/PerWorkspace.hs index 16fcc290..2df44f49 100644 --- a/XMonad/Layout/PerWorkspace.hs +++ b/XMonad/Layout/PerWorkspace.hs @@ -123,4 +123,3 @@ mkNewPerWorkspaceF :: PerWorkspace l1 l2 a -> Maybe (l2 a) -> PerWorkspace l1 l2 a mkNewPerWorkspaceF (PerWorkspace wsIds _ lt lf) mlf' = PerWorkspace wsIds False lt $ fromMaybe lf mlf' - diff --git a/XMonad/Layout/Reflect.hs b/XMonad/Layout/Reflect.hs index 87c416f4..d8f062ed 100644 --- a/XMonad/Layout/Reflect.hs +++ b/XMonad/Layout/Reflect.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | @@ -23,7 +23,6 @@ module XMonad.Layout.Reflect ( ) where -import XMonad.Core import XMonad.Prelude (fi) import Graphics.X11 (Rectangle(..), Window) import Control.Arrow (second) @@ -101,8 +100,8 @@ instance LayoutModifier Reflect a where -------- instances for MultiToggle ------------------ -data REFLECTX = REFLECTX deriving (Read, Show, Eq, Typeable) -data REFLECTY = REFLECTY deriving (Read, Show, Eq, Typeable) +data REFLECTX = REFLECTX deriving (Read, Show, Eq) +data REFLECTY = REFLECTY deriving (Read, Show, Eq) instance Transformer REFLECTX Window where transform REFLECTX x k = k (reflectHoriz x) (\(ModifiedLayout _ x') -> x') diff --git a/XMonad/Layout/ResizableTile.hs b/XMonad/Layout/ResizableTile.hs index 48a26dcf..2481f7d5 100644 --- a/XMonad/Layout/ResizableTile.hs +++ b/XMonad/Layout/ResizableTile.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, TupleSections #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TupleSections #-} ----------------------------------------------------------------------------- -- | @@ -48,7 +48,7 @@ import qualified Data.Map as M -- -- "XMonad.Doc.Extending#Editing_key_bindings". -data MirrorResize = MirrorShrink | MirrorExpand deriving Typeable +data MirrorResize = MirrorShrink | MirrorExpand instance Message MirrorResize data ResizableTall a = ResizableTall diff --git a/XMonad/Layout/Spacing.hs b/XMonad/Layout/Spacing.hs index dcfa89b2..0990150e 100644 --- a/XMonad/Layout/Spacing.hs +++ b/XMonad/Layout/Spacing.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} ----------------------------------------------------------------------------- -- | @@ -208,7 +208,6 @@ data SpacingModifier | ModifyScreenBorderEnabled (Bool -> Bool) | ModifyWindowBorder (Border -> Border) | ModifyWindowBorderEnabled (Bool -> Bool) - deriving (Typeable) instance Message SpacingModifier @@ -349,7 +348,7 @@ type SmartSpacingWithEdge = Spacing -- | Message to dynamically modify (e.g. increase\/decrease\/set) the size of -- the screen spacing and window spacing. See 'SpacingModifier'. -newtype ModifySpacing = ModifySpacing (Int -> Int) deriving (Typeable) +newtype ModifySpacing = ModifySpacing (Int -> Int) instance Message ModifySpacing diff --git a/XMonad/Layout/SubLayouts.hs b/XMonad/Layout/SubLayouts.hs index f305eb68..08ba25a7 100644 --- a/XMonad/Layout/SubLayouts.hs +++ b/XMonad/Layout/SubLayouts.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE PatternGuards, ParallelListComp, DeriveDataTypeable, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} +{-# LANGUAGE PatternGuards, ParallelListComp, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.SubLayouts @@ -255,7 +255,6 @@ data GroupMsg a | WithGroup (W.Stack a -> X (W.Stack a)) a | SubMessage SomeMessage a -- ^ the sublayout with the given window will get the message - deriving (Typeable) -- | merge the window that would be focused by the function when applied to the -- W.Stack of all windows, with the current group removed. The given window @@ -271,7 +270,6 @@ mergeDir f = WithGroup g return cs newtype Broadcast = Broadcast SomeMessage -- ^ send a message to all sublayouts - deriving (Typeable) instance Message Broadcast instance Typeable a => Message (GroupMsg a) diff --git a/XMonad/Layout/TallMastersCombo.hs b/XMonad/Layout/TallMastersCombo.hs index 9f51c801..cba926e2 100644 --- a/XMonad/Layout/TallMastersCombo.hs +++ b/XMonad/Layout/TallMastersCombo.hs @@ -1,5 +1,5 @@ --- {-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, DeriveDataTypeable, TypeSynonymInstances, MultiParamTypeClasses #-} -{-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, DeriveDataTypeable, MultiParamTypeClasses #-} +-- {-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, TypeSynonymInstances, MultiParamTypeClasses #-} +{-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} --------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.TallMastersCombo @@ -178,7 +178,7 @@ tmsCombineTwo :: (LayoutClass l1 Window, LayoutClass l2 Window) => Bool -> Int -> Rational -> Rational -> l1 Window -> l2 Window -> TMSCombineTwo l1 l2 Window tmsCombineTwo = TMSCombineTwo [] [] [] -data Orientation = Row | Col deriving (Read, Show, Typeable) +data Orientation = Row | Col deriving (Read, Show) instance Message Orientation -- | A message that switches the orientation of TallMasterCombo layout and the RowsOrColumns layout. @@ -186,23 +186,23 @@ instance Message Orientation -- applies to the 'XMonad.Layout.Tabbed' decoration, it will also mirror the tabs, which may lead to unintended -- visualizations. The 'SwitchOrientation' message refreshes layouts according to the orientation of the parent layout, -- and will not affect the 'XMonad.Layout.Tabbed' decoration. -data SwitchOrientation = SwitchOrientation deriving (Read, Show, Typeable) +data SwitchOrientation = SwitchOrientation deriving (Read, Show) instance Message SwitchOrientation -- | This message swaps the current focused window with the sub master window (first window in the second pane). -data SwapSubMaster = SwapSubMaster deriving (Read, Show, Typeable) +data SwapSubMaster = SwapSubMaster deriving (Read, Show) instance Message SwapSubMaster -- | This message changes the focus to the sub master window (first window in the second pane). -data FocusSubMaster = FocusSubMaster deriving (Read, Show, Typeable) +data FocusSubMaster = FocusSubMaster deriving (Read, Show) instance Message FocusSubMaster -- | This message triggers the 'NextLayout' message in the pane that contains the focused window. -data FocusedNextLayout = FocusedNextLayout deriving (Read, Show, Typeable) +data FocusedNextLayout = FocusedNextLayout deriving (Read, Show) instance Message FocusedNextLayout -- | This is a message for changing to the previous or next focused window across all the sub-layouts. -data ChangeFocus = NextFocus | PrevFocus deriving (Read, Show, Typeable) +data ChangeFocus = NextFocus | PrevFocus deriving (Read, Show) instance Message ChangeFocus -- instance (Typeable l1, Typeable l2, LayoutClass l1 Window, LayoutClass l2 Window) => LayoutClass (TMSCombineTwo l1 l2) Window where @@ -427,7 +427,7 @@ elseOr x y = case y of data LR = L | R deriving (Show, Read, Eq) data ChooseWrapper l r a = ChooseWrapper LR (l a) (r a) (Choose l r a) deriving (Show, Read) -data NextNoWrap = NextNoWrap deriving (Eq, Show, Typeable) +data NextNoWrap = NextNoWrap deriving (Eq, Show) instance Message NextNoWrap handle :: (LayoutClass l a, Message m) => l a -> m -> X (Maybe (l a)) diff --git a/XMonad/Layout/ToggleLayouts.hs b/XMonad/Layout/ToggleLayouts.hs index c81a74d0..2c82bdfc 100644 --- a/XMonad/Layout/ToggleLayouts.hs +++ b/XMonad/Layout/ToggleLayouts.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} ----------------------------------------------------------------------------- -- | @@ -50,7 +50,7 @@ import XMonad.StackSet (Workspace (..)) -- "XMonad.Doc.Extending#Editing_key_bindings". data ToggleLayouts lt lf a = ToggleLayouts Bool (lt a) (lf a) deriving (Read,Show) -data ToggleLayout = ToggleLayout | Toggle String deriving (Read,Show,Typeable) +data ToggleLayout = ToggleLayout | Toggle String deriving (Read,Show) instance Message ToggleLayout toggleLayouts :: (LayoutClass lt a, LayoutClass lf a) => lt a -> lf a -> ToggleLayouts lt lf a diff --git a/XMonad/Layout/WindowArranger.hs b/XMonad/Layout/WindowArranger.hs index 5b220c9b..c88a420f 100644 --- a/XMonad/Layout/WindowArranger.hs +++ b/XMonad/Layout/WindowArranger.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, PatternGuards, FlexibleInstances, MultiParamTypeClasses #-} +{-# LANGUAGE PatternGuards, FlexibleInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.WindowArranger @@ -92,7 +92,6 @@ data WindowArrangerMsg = DeArrange | MoveUp Int | MoveDown Int | SetGeometry Rectangle - deriving ( Typeable ) instance Message WindowArrangerMsg data ArrangedWindow a = WR (a, Rectangle) diff --git a/XMonad/Layout/WindowNavigation.hs b/XMonad/Layout/WindowNavigation.hs index aeb97d5f..76d808d3 100644 --- a/XMonad/Layout/WindowNavigation.hs +++ b/XMonad/Layout/WindowNavigation.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} ----------------------------------------------------------------------------- -- | @@ -64,12 +64,11 @@ import XMonad.Util.XUtils -- "XMonad.Doc.Extending#Editing_key_bindings". -data MoveWindowToWindow a = MoveWindowToWindow a a deriving ( Read, Show, Typeable ) +data MoveWindowToWindow a = MoveWindowToWindow a a deriving ( Read, Show) instance Typeable a => Message (MoveWindowToWindow a) data Navigate = Go Direction2D | Swap Direction2D | Move Direction2D | Apply (Window -> X()) Direction2D -- ^ Apply action with destination window - deriving ( Typeable ) instance Message Navigate data WNConfig = diff --git a/XMonad/Layout/WorkspaceDir.hs b/XMonad/Layout/WorkspaceDir.hs index cf818c79..d1ce6565 100644 --- a/XMonad/Layout/WorkspaceDir.hs +++ b/XMonad/Layout/WorkspaceDir.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} ----------------------------------------------------------------------------- -- | @@ -68,7 +68,7 @@ import XMonad.StackSet ( tag, currentTag ) -- -- "XMonad.Doc.Extending#Editing_key_bindings". -newtype Chdir = Chdir String deriving ( Typeable ) +newtype Chdir = Chdir String instance Message Chdir newtype WorkspaceDir a = WorkspaceDir String deriving ( Read, Show ) diff --git a/XMonad/Layout/ZoomRow.hs b/XMonad/Layout/ZoomRow.hs index 33215002..076a75f8 100644 --- a/XMonad/Layout/ZoomRow.hs +++ b/XMonad/Layout/ZoomRow.hs @@ -1,6 +1,6 @@ {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses - , PatternGuards, DeriveDataTypeable, ExistentialQuantification + , PatternGuards, ExistentialQuantification , FlexibleContexts #-} ----------------------------------------------------------------------------- @@ -162,7 +162,7 @@ data ZoomMessage = Zoom Rational | ZoomFullToggle -- ^ Toggle whether the focused window should -- occupy all available space when it has focus - deriving (Typeable, Show) + deriving (Show) instance Message ZoomMessage diff --git a/XMonad/Prompt/Unicode.hs b/XMonad/Prompt/Unicode.hs index edaac1c1..e65d25ca 100644 --- a/XMonad/Prompt/Unicode.hs +++ b/XMonad/Prompt/Unicode.hs @@ -14,8 +14,6 @@ The provided @unicodePrompt@ and @typeUnicodePrompt@ use @xsel@ and @xdotool@ respectively. -} -{-# LANGUAGE DeriveDataTypeable #-} - module XMonad.Prompt.Unicode ( -- * Usage -- $usage @@ -44,7 +42,7 @@ instance XPrompt Unicode where nextCompletion Unicode = getNextCompletion newtype UnicodeData = UnicodeData { getUnicodeData :: [(Char, BS.ByteString)] } - deriving (Typeable, Read, Show) + deriving (Read, Show) instance ExtensionClass UnicodeData where initialValue = UnicodeData [] diff --git a/XMonad/Prompt/Zsh.hs b/XMonad/Prompt/Zsh.hs index 649a8dbb..ff410560 100644 --- a/XMonad/Prompt/Zsh.hs +++ b/XMonad/Prompt/Zsh.hs @@ -61,4 +61,3 @@ stripZsh :: String -> String stripZsh "" = "" stripZsh (' ':'-':'-':' ':_) = "" stripZsh (x:xs) = x : stripZsh xs - diff --git a/XMonad/Util/ActionCycle.hs b/XMonad/Util/ActionCycle.hs index 18ad3f78..c5c05fd9 100644 --- a/XMonad/Util/ActionCycle.hs +++ b/XMonad/Util/ActionCycle.hs @@ -70,7 +70,7 @@ cycleActionWithResult name actions = do actions !! idx -newtype ActionCycleState = ActionCycleState (M.Map String Int) deriving (Typeable) +newtype ActionCycleState = ActionCycleState (M.Map String Int) instance ExtensionClass ActionCycleState where initialValue = ActionCycleState mempty diff --git a/XMonad/Util/DynamicScratchpads.hs b/XMonad/Util/DynamicScratchpads.hs index 42105836..dd2b77ca 100644 --- a/XMonad/Util/DynamicScratchpads.hs +++ b/XMonad/Util/DynamicScratchpads.hs @@ -46,7 +46,7 @@ import qualified XMonad.Util.ExtensibleState as XS -- | Stores dynamic scratchpads as a map of name to window newtype SPStorage = SPStorage (M.Map String Window) - deriving (Typeable,Read,Show) + deriving (Read,Show) instance ExtensionClass SPStorage where initialValue = SPStorage M.empty diff --git a/XMonad/Util/ExtensibleState.hs b/XMonad/Util/ExtensibleState.hs index c2be118b..e7628dc8 100644 --- a/XMonad/Util/ExtensibleState.hs +++ b/XMonad/Util/ExtensibleState.hs @@ -40,10 +40,9 @@ import XMonad.Prelude (fromMaybe) -- and make it an instance of ExtensionClass. You can then use -- the functions from this module for storing and retrieving your data: -- --- > {-# LANGUAGE DeriveDataTypeable #-} -- > import qualified XMonad.Util.ExtensibleState as XS -- > --- > data ListStorage = ListStorage [Integer] deriving Typeable +-- > data ListStorage = ListStorage [Integer] -- > instance ExtensionClass ListStorage where -- > initialValue = ListStorage [] -- > @@ -61,7 +60,7 @@ import XMonad.Prelude (fromMaybe) -- To make your data persistent between restarts, the data type needs to be -- an instance of Read and Show and the instance declaration has to be changed: -- --- > data ListStorage = ListStorage [Integer] deriving (Typeable,Read,Show) +-- > data ListStorage = ListStorage [Integer] deriving (Read,Show) -- > -- > instance ExtensionClass ListStorage where -- > initialValue = ListStorage [] diff --git a/XMonad/Util/Font.hs b/XMonad/Util/Font.hs index 51b33da0..d7eeeb8b 100644 --- a/XMonad/Util/Font.hs +++ b/XMonad/Util/Font.hs @@ -202,4 +202,4 @@ printStringXMF dpy drw fs@(Xft font) gc fc bc x y s = do io $ withXftDraw dpy drw visual colormap $ \draw -> withXftColorName dpy visual colormap fc $ \color -> xftDrawString draw color font x y s -#endif \ No newline at end of file +#endif diff --git a/XMonad/Util/Loggers/NamedScratchpad.hs b/XMonad/Util/Loggers/NamedScratchpad.hs index 84927009..675899c1 100644 --- a/XMonad/Util/Loggers/NamedScratchpad.hs +++ b/XMonad/Util/Loggers/NamedScratchpad.hs @@ -12,8 +12,6 @@ -- ----------------------------------------------------------------------------- -{-# LANGUAGE DeriveDataTypeable #-} - module XMonad.Util.Loggers.NamedScratchpad (-- * Usage -- $usage nspTrackStartup @@ -54,7 +52,7 @@ import qualified XMonad.StackSet as W (allWindows) -- them instead (see 'XMonad.Util.NoTaskbar'). -- The extension data for tracking NSP windows -newtype NSPTrack = NSPTrack [Maybe Window] deriving Typeable +newtype NSPTrack = NSPTrack [Maybe Window] instance ExtensionClass NSPTrack where initialValue = NSPTrack [] diff --git a/XMonad/Util/Minimize.hs b/XMonad/Util/Minimize.hs index 00334fe6..59d269f6 100644 --- a/XMonad/Util/Minimize.hs +++ b/XMonad/Util/Minimize.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable #-} ----------------------------------------------------------------------------- +----------------------------------------------------------------------------- -- | -- Module : XMonad.Util.Minimize -- Copyright : (c) Bogdan Sinitsyn (2016) @@ -28,7 +27,7 @@ data Minimized = Minimized { rectMap :: RectMap , minimizedStack :: [Window] } - deriving (Eq, Typeable, Read, Show) + deriving (Eq, Read, Show) instance ExtensionClass Minimized where initialValue = Minimized { rectMap = M.empty diff --git a/XMonad/Util/PositionStore.hs b/XMonad/Util/PositionStore.hs index 62e4b96c..f8f54f5d 100644 --- a/XMonad/Util/PositionStore.hs +++ b/XMonad/Util/PositionStore.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ---------------------------------------------------------------------------- -- | -- Module : XMonad.Util.PositionStore @@ -35,9 +33,9 @@ import qualified Data.Map as M -- This way windows can be easily relocated and scaled when switching screens. newtype PositionStore = PS (M.Map Window PosStoreRectangle) - deriving (Read,Show,Typeable) + deriving (Read,Show) data PosStoreRectangle = PSRectangle Double Double Double Double - deriving (Read,Show,Typeable) + deriving (Read,Show) instance ExtensionClass PositionStore where initialValue = PS M.empty diff --git a/XMonad/Util/SessionStart.hs b/XMonad/Util/SessionStart.hs index 6a2c905d..41bf0641 100644 --- a/XMonad/Util/SessionStart.hs +++ b/XMonad/Util/SessionStart.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ----------------------------------------------------------------------------- -- | -- Module : XMonad.Util.SessionStart @@ -39,7 +37,7 @@ import qualified XMonad.Util.ExtensibleState as XS -- --------------------------------------------------------------------- newtype SessionStart = SessionStart { unSessionStart :: Bool } - deriving (Read, Show, Typeable) + deriving (Read, Show) instance ExtensionClass SessionStart where initialValue = SessionStart True diff --git a/XMonad/Util/SpawnNamedPipe.hs b/XMonad/Util/SpawnNamedPipe.hs index cb7086a5..b4cc21a9 100644 --- a/XMonad/Util/SpawnNamedPipe.hs +++ b/XMonad/Util/SpawnNamedPipe.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ----------------------------------------------------------------------------- -- | -- Module : XMonad.Util.SpawnNamedPipe @@ -51,7 +49,7 @@ import qualified Data.Map as Map -- newtype NamedPipes = NamedPipes { pipeMap :: Map.Map String Handle } - deriving (Show, Typeable) + deriving (Show) instance ExtensionClass NamedPipes where initialValue = NamedPipes Map.empty diff --git a/XMonad/Util/SpawnOnce.hs b/XMonad/Util/SpawnOnce.hs index 284d571b..a835a51b 100644 --- a/XMonad/Util/SpawnOnce.hs +++ b/XMonad/Util/SpawnOnce.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} - ----------------------------------------------------------------------------- -- | -- Module : XMonad.Util.SpawnOnce @@ -24,7 +22,7 @@ import qualified XMonad.Util.ExtensibleState as XS import XMonad.Prelude newtype SpawnOnce = SpawnOnce { unspawnOnce :: Set String } - deriving (Read, Show, Typeable) + deriving (Read, Show) instance ExtensionClass SpawnOnce where initialValue = SpawnOnce Set.empty diff --git a/XMonad/Util/Types.hs b/XMonad/Util/Types.hs index 9aa67d80..0173bb02 100644 --- a/XMonad/Util/Types.hs +++ b/XMonad/Util/Types.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Util.Types @@ -17,14 +16,12 @@ module XMonad.Util.Types (Direction1D(..) ,Direction2D(..) ) where -import Data.Typeable (Typeable) - -- | One-dimensional directions: -data Direction1D = Next | Prev deriving (Eq,Read,Show,Typeable) +data Direction1D = Next | Prev deriving (Eq,Read,Show) -- | Two-dimensional directions: data Direction2D = U -- ^ Up | D -- ^ Down | R -- ^ Right | L -- ^ Left - deriving (Eq,Read,Show,Ord,Enum,Bounded,Typeable) + deriving (Eq,Read,Show,Ord,Enum,Bounded)