Remove all derivations of Typeable

Typeable has been automatically derived for every type since GHC 7.10,
so remove these obsolete derivations.  This also allows us to get rid of
the `DeriveDataTypeable` pragma quite naturally.

Related: https://github.com/xmonad/xmonad/pull/299 (xmonad/xmonad@9e5b16ed8a)
Related: bd5b969d9ba24236c0d5ef521c0397390dbc4b37
Fixes: https://github.com/xmonad/xmonad-contrib/issues/548
This commit is contained in:
Joan Milev 2021-06-17 12:08:04 +03:00 committed by slotThe
parent 4ddb3e4915
commit f732082fdc
91 changed files with 143 additions and 235 deletions

View File

@ -1,4 +1,3 @@
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.CycleWorkspaceByScreen -- Module : XMonad.Actions.CycleWorkspaceByScreen

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.DynamicProjects -- Module : XMonad.Actions.DynamicProjects
@ -126,14 +124,14 @@ data Project = Project
{ projectName :: !ProjectName -- ^ Workspace name. { projectName :: !ProjectName -- ^ Workspace name.
, projectDirectory :: !FilePath -- ^ Working directory. , projectDirectory :: !FilePath -- ^ Working directory.
, projectStartHook :: !(Maybe (X ())) -- ^ Optional start-up hook. , projectStartHook :: !(Maybe (X ())) -- ^ Optional start-up hook.
} deriving Typeable }
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Internal project state. -- | Internal project state.
data ProjectState = ProjectState data ProjectState = ProjectState
{ projects :: !ProjectTable { projects :: !ProjectTable
, previousProject :: !(Maybe WorkspaceId) , previousProject :: !(Maybe WorkspaceId)
} deriving Typeable }
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
instance ExtensionClass ProjectState where instance ExtensionClass ProjectState where

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.DynamicWorkspaceGroups -- Module : XMonad.Actions.DynamicWorkspaceGroups
@ -69,7 +67,7 @@ type WSGroup = [(ScreenId,WorkspaceId)]
type WSGroupId = String type WSGroupId = String
newtype WSGroupStorage = WSG { unWSG :: M.Map WSGroupId WSGroup } 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 :: (M.Map WSGroupId WSGroup -> M.Map WSGroupId WSGroup) -> WSGroupStorage -> WSGroupStorage
withWSG f = WSG . f . unWSG withWSG f = WSG . f . unWSG

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.DynamicWorkspaceOrder -- Module : XMonad.Actions.DynamicWorkspaceOrder
@ -90,7 +88,7 @@ import Data.Ord (comparing)
-- | Extensible state storage for the workspace order. -- | Extensible state storage for the workspace order.
newtype WSOrderStorage = WSO { unWSO :: Maybe (M.Map WorkspaceId Int) } newtype WSOrderStorage = WSO { unWSO :: Maybe (M.Map WorkspaceId Int) }
deriving (Typeable, Read, Show) deriving (Read, Show)
instance ExtensionClass WSOrderStorage where instance ExtensionClass WSOrderStorage where
initialValue = WSO Nothing initialValue = WSO Nothing

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.DynamicWorkspaces -- Module : XMonad.Actions.DynamicWorkspaces
@ -87,7 +85,7 @@ type WorkspaceIndex = Int
-- | Internal dynamic project state that stores a mapping between -- | Internal dynamic project state that stores a mapping between
-- workspace indexes and workspace tags. -- workspace indexes and workspace tags.
newtype DynamicWorkspaceState = DynamicWorkspaceState {workspaceIndexMap :: Map.Map WorkspaceIndex WorkspaceTag} newtype DynamicWorkspaceState = DynamicWorkspaceState {workspaceIndexMap :: Map.Map WorkspaceIndex WorkspaceTag}
deriving (Typeable, Read, Show) deriving (Read, Show)
instance ExtensionClass DynamicWorkspaceState where instance ExtensionClass DynamicWorkspaceState where
initialValue = DynamicWorkspaceState Map.empty initialValue = DynamicWorkspaceState Map.empty

View File

@ -117,4 +117,3 @@ keysMoveResize f move resize w = whenX (isClient w) $ withDisplay $ \d -> do
io $ resizeWindow d w `uncurry` wn_dim io $ resizeWindow d w `uncurry` wn_dim
io $ moveWindow d w `uncurry` wn_pos io $ moveWindow d w `uncurry` wn_pos
float w float w

View File

@ -57,5 +57,3 @@ listToStack n l = Stack t ls rs
where where
(t:rs) = drop n l (t:rs) = drop n l
ls = reverse (take n l) ls = reverse (take n l)

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
---------------------------------------------------------------------- ----------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.GroupNavigation -- Module : XMonad.Actions.GroupNavigation
@ -157,7 +155,7 @@ orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs'
-- The state extension that holds the history information -- The state extension that holds the history information
data HistoryDB = HistoryDB (Maybe Window) -- currently focused window data HistoryDB = HistoryDB (Maybe Window) -- currently focused window
(Seq Window) -- previously focused windows (Seq Window) -- previously focused windows
deriving (Read, Show, Typeable) deriving (Read, Show)
instance ExtensionClass HistoryDB where instance ExtensionClass HistoryDB where

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.KeyRemap -- Module : XMonad.Actions.KeyRemap
@ -33,7 +32,7 @@ import XMonad.Util.Paste
import qualified XMonad.Util.ExtensibleState as XS 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 instance ExtensionClass KeymapTable where
initialValue = KeymapTable [] initialValue = KeymapTable []

View File

@ -14,7 +14,6 @@
-- --
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
{-# LANGUAGE DeriveDataTypeable #-}
module XMonad.Actions.LinkWorkspaces ( module XMonad.Actions.LinkWorkspaces (
-- * Usage -- * Usage
-- $usage -- $usage
@ -76,7 +75,7 @@ noMessageFn :: ScreenId -> [Char] -> [Char] -> [Char] -> X()
noMessageFn _ _ _ _ = return () :: X () noMessageFn _ _ _ _ = return () :: X ()
-- | Stuff for linking workspaces -- | 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 instance ExtensionClass WorkspaceMap
where initialValue = WorkspaceMap M.empty where initialValue = WorkspaceMap M.empty
extensionType = PersistentExtension extensionType = PersistentExtension

View File

@ -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 -- function calculates a rectangle for a given unmapped
-- window from the screen it is on and its window ID. -- window from the screen it is on and its window ID.
-- See <#Finer_Points> for how to use this. -- See <#Finer_Points> for how to use this.
} deriving Typeable }
-- | Shorthand for the tedious screen type -- | Shorthand for the tedious screen type
type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail

View File

@ -46,4 +46,3 @@ bindOn bindings = chooseAction chooser where
Nothing -> case lookup "" bindings of Nothing -> case lookup "" bindings of
Just action -> action Just action -> action
Nothing -> return () Nothing -> return ()

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -110,7 +110,7 @@ implementation is the following:
-} -}
data PrefixArgument = Raw Int | Numeric Int | None data PrefixArgument = Raw Int | Numeric Int | None
deriving (Typeable, Read, Show) deriving (Read, Show)
instance ExtensionClass PrefixArgument where instance ExtensionClass PrefixArgument where
initialValue = None initialValue = None
extensionType = PersistentExtension extensionType = PersistentExtension

View File

@ -1,5 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE CPP #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.ShowText -- 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 -- | ShowText contains the map with timers as keys and created windows as values
newtype ShowText = ShowText (Map Atom Window) newtype ShowText = ShowText (Map Atom Window)
deriving (Read,Show,Typeable) deriving (Read,Show)
instance ExtensionClass ShowText where instance ExtensionClass ShowText where
initialValue = ShowText empty initialValue = ShowText empty

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.SpawnOn -- Module : XMonad.Actions.SpawnOn
@ -66,7 +65,7 @@ import qualified XMonad.Util.ExtensibleState as XS
-- For detailed instructions on editing your key bindings, see -- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings". -- "XMonad.Doc.Extending#Editing_key_bindings".
newtype Spawner = Spawner {pidsRef :: [(ProcessID, ManageHook)]} deriving Typeable newtype Spawner = Spawner {pidsRef :: [(ProcessID, ManageHook)]}
instance ExtensionClass Spawner where instance ExtensionClass Spawner where
initialValue = Spawner [] initialValue = Spawner []

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.SwapPromote -- Module : XMonad.Actions.SwapPromote
@ -115,7 +113,7 @@ import Control.Arrow
-- Without history, the list is empty. -- Without history, the list is empty.
newtype MasterHistory = MasterHistory newtype MasterHistory = MasterHistory
{ getMasterHistory :: M.Map WorkspaceId [Window] { getMasterHistory :: M.Map WorkspaceId [Window]
} deriving (Read,Show,Typeable) } deriving (Read,Show)
instance ExtensionClass MasterHistory where instance ExtensionClass MasterHistory where
initialValue = MasterHistory M.empty initialValue = MasterHistory M.empty

View File

@ -49,4 +49,4 @@ withAll f = withWindowSet $ \ws -> let all' = integrate' . stack . workspace . c
-- | Kill all the windows on the current workspace. -- | Kill all the windows on the current workspace.
killAll :: X() killAll :: X()
killAll = withAll killWindow killAll = withAll killWindow

View File

@ -20,7 +20,6 @@
-- This also permits to see all workspaces of a workscreen even if just -- 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. -- one screen is present, and to move windows from workspace to workscreen.
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
{-# LANGUAGE DeriveDataTypeable #-}
module XMonad.Actions.Workscreen ( module XMonad.Actions.Workscreen (
-- * Usage -- * Usage
@ -58,10 +57,10 @@ import XMonad.Actions.OnScreen
-- "XMonad.Doc.Extending#Editing_key_bindings". -- "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 type WorkscreenId=Int
data WorkscreenStorage = WorkscreenStorage WorkscreenId [Workscreen] deriving (Show,Typeable) data WorkscreenStorage = WorkscreenStorage WorkscreenId [Workscreen] deriving (Show)
instance ExtensionClass WorkscreenStorage where instance ExtensionClass WorkscreenStorage where
initialValue = WorkscreenStorage 0 [] initialValue = WorkscreenStorage 0 []

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Actions.WorkspaceCursors -- Module : XMonad.Actions.WorkspaceCursors
@ -46,7 +46,7 @@ import qualified XMonad.StackSet as W
import XMonad.Actions.FocusNth(focusNth') import XMonad.Actions.FocusNth(focusNth')
import XMonad.Layout.LayoutModifier(ModifiedLayout(..), import XMonad.Layout.LayoutModifier(ModifiedLayout(..),
LayoutModifier(handleMess, redoLayout)) LayoutModifier(handleMess, redoLayout))
import XMonad(Typeable, Message, WorkspaceId, X, XState(windowset), import XMonad(Message, WorkspaceId, X, XState(windowset),
fromMessage, sendMessage, windows, gets) fromMessage, sendMessage, windows, gets)
import XMonad.Util.Stack (reverseS) import XMonad.Util.Stack (reverseS)
import XMonad.Prelude (find, fromJust, guard, liftA2, toList, when, (<=<)) import XMonad.Prelude (find, fromJust, guard, liftA2, toList, when, (<=<))
@ -114,7 +114,7 @@ end = Cons . fromJust . W.differentiate . map End
data Cursors a data Cursors a
= Cons (W.Stack (Cursors a)) = Cons (W.Stack (Cursors a))
| End a deriving (Eq,Show,Read,Typeable) | End a deriving (Eq,Show,Read)
instance Foldable Cursors where instance Foldable Cursors where
foldMap f (End x) = f x foldMap f (End x) = f x
@ -190,7 +190,7 @@ modifyCursors :: (Cursors String -> X (Cursors String)) -> X ()
modifyCursors = sendMessage . ChangeCursors . (liftA2 (>>) updateXMD return <=<) modifyCursors = sendMessage . ChangeCursors . (liftA2 (>>) updateXMD return <=<)
newtype WorkspaceCursors a = WorkspaceCursors (Cursors String) 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 -- | The state is stored in the 'WorkspaceCursors' layout modifier. Put this as
-- your outermost modifier, unless you want different cursors at different -- 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 workspaceCursors = ModifiedLayout . WorkspaceCursors
newtype ChangeCursors = ChangeCursors { unWrap :: Cursors String -> X (Cursors String) } newtype ChangeCursors = ChangeCursors { unWrap :: Cursors String -> X (Cursors String) }
deriving (Typeable)
instance Message ChangeCursors instance Message ChangeCursors

View File

@ -15,8 +15,6 @@
-- --
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
{-# LANGUAGE DeriveDataTypeable #-}
module XMonad.Actions.WorkspaceNames ( module XMonad.Actions.WorkspaceNames (
-- * Usage -- * Usage
-- $usage -- $usage
@ -87,7 +85,7 @@ import qualified Data.Map as M
-- | Workspace names container. -- | Workspace names container.
newtype WorkspaceNames = WorkspaceNames (M.Map WorkspaceId String) newtype WorkspaceNames = WorkspaceNames (M.Map WorkspaceId String)
deriving (Typeable, Read, Show) deriving (Read, Show)
instance ExtensionClass WorkspaceNames where instance ExtensionClass WorkspaceNames where
initialValue = WorkspaceNames M.empty initialValue = WorkspaceNames M.empty

View File

@ -76,4 +76,3 @@ myLogHook p = do
, ppTitle = xmobarColor "green" "" . shorten 180 , ppTitle = xmobarColor "green" "" . shorten 180
} }
fadeInactiveLogHook 0.6 fadeInactiveLogHook 0.6

View File

@ -148,4 +148,3 @@ GHC and xmonad are in the @$PATH@ in the environment from which xmonad
is started. is started.
-} -}

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
---------------------------------------------------------------------------- ----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Hooks.CurrentWorkspaceOnTop -- 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 instance ExtensionClass CWOTState where
initialValue = CWOTS "" initialValue = CWOTS ""

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Hooks.DynamicBars -- Module : XMonad.Hooks.DynamicBars
@ -81,7 +80,7 @@ import qualified XMonad.Util.ExtensibleState as XS
newtype DynStatusBarInfo = DynStatusBarInfo newtype DynStatusBarInfo = DynStatusBarInfo
{ dsbInfo :: [(ScreenId, Handle)] { dsbInfo :: [(ScreenId, Handle)]
} deriving (Typeable) }
instance ExtensionClass DynStatusBarInfo where instance ExtensionClass DynStatusBarInfo where
initialValue = DynStatusBarInfo [] initialValue = DynStatusBarInfo []

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Hooks.DynamicHooks -- Module : XMonad.Hooks.DynamicHooks
@ -48,7 +47,6 @@ import qualified XMonad.Util.ExtensibleState as XS
data DynamicHooks = DynamicHooks data DynamicHooks = DynamicHooks
{ transients :: [(Query Bool, ManageHook)] { transients :: [(Query Bool, ManageHook)]
, permanent :: ManageHook } , permanent :: ManageHook }
deriving Typeable
instance ExtensionClass DynamicHooks where instance ExtensionClass DynamicHooks where
initialValue = DynamicHooks [] idHook initialValue = DynamicHooks [] idHook

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PatternGuards #-} {-# LANGUAGE PatternGuards #-}
@ -111,7 +110,7 @@ ewmhDesktopsLogHook = ewmhDesktopsLogHookCustom id
-- Cached desktop names (e.g. @_NET_NUMBER_OF_DESKTOPS@ and -- Cached desktop names (e.g. @_NET_NUMBER_OF_DESKTOPS@ and
-- @_NET_DESKTOP_NAMES@). -- @_NET_DESKTOP_NAMES@).
newtype DesktopNames = DesktopNames [String] newtype DesktopNames = DesktopNames [String]
deriving (Eq) deriving Eq
instance ExtensionClass DesktopNames where instance ExtensionClass DesktopNames where
initialValue = DesktopNames [] initialValue = DesktopNames []
@ -119,7 +118,7 @@ instance ExtensionClass DesktopNames where
-- | -- |
-- Cached client list (e.g. @_NET_CLIENT_LIST@). -- Cached client list (e.g. @_NET_CLIENT_LIST@).
newtype ClientList = ClientList [Window] newtype ClientList = ClientList [Window]
deriving (Eq) deriving Eq
instance ExtensionClass ClientList where instance ExtensionClass ClientList where
initialValue = ClientList [none] initialValue = ClientList [none]
@ -127,7 +126,7 @@ instance ExtensionClass ClientList where
-- | -- |
-- Cached current desktop (e.g. @_NET_CURRENT_DESKTOP@). -- Cached current desktop (e.g. @_NET_CURRENT_DESKTOP@).
newtype CurrentDesktop = CurrentDesktop Int newtype CurrentDesktop = CurrentDesktop Int
deriving (Eq) deriving Eq
instance ExtensionClass CurrentDesktop where instance ExtensionClass CurrentDesktop where
initialValue = CurrentDesktop (-1) initialValue = CurrentDesktop (-1)
@ -135,7 +134,7 @@ instance ExtensionClass CurrentDesktop where
-- | -- |
-- Cached window-desktop assignments (e.g. @_NET_CLIENT_LIST_STACKING@). -- Cached window-desktop assignments (e.g. @_NET_CLIENT_LIST_STACKING@).
newtype WindowDesktops = WindowDesktops (M.Map Window Int) newtype WindowDesktops = WindowDesktops (M.Map Window Int)
deriving (Eq) deriving Eq
instance ExtensionClass WindowDesktops where instance ExtensionClass WindowDesktops where
initialValue = WindowDesktops (M.singleton none (-1)) 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 -- The value of @_NET_ACTIVE_WINDOW@, cached to avoid unnecessary property
-- updates. -- updates.
newtype ActiveWindow = ActiveWindow Window newtype ActiveWindow = ActiveWindow Window
deriving (Eq) deriving Eq
instance ExtensionClass ActiveWindow where instance ExtensionClass ActiveWindow where
initialValue = ActiveWindow (complement none) 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 -- 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. -- windows and i need a way to tell 'logHook' what window is activated.
newtype NetActivated = NetActivated {netActivated :: Maybe Window} newtype NetActivated = NetActivated {netActivated :: Maybe Window}
deriving (Show, Typeable) deriving Show
instance ExtensionClass NetActivated where instance ExtensionClass NetActivated where
initialValue = NetActivated Nothing initialValue = NetActivated Nothing

View File

@ -1,6 +1,5 @@
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# OPTIONS_HADDOCK show-extensions #-} {-# OPTIONS_HADDOCK show-extensions #-}
-- | -- |
@ -349,7 +348,7 @@ instance Default Focus where
} }
newtype FocusLock = FocusLock {getFocusLock :: Bool} newtype FocusLock = FocusLock {getFocusLock :: Bool}
deriving (Show, Typeable) deriving (Show)
instance ExtensionClass FocusLock where instance ExtensionClass FocusLock where
initialValue = FocusLock False initialValue = FocusLock False

View File

@ -39,4 +39,3 @@ takeTopFocus ::
X () X ()
takeTopFocus = takeTopFocus =
withWindowSet (maybe (setFocusX =<< asks theRoot) takeFocusX . W.peek) >> setWMName "LG3D" withWindowSet (maybe (setFocusX =<< asks theRoot) takeFocusX . W.peek) >> setWMName "LG3D"

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Hooks.ManageDebug -- Module : XMonad.Hooks.ManageDebug
@ -36,7 +34,7 @@ import XMonad.Util.EZConfig
import qualified XMonad.Util.ExtensibleState as XS import qualified XMonad.Util.ExtensibleState as XS
-- persistent state for manageHook debugging to trigger logHook debugging -- 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 instance ExtensionClass ManageStackDebug where
initialValue = MSD (False,False) initialValue = MSD (False,False)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, PatternGuards, FlexibleInstances, MultiParamTypeClasses, CPP #-} {-# LANGUAGE PatternGuards, FlexibleInstances, MultiParamTypeClasses, CPP #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Hooks.ManageDocks -- Module : XMonad.Hooks.ManageDocks
@ -90,7 +90,7 @@ docks c = c { startupHook = docksStartupHook <+> startupHook c
type WindowStruts = M.Map Window [Strut] type WindowStruts = M.Map Window [Strut]
data UpdateDocks = UpdateDocks deriving Typeable data UpdateDocks = UpdateDocks
instance Message UpdateDocks instance Message UpdateDocks
refreshDocks :: X () refreshDocks :: X ()
@ -98,7 +98,7 @@ refreshDocks = sendMessage UpdateDocks
-- Nothing means cache hasn't been initialized yet -- Nothing means cache hasn't been initialized yet
newtype StrutCache = StrutCache { fromStrutCache :: Maybe WindowStruts } newtype StrutCache = StrutCache { fromStrutCache :: Maybe WindowStruts }
deriving (Eq, Typeable) deriving Eq
instance ExtensionClass StrutCache where instance ExtensionClass StrutCache where
initialValue = StrutCache Nothing initialValue = StrutCache Nothing
@ -227,7 +227,7 @@ newtype AvoidStruts a = AvoidStruts (S.Set Direction2D) deriving ( Read, Show )
-- modifier to alter its behavior. -- modifier to alter its behavior.
data ToggleStruts = ToggleStruts data ToggleStruts = ToggleStruts
| ToggleStrut Direction2D | ToggleStrut Direction2D
deriving (Read,Show,Typeable) deriving (Read,Show)
instance Message ToggleStruts instance Message ToggleStruts
@ -253,7 +253,7 @@ instance Message ToggleStruts
data SetStruts = SetStruts { addedStruts :: [Direction2D] data SetStruts = SetStruts { addedStruts :: [Direction2D]
, removedStruts :: [Direction2D] -- ^ These are removed from the currently set struts before 'addedStruts' are added. , removedStruts :: [Direction2D] -- ^ These are removed from the currently set struts before 'addedStruts' are added.
} }
deriving (Read,Show,Typeable) deriving (Read,Show)
instance Message SetStruts instance Message SetStruts

View File

@ -110,7 +110,7 @@ data RecentWins = Recent { previous :: !Window, current :: !Window }
-- | Newtype wrapper for a @Map@ holding the @RecentWins@ for each workspace. -- | Newtype wrapper for a @Map@ holding the @RecentWins@ for each workspace.
-- Is an instance of @ExtensionClass@ with persistence of state. -- Is an instance of @ExtensionClass@ with persistence of state.
newtype RecentsMap = RecentsMap (M.Map WorkspaceId RecentWins) newtype RecentsMap = RecentsMap (M.Map WorkspaceId RecentWins)
deriving (Show, Read, Eq, Typeable) deriving (Show, Read, Eq)
instance ExtensionClass RecentsMap where instance ExtensionClass RecentsMap where
initialValue = RecentsMap M.empty 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. -- | A newtype on @Bool@ to act as a universal toggle for refocusing.
newtype RefocusLastToggle = RefocusLastToggle { refocusing :: Bool } newtype RefocusLastToggle = RefocusLastToggle { refocusing :: Bool }
deriving (Show, Read, Eq, Typeable) deriving (Show, Read, Eq)
instance ExtensionClass RefocusLastToggle where instance ExtensionClass RefocusLastToggle where
initialValue = RefocusLastToggle { refocusing = True } initialValue = RefocusLastToggle { refocusing = True }

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, TupleSections #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TupleSections #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Hooks.ScreenCorners -- Module : XMonad.Hooks.ScreenCorners
@ -43,14 +43,11 @@ data ScreenCorner = SCUpperLeft
| SCLowerRight | SCLowerRight
deriving (Eq, Ord, Show) deriving (Eq, Ord, Show)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- ExtensibleState modifications -- ExtensibleState modifications
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
newtype ScreenCornerState = ScreenCornerState (M.Map Window (ScreenCorner, X ())) newtype ScreenCornerState = ScreenCornerState (M.Map Window (ScreenCorner, X ()))
deriving Typeable
instance ExtensionClass ScreenCornerState where instance ExtensionClass ScreenCornerState where
initialValue = ScreenCornerState M.empty initialValue = ScreenCornerState M.empty

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Hooks.ToggleHook -- 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 -} {- 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 instance ExtensionClass HookState where
initialValue = HookState empty initialValue = HookState empty

View File

@ -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 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 :: ([Window] -> [Window]) -> Urgents -> Urgents
onUrgents f = Urgents . f . fromUrgents onUrgents f = Urgents . f . fromUrgents
@ -295,7 +295,7 @@ data Reminder = Reminder { timer :: TimerId
, window :: Window , window :: Window
, interval :: Interval , interval :: Interval
, remaining :: Maybe Int , remaining :: Maybe Int
} deriving (Show,Read,Eq,Typeable) } deriving (Show,Read,Eq)
instance ExtensionClass [Reminder] where instance ExtensionClass [Reminder] where
initialValue = [] initialValue = []

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------- -----------------------------------
-- | -- |
-- Module : XMonad.Hooks.WallpaperSetter -- 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) -- * 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 -- | 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 instance ExtensionClass WCState where
initialValue = WCState Nothing Nothing initialValue = WCState Nothing Nothing

View File

@ -208,7 +208,7 @@ data SwallowingState =
{ currentlySwallowed :: M.Map Window Window -- ^ mapping from child window window to the currently swallowed parent window { 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 , 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 , 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 :: Window -> SwallowingState -> Maybe Window
getSwallowedParent win SwallowingState { currentlySwallowed } = getSwallowedParent win SwallowingState { currentlySwallowed } =

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Hooks.WorkspaceHistory -- Module : XMonad.Hooks.WorkspaceHistory
@ -64,7 +62,7 @@ import qualified XMonad.Util.ExtensibleState as XS
newtype WorkspaceHistory = WorkspaceHistory newtype WorkspaceHistory = WorkspaceHistory
{ history :: [(ScreenId, WorkspaceId)] -- ^ Workspace Screens in { history :: [(ScreenId, WorkspaceId)] -- ^ Workspace Screens in
-- reverse-chronological order. -- reverse-chronological order.
} deriving (Typeable, Read, Show) } deriving (Read, Show)
instance ExtensionClass WorkspaceHistory where instance ExtensionClass WorkspaceHistory where
initialValue = WorkspaceHistory [] initialValue = WorkspaceHistory []

View File

@ -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. = AvoidFloatToggle -- ^ Toggle between avoiding all or only selected.
| AvoidFloatSet Bool -- ^ Set if all all floating windows should be avoided. | AvoidFloatSet Bool -- ^ Set if all all floating windows should be avoided.
| AvoidFloatClearItems -- ^ Clear the set of windows to specifically avoid. | AvoidFloatClearItems -- ^ Clear the set of windows to specifically avoid.
deriving (Typeable)
-- | Change the state of the avoid float layout modifier conserning a specific window. -- | Change the state of the avoid float layout modifier conserning a specific window.
data AvoidFloatItemMsg a data AvoidFloatItemMsg a
= AvoidFloatAddItem a -- ^ Add a window to always avoid. = AvoidFloatAddItem a -- ^ Add a window to always avoid.
| AvoidFloatRemoveItem a -- ^ Stop always avoiding selected window. | AvoidFloatRemoveItem a -- ^ Stop always avoiding selected window.
| AvoidFloatToggleItem a -- ^ Toggle between always avoiding selected window. | AvoidFloatToggleItem a -- ^ Toggle between always avoiding selected window.
deriving (Typeable)
instance Message AvoidFloatMsg instance Message AvoidFloatMsg
instance Typeable a => Message (AvoidFloatItemMsg a) instance Typeable a => Message (AvoidFloatItemMsg a)

View File

@ -1,7 +1,7 @@
{-# LANGUAGE PatternGuards #-} {-# LANGUAGE PatternGuards #-}
{-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE DoAndIfThenElse #-} {-# LANGUAGE DoAndIfThenElse #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.BinarySpacePartition -- 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 -- | 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 instance Message TreeRotate
-- | Message to balance the tree in some way (Balance retiles the windows, Equalize changes ratios) -- | 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 instance Message TreeBalance
-- | Message for resizing one of the cells in the BSP -- | Message for resizing one of the cells in the BSP
data ResizeDirectional = data ResizeDirectional =
ExpandTowardsBy Direction2D Rational ExpandTowardsBy Direction2D Rational
| ShrinkFromBy Direction2D Rational | ShrinkFromBy Direction2D Rational
| MoveSplitBy Direction2D Rational deriving Typeable | MoveSplitBy Direction2D Rational
instance Message ResizeDirectional instance Message ResizeDirectional
-- | @ExpandTowards x@ is now the equivalent of @ExpandTowardsBy x 0.05@ -- | @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 pattern MoveSplit d = MoveSplitBy d 0.05
-- | Message for rotating a split (horizontal/vertical) in the BSP -- | Message for rotating a split (horizontal/vertical) in the BSP
data Rotate = Rotate deriving Typeable data Rotate = Rotate
instance Message Rotate instance Message Rotate
-- | Message for swapping the left child of a split with the right child of split -- | 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 instance Message Swap
-- | Message to cyclically select the parent node instead of the leaf -- | Message to cyclically select the parent node instead of the leaf
data FocusParent = FocusParent deriving Typeable data FocusParent = FocusParent
instance Message FocusParent instance Message FocusParent
-- | Message to move nodes inside the tree -- | Message to move nodes inside the tree
data SelectMoveNode = SelectNode | MoveNode deriving Typeable data SelectMoveNode = SelectNode | MoveNode
instance Message SelectMoveNode instance Message SelectMoveNode
data Axis = Horizontal | Vertical deriving (Show, Read, Eq) data Axis = Horizontal | Vertical deriving (Show, Read, Eq)
-- | Message for shifting window by splitting its neighbour -- | Message for shifting window by splitting its neighbour
newtype SplitShiftDirectional = SplitShift Direction1D deriving Typeable newtype SplitShiftDirectional = SplitShift Direction1D
instance Message SplitShiftDirectional instance Message SplitShiftDirectional
oppositeDirection :: Direction2D -> Direction2D oppositeDirection :: Direction2D -> Direction2D

View File

@ -1,4 +1,4 @@
{-# LANGUAGE MultiParamTypeClasses, DeriveDataTypeable #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances #-} {-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -34,7 +34,7 @@ module XMonad.Layout.BoringWindows (
import XMonad.Layout.LayoutModifier(ModifiedLayout(..), import XMonad.Layout.LayoutModifier(ModifiedLayout(..),
LayoutModifier(handleMessOrMaybeModifyIt, redoLayout)) LayoutModifier(handleMessOrMaybeModifyIt, redoLayout))
import XMonad(Typeable, LayoutClass, Message, X, fromMessage, import XMonad(LayoutClass, Message, X, fromMessage,
broadcastMessage, sendMessage, windows, withFocused, Window) broadcastMessage, sendMessage, windows, withFocused, Window)
import XMonad.Prelude (find, fromMaybe, listToMaybe, maybeToList, union, (\\)) import XMonad.Prelude (find, fromMaybe, listToMaybe, maybeToList, union, (\\))
import XMonad.Util.Stack (reverseS) import XMonad.Util.Stack (reverseS)
@ -70,14 +70,13 @@ data BoringMessage = FocusUp | FocusDown | FocusMaster | IsBoring Window | Clear
| SwapDown | SwapDown
| SiftUp | SiftUp
| SiftDown | SiftDown
deriving ( Read, Show, Typeable ) deriving ( Read, Show )
instance Message BoringMessage instance Message BoringMessage
-- | UpdateBoring is sent before attempting to view another boring window, so -- | UpdateBoring is sent before attempting to view another boring window, so
-- that layouts have a chance to mark boring windows. -- that layouts have a chance to mark boring windows.
data UpdateBoring = UpdateBoring data UpdateBoring = UpdateBoring
deriving (Typeable)
instance Message UpdateBoring instance Message UpdateBoring
markBoring, clearBoring, focusUp, focusDown, focusMaster, swapUp, swapDown, siftUp, siftDown :: X () 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 { namedBoring :: M.Map String [a] -- ^ store borings with a specific source
, chosenBoring :: [a] -- ^ user-chosen borings , chosenBoring :: [a] -- ^ user-chosen borings
, hiddenBoring :: Maybe [a] -- ^ maybe mark hidden windows , 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 :: (LayoutClass l a, Eq a) => l a -> ModifiedLayout BoringWindows l a
boringWindows = ModifiedLayout (BoringWindows M.empty [] Nothing) boringWindows = ModifiedLayout (BoringWindows M.empty [] Nothing)

View File

@ -72,4 +72,3 @@ satellite (Rectangle sx sy sw sh) a = Rectangle (sx + round (rx + rx * cos a))
ry = fromIntegral (sh - h) / 2 ry = fromIntegral (sh - h) / 2
w = sw * 10 `div` 25 w = sw * 10 `div` 25
h = sh * 10 `div` 25 h = sh * 10 `div` 25

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, PatternGuards #-} {-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, PatternGuards #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.ComboP -- Module : XMonad.Layout.ComboP
@ -67,7 +67,7 @@ import qualified XMonad.StackSet as W
data SwapWindow = SwapWindow -- ^ Swap window between panes data SwapWindow = SwapWindow -- ^ Swap window between panes
| SwapWindowN Int -- ^ Swap window between panes in the N-th nested ComboP. @SwapWindowN 0@ equals to SwapWindow | 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 instance Message SwapWindow
data PartitionWins = PartitionWins -- ^ Reset the layout and data PartitionWins = PartitionWins -- ^ Reset the layout and
@ -77,7 +77,7 @@ data PartitionWins = PartitionWins -- ^ Reset the layout and
-- changed and you want ComboP to -- changed and you want ComboP to
-- update which layout a window -- update which layout a window
-- belongs to. -- belongs to.
deriving (Read, Show, Typeable) deriving (Read, Show)
instance Message PartitionWins instance Message PartitionWins
data CombineTwoP l l1 l2 a = C2P [a] [a] [a] l (l1 a) (l2 a) Property data CombineTwoP l l1 l2 a = C2P [a] [a] [a] l (l1 a) (l2 a) Property

View File

@ -109,4 +109,3 @@ leftRectangle (Rectangle rx ry rw rh) f = Rectangle
rx rx
(ry + fromIntegral (rh <%> ((1-f)*(1/2)))) (ry + fromIntegral (rh <%> ((1-f)*(1/2))))
(rw <%> (1/2)) (rh <%> f) (rw <%> (1/2)) (rh <%> f)

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
@ -120,7 +119,7 @@ instance Default Theme where
-- | 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'.
newtype DecorationMsg = SetTheme Theme deriving ( Typeable ) newtype DecorationMsg = SetTheme Theme
instance Message DecorationMsg instance Message DecorationMsg
-- | The 'Decoration' state component, where the list of decorated -- | The 'Decoration' state component, where the list of decorated

View File

@ -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 doLayout d@(DragPane _ Horizontal _ _) = doLay mirrorRect d
handleMessage = handleMess handleMessage = handleMess
data SetFrac = SetFrac Int Double deriving ( Show, Read, Eq, Typeable ) data SetFrac = SetFrac Int Double deriving ( Show, Read, Eq)
instance Message SetFrac instance Message SetFrac
handleMess :: DragPane a -> SomeMessage -> X (Maybe (DragPane a)) handleMess :: DragPane a -> SomeMessage -> X (Maybe (DragPane a))

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, TypeSynonymInstances, MultiParamTypeClasses, FlexibleContexts #-} {-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, FlexibleContexts #-}
---------------------------------------------------------------------------- ----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.DraggingVisualizer -- Module : XMonad.Layout.DraggingVisualizer
@ -30,7 +30,7 @@ draggingVisualizer = ModifiedLayout $ DraggingVisualizer Nothing
data DraggingVisualizerMsg = DraggingWindow Window Rectangle data DraggingVisualizerMsg = DraggingWindow Window Rectangle
| DraggingStopped | DraggingStopped
deriving ( Typeable, Eq ) deriving Eq
instance Message DraggingVisualizerMsg instance Message DraggingVisualizerMsg
instance LayoutModifier DraggingVisualizer Window where instance LayoutModifier DraggingVisualizer Window where

View File

@ -110,7 +110,7 @@ import XMonad.Util.Types ( Direction2D(..) )
-- --
-- * First split chirality -- * 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 -- allocated to remaining windows
-- --
-- * Factor by which the size ratio is changed in response to 'Expand' or 'Shrink' -- * Factor by which the size ratio is changed in response to 'Expand' or 'Shrink'

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-} {-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.Fullscreen -- Module : XMonad.Layout.Fullscreen
@ -104,7 +104,6 @@ fullscreenSupportBorder c =
data FullscreenMessage = AddFullscreen Window data FullscreenMessage = AddFullscreen Window
| RemoveFullscreen Window | RemoveFullscreen Window
| FullscreenChanged | FullscreenChanged
deriving (Typeable)
instance Message FullscreenMessage instance Message FullscreenMessage

View File

@ -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. | IncGap !Int !Direction2D -- ^ Increase a gap by a certain number of pixels.
| DecGap !Int !Direction2D -- ^ Decrease a gap. | DecGap !Int !Direction2D -- ^ Decrease a gap.
| ModifyGaps (GapSpec -> GapSpec) -- ^ Modify arbitrarily. | ModifyGaps (GapSpec -> GapSpec) -- ^ Modify arbitrarily.
deriving (Typeable)
instance Message GapMessage instance Message GapMessage

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
---------------------------------------------------------------------- ----------------------------------------------------------------------
-- | -- |
@ -82,7 +82,6 @@ changeGridAspect (Grid aspect) (ChangeGridAspect delta) =
data ChangeGridGeom data ChangeGridGeom
= SetGridAspect !Rational = SetGridAspect !Rational
| ChangeGridAspect !Rational | ChangeGridAspect !Rational
deriving Typeable
instance Message ChangeGridGeom instance Message ChangeGridGeom
@ -125,7 +124,6 @@ data ChangeMasterGridGeom
| SetMasterRows !Int -- ^Set the number of master rows to absolute value | SetMasterRows !Int -- ^Set the number of master rows to absolute value
| SetMasterCols !Int -- ^Set the number of master columns 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 | SetMasterFraction !Rational -- ^Set the fraction of the screen used by the master grid
deriving Typeable
instance Message ChangeMasterGridGeom instance Message ChangeMasterGridGeom

View File

@ -1,5 +1,5 @@
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds #-} {-# 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 | Modify ModifySpec -- ^ Modify the ordering\/grouping\/focusing
-- of windows according to a 'ModifySpec' -- of windows according to a 'ModifySpec'
| ModifyX ModifySpecX -- ^ Same as 'Modify', but within the 'X' monad | ModifyX ModifySpecX -- ^ Same as 'Modify', but within the 'X' monad
deriving Typeable
instance Show GroupsMessage where instance Show GroupsMessage where
show (ToEnclosing _) = "ToEnclosing {...}" show (ToEnclosing _) = "ToEnclosing {...}"

View File

@ -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). | PopNewestHiddenWindow -- ^ Restore window (FILO).
| PopOldestHiddenWindow -- ^ Restore window (FIFO). | PopOldestHiddenWindow -- ^ Restore window (FIFO).
| PopSpecificHiddenWindow Window -- ^ Restore specific window. | PopSpecificHiddenWindow Window -- ^ Restore specific window.
deriving (Typeable, Eq) deriving (Eq)
instance Message HiddenMsg instance Message HiddenMsg

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# 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. -- | Change the number of windows handled by the focused layout.
newtype IncLayoutN = IncLayoutN Int deriving Typeable newtype IncLayoutN = IncLayoutN Int
instance Message IncLayoutN instance Message IncLayoutN
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------

View File

@ -1,4 +1,4 @@
{-# LANGUAGE CPP, FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} {-# LANGUAGE CPP, FlexibleInstances, MultiParamTypeClasses, PatternGuards #-}
#ifdef TESTING #ifdef TESTING
{-# OPTIONS_GHC -Wno-duplicate-exports #-} {-# OPTIONS_GHC -Wno-duplicate-exports #-}
#endif #endif
@ -88,7 +88,7 @@ data LimitWindows a = LimitWindows SliceStyle Int deriving (Read,Show)
data SliceStyle = FirstN | Slice 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 instance Message LimitChange

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards #-} {-# LANGUAGE PatternGuards #-}
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
@ -158,7 +157,7 @@ magnifierczOff' cz = magnify cz (NoMaster 1) False
maximizeVertical :: l a -> ModifiedLayout Magnifier l a maximizeVertical :: l a -> ModifiedLayout Magnifier l a
maximizeVertical = ModifiedLayout (Mag 1 (1, 1000) Off (AllWins 1)) 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 instance Message MagnifyMsg
-- | The type for magnifying a given type; do note that the given type -- | The type for magnifying a given type; do note that the given type

View File

@ -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 :: LayoutClass l Window => Dimension -> l Window -> ModifiedLayout Maximize l Window
maximizeWithPadding padding = ModifiedLayout $ Maximize padding Nothing maximizeWithPadding padding = ModifiedLayout $ Maximize padding Nothing
newtype MaximizeRestore = MaximizeRestore Window deriving ( Typeable, Eq ) newtype MaximizeRestore = MaximizeRestore Window deriving ( Eq )
instance Message MaximizeRestore instance Message MaximizeRestore
maximizeRestore :: Window -> MaximizeRestore maximizeRestore :: Window -> MaximizeRestore
maximizeRestore = MaximizeRestore maximizeRestore = MaximizeRestore

View File

@ -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 XMonad.Layout.LayoutModifier (LayoutModifier(..), ModifiedLayout(..))
import Data.Typeable (Typeable)
import Control.Arrow (second) import Control.Arrow (second)
-- $usage -- $usage
@ -96,8 +95,6 @@ instance LayoutModifier UnEscape a where
-- | Data type for an escaped message. Send with 'escape'. -- | Data type for an escaped message. Send with 'escape'.
newtype EscapedMessage = Escape SomeMessage newtype EscapedMessage = Escape SomeMessage
deriving Typeable
instance Message EscapedMessage instance Message EscapedMessage

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} {-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, PatternGuards #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -115,7 +115,7 @@ data MonitorMessage = ToggleMonitor | ShowMonitor | HideMonitor
| ToggleMonitorNamed String | ToggleMonitorNamed String
| ShowMonitorNamed String | ShowMonitorNamed String
| HideMonitorNamed String | HideMonitorNamed String
deriving (Read,Show,Eq,Typeable) deriving (Read,Show,Eq)
instance Message MonitorMessage instance Message MonitorMessage
withMonitor :: Property -> a -> (Window -> X a) -> X a withMonitor :: Property -> a -> (Window -> X a) -> X a

View File

@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.Mosaic -- Module : XMonad.Layout.Mosaic
@ -28,8 +28,7 @@ module XMonad.Layout.Mosaic (
import Prelude hiding (sum) import Prelude hiding (sum)
import XMonad(Typeable, import XMonad(LayoutClass(doLayout, handleMessage, pureMessage, description),
LayoutClass(doLayout, handleMessage, pureMessage, description),
Message, X, fromMessage, withWindowSet, Resize(..), Message, X, fromMessage, withWindowSet, Resize(..),
splitHorizontallyBy, splitVerticallyBy, sendMessage, Rectangle) splitHorizontallyBy, splitVerticallyBy, sendMessage, Rectangle)
import XMonad.Prelude (mplus, on, sortBy, sum) import XMonad.Prelude (mplus, on, sortBy, sum)
@ -67,7 +66,6 @@ data Aspect
| Wider | Wider
| Reset | Reset
| SlopeMod ([Rational] -> [Rational]) | SlopeMod ([Rational] -> [Rational])
deriving (Typeable)
instance Message Aspect instance Message Aspect

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, MultiParamTypeClasses, TypeSynonymInstances #-} {-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -70,7 +70,7 @@ data HandleWindowAlt =
| TallWindowAlt Window | TallWindowAlt Window
| WideWindowAlt Window | WideWindowAlt Window
| ResetAlt | ResetAlt
deriving ( Typeable, Eq ) deriving ( Eq )
instance Message HandleWindowAlt instance Message HandleWindowAlt
shrinkWindowAlt, expandWindowAlt :: Window -> HandleWindowAlt shrinkWindowAlt, expandWindowAlt :: Window -> HandleWindowAlt
tallWindowAlt, wideWindowAlt :: Window -> HandleWindowAlt tallWindowAlt, wideWindowAlt :: Window -> HandleWindowAlt

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-}
---------------------------------------------------------------------------- ----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.MouseResizableTile -- Module : XMonad.Layout.MouseResizableTile
@ -80,7 +80,6 @@ data MRTMessage = SetMasterFraction Rational
| SetRightSlaveFraction Int Rational | SetRightSlaveFraction Int Rational
| ShrinkSlave | ShrinkSlave
| ExpandSlave | ExpandSlave
deriving Typeable
instance Message MRTMessage instance Message MRTMessage
data DraggerInfo = MasterDragger Position Rational data DraggerInfo = MasterDragger Position Rational

View File

@ -39,7 +39,7 @@ import XMonad.Prelude (ap)
-- the maximum number of dishes allowed within a stack. -- the maximum number of dishes allowed within a stack.
-- --
-- > MultiDishes x 1 y -- > MultiDishes x 1 y
-- is equivalent to -- is equivalent to
-- > Dishes x y -- > Dishes x y
-- --
-- The stack with the fewest dishes is always on top, so 4 windows -- The stack with the fewest dishes is always on top, so 4 windows

View File

@ -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 -- which is an instance of the 'Transformer' class. For example, here
-- is the definition of @MIRROR@: -- 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 -- > instance Transformer MIRROR Window where
-- > transform _ x k = k (Mirror x) (\(Mirror x') -> x') -- > 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 -- TypeSynonymInstances, MultiParamTypeClasses \#-}@ at the
-- beginning of your file. -- 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. -- | Toggle the specified layout transformer.
data Toggle a = forall t. (Transformer t a) => Toggle t data Toggle a = forall t. (Transformer t a) => Toggle t
deriving (Typeable)
instance (Typeable a) => Message (Toggle a) instance (Typeable a) => Message (Toggle a)

View File

@ -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. | MIRROR -- ^ Mirror the current layout.
| NOBORDERS -- ^ Remove borders. | NOBORDERS -- ^ Remove borders.
| SMARTBORDERS -- ^ Apply smart borders. | SMARTBORDERS -- ^ Apply smart borders.
deriving (Read, Show, Eq, Typeable) deriving (Read, Show, Eq)
instance Transformer StdTransformers Window where instance Transformer StdTransformers Window where
transform FULL x k = k Full (const x) transform FULL x k = k Full (const x)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TypeSynonymInstances, DeriveDataTypeable, MultiParamTypeClasses #-} {-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -42,6 +42,6 @@ import XMonad.Layout.TabBarDecoration
-- > ... -- > ...
-- | Transformer for "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 instance Transformer SimpleTabBar Window where
transform _ x k = k (simpleTabBar x) (\(ModifiedLayout _ (ModifiedLayout _ x')) -> x') transform _ x k = k (simpleTabBar x) (\(ModifiedLayout _ (ModifiedLayout _ x')) -> x')

View File

@ -1,5 +1,5 @@
{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} {-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards, DeriveDataTypeable #-} {-# LANGUAGE PatternGuards #-}
{-# OPTIONS_GHC -Wno-dodgy-imports #-} -- singleton in Data.List since base 4.15 {-# OPTIONS_GHC -Wno-dodgy-imports #-} -- singleton in Data.List since base 4.15
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
@ -122,7 +122,6 @@ data BorderMessage
| ResetBorder Window | ResetBorder Window
-- ^ Reset the effects of any 'HasBorder' messages on the specified -- ^ Reset the effects of any 'HasBorder' messages on the specified
-- window. -- window.
deriving (Typeable)
instance Message BorderMessage instance Message BorderMessage

View File

@ -129,5 +129,3 @@ shiftR s (Rectangle x y w h) = Rectangle (x+s) y w h
-- | Shift rectangle bottom -- | Shift rectangle bottom
shiftB :: Position -> Rectangle -> Rectangle shiftB :: Position -> Rectangle -> Rectangle
shiftB s (Rectangle x y w h) = Rectangle x (y+s) w h shiftB s (Rectangle x y w h) = Rectangle x (y+s) w h

View File

@ -123,4 +123,3 @@ mkNewPerWorkspaceF :: PerWorkspace l1 l2 a -> Maybe (l2 a) ->
PerWorkspace l1 l2 a PerWorkspace l1 l2 a
mkNewPerWorkspaceF (PerWorkspace wsIds _ lt lf) mlf' = mkNewPerWorkspaceF (PerWorkspace wsIds _ lt lf) mlf' =
PerWorkspace wsIds False lt $ fromMaybe lf mlf' PerWorkspace wsIds False lt $ fromMaybe lf mlf'

View File

@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -23,7 +23,6 @@ module XMonad.Layout.Reflect (
) where ) where
import XMonad.Core
import XMonad.Prelude (fi) import XMonad.Prelude (fi)
import Graphics.X11 (Rectangle(..), Window) import Graphics.X11 (Rectangle(..), Window)
import Control.Arrow (second) import Control.Arrow (second)
@ -101,8 +100,8 @@ instance LayoutModifier Reflect a where
-------- instances for MultiToggle ------------------ -------- instances for MultiToggle ------------------
data REFLECTX = REFLECTX deriving (Read, Show, Eq, Typeable) data REFLECTX = REFLECTX deriving (Read, Show, Eq)
data REFLECTY = REFLECTY deriving (Read, Show, Eq, Typeable) data REFLECTY = REFLECTY deriving (Read, Show, Eq)
instance Transformer REFLECTX Window where instance Transformer REFLECTX Window where
transform REFLECTX x k = k (reflectHoriz x) (\(ModifiedLayout _ x') -> x') transform REFLECTX x k = k (reflectHoriz x) (\(ModifiedLayout _ x') -> x')

View File

@ -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". -- "XMonad.Doc.Extending#Editing_key_bindings".
data MirrorResize = MirrorShrink | MirrorExpand deriving Typeable data MirrorResize = MirrorShrink | MirrorExpand
instance Message MirrorResize instance Message MirrorResize
data ResizableTall a = ResizableTall data ResizableTall a = ResizableTall

View File

@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -208,7 +208,6 @@ data SpacingModifier
| ModifyScreenBorderEnabled (Bool -> Bool) | ModifyScreenBorderEnabled (Bool -> Bool)
| ModifyWindowBorder (Border -> Border) | ModifyWindowBorder (Border -> Border)
| ModifyWindowBorderEnabled (Bool -> Bool) | ModifyWindowBorderEnabled (Bool -> Bool)
deriving (Typeable)
instance Message SpacingModifier instance Message SpacingModifier
@ -349,7 +348,7 @@ type SmartSpacingWithEdge = Spacing
-- | Message to dynamically modify (e.g. increase\/decrease\/set) the size of -- | Message to dynamically modify (e.g. increase\/decrease\/set) the size of
-- the screen spacing and window spacing. See 'SpacingModifier'. -- the screen spacing and window spacing. See 'SpacingModifier'.
newtype ModifySpacing = ModifySpacing (Int -> Int) deriving (Typeable) newtype ModifySpacing = ModifySpacing (Int -> Int)
instance Message ModifySpacing instance Message ModifySpacing

View File

@ -1,4 +1,4 @@
{-# LANGUAGE PatternGuards, ParallelListComp, DeriveDataTypeable, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} {-# LANGUAGE PatternGuards, ParallelListComp, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.SubLayouts -- Module : XMonad.Layout.SubLayouts
@ -255,7 +255,6 @@ data GroupMsg a
| WithGroup (W.Stack a -> X (W.Stack a)) a | WithGroup (W.Stack a -> X (W.Stack a)) a
| SubMessage SomeMessage a | SubMessage SomeMessage a
-- ^ the sublayout with the given window will get the message -- ^ 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 -- | 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 -- W.Stack of all windows, with the current group removed. The given window
@ -271,7 +270,6 @@ mergeDir f = WithGroup g
return cs return cs
newtype Broadcast = Broadcast SomeMessage -- ^ send a message to all sublayouts newtype Broadcast = Broadcast SomeMessage -- ^ send a message to all sublayouts
deriving (Typeable)
instance Message Broadcast instance Message Broadcast
instance Typeable a => Message (GroupMsg a) instance Typeable a => Message (GroupMsg a)

View File

@ -1,5 +1,5 @@
-- {-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, DeriveDataTypeable, TypeSynonymInstances, MultiParamTypeClasses #-} -- {-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, TypeSynonymInstances, MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, DeriveDataTypeable, MultiParamTypeClasses #-} {-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.TallMastersCombo -- 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 Bool -> Int -> Rational -> Rational -> l1 Window -> l2 Window -> TMSCombineTwo l1 l2 Window
tmsCombineTwo = TMSCombineTwo [] [] [] tmsCombineTwo = TMSCombineTwo [] [] []
data Orientation = Row | Col deriving (Read, Show, Typeable) data Orientation = Row | Col deriving (Read, Show)
instance Message Orientation instance Message Orientation
-- | A message that switches the orientation of TallMasterCombo layout and the RowsOrColumns layout. -- | 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 -- 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, -- visualizations. The 'SwitchOrientation' message refreshes layouts according to the orientation of the parent layout,
-- and will not affect the 'XMonad.Layout.Tabbed' decoration. -- 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 instance Message SwitchOrientation
-- | This message swaps the current focused window with the sub master window (first window in the second pane). -- | 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 instance Message SwapSubMaster
-- | This message changes the focus to the sub master window (first window in the second pane). -- | 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 instance Message FocusSubMaster
-- | This message triggers the 'NextLayout' message in the pane that contains the focused window. -- | 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 instance Message FocusedNextLayout
-- | This is a message for changing to the previous or next focused window across all the sub-layouts. -- | 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 Message ChangeFocus
-- instance (Typeable l1, Typeable l2, LayoutClass l1 Window, LayoutClass l2 Window) => LayoutClass (TMSCombineTwo l1 l2) Window where -- 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 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 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 instance Message NextNoWrap
handle :: (LayoutClass l a, Message m) => l a -> m -> X (Maybe (l a)) handle :: (LayoutClass l a, Message m) => l a -> m -> X (Maybe (l a))

View File

@ -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". -- "XMonad.Doc.Extending#Editing_key_bindings".
data ToggleLayouts lt lf a = ToggleLayouts Bool (lt a) (lf a) deriving (Read,Show) 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 instance Message ToggleLayout
toggleLayouts :: (LayoutClass lt a, LayoutClass lf a) => lt a -> lf a -> ToggleLayouts lt lf a toggleLayouts :: (LayoutClass lt a, LayoutClass lf a) => lt a -> lf a -> ToggleLayouts lt lf a

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, PatternGuards, FlexibleInstances, MultiParamTypeClasses #-} {-# LANGUAGE PatternGuards, FlexibleInstances, MultiParamTypeClasses #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.WindowArranger -- Module : XMonad.Layout.WindowArranger
@ -92,7 +92,6 @@ data WindowArrangerMsg = DeArrange
| MoveUp Int | MoveUp Int
| MoveDown Int | MoveDown Int
| SetGeometry Rectangle | SetGeometry Rectangle
deriving ( Typeable )
instance Message WindowArrangerMsg instance Message WindowArrangerMsg
data ArrangedWindow a = WR (a, Rectangle) data ArrangedWindow a = WR (a, Rectangle)

View File

@ -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". -- "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) instance Typeable a => Message (MoveWindowToWindow a)
data Navigate = Go Direction2D | Swap Direction2D | Move Direction2D data Navigate = Go Direction2D | Swap Direction2D | Move Direction2D
| Apply (Window -> X()) Direction2D -- ^ Apply action with destination window | Apply (Window -> X()) Direction2D -- ^ Apply action with destination window
deriving ( Typeable )
instance Message Navigate instance Message Navigate
data WNConfig = data WNConfig =

View File

@ -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". -- "XMonad.Doc.Extending#Editing_key_bindings".
newtype Chdir = Chdir String deriving ( Typeable ) newtype Chdir = Chdir String
instance Message Chdir instance Message Chdir
newtype WorkspaceDir a = WorkspaceDir String deriving ( Read, Show ) newtype WorkspaceDir a = WorkspaceDir String deriving ( Read, Show )

View File

@ -1,6 +1,6 @@
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds #-} {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses
, PatternGuards, DeriveDataTypeable, ExistentialQuantification , PatternGuards, ExistentialQuantification
, FlexibleContexts #-} , FlexibleContexts #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
@ -162,7 +162,7 @@ data ZoomMessage = Zoom Rational
| ZoomFullToggle | ZoomFullToggle
-- ^ Toggle whether the focused window should -- ^ Toggle whether the focused window should
-- occupy all available space when it has focus -- occupy all available space when it has focus
deriving (Typeable, Show) deriving (Show)
instance Message ZoomMessage instance Message ZoomMessage

View File

@ -14,8 +14,6 @@ The provided @unicodePrompt@ and @typeUnicodePrompt@ use @xsel@ and @xdotool@
respectively. respectively.
-} -}
{-# LANGUAGE DeriveDataTypeable #-}
module XMonad.Prompt.Unicode ( module XMonad.Prompt.Unicode (
-- * Usage -- * Usage
-- $usage -- $usage
@ -44,7 +42,7 @@ instance XPrompt Unicode where
nextCompletion Unicode = getNextCompletion nextCompletion Unicode = getNextCompletion
newtype UnicodeData = UnicodeData { getUnicodeData :: [(Char, BS.ByteString)] } newtype UnicodeData = UnicodeData { getUnicodeData :: [(Char, BS.ByteString)] }
deriving (Typeable, Read, Show) deriving (Read, Show)
instance ExtensionClass UnicodeData where instance ExtensionClass UnicodeData where
initialValue = UnicodeData [] initialValue = UnicodeData []

View File

@ -61,4 +61,3 @@ stripZsh :: String -> String
stripZsh "" = "" stripZsh "" = ""
stripZsh (' ':'-':'-':' ':_) = "" stripZsh (' ':'-':'-':' ':_) = ""
stripZsh (x:xs) = x : stripZsh xs stripZsh (x:xs) = x : stripZsh xs

View File

@ -70,7 +70,7 @@ cycleActionWithResult name actions = do
actions !! idx actions !! idx
newtype ActionCycleState = ActionCycleState (M.Map String Int) deriving (Typeable) newtype ActionCycleState = ActionCycleState (M.Map String Int)
instance ExtensionClass ActionCycleState where instance ExtensionClass ActionCycleState where
initialValue = ActionCycleState mempty initialValue = ActionCycleState mempty

View File

@ -46,7 +46,7 @@ import qualified XMonad.Util.ExtensibleState as XS
-- | Stores dynamic scratchpads as a map of name to window -- | Stores dynamic scratchpads as a map of name to window
newtype SPStorage = SPStorage (M.Map String Window) newtype SPStorage = SPStorage (M.Map String Window)
deriving (Typeable,Read,Show) deriving (Read,Show)
instance ExtensionClass SPStorage where instance ExtensionClass SPStorage where
initialValue = SPStorage M.empty initialValue = SPStorage M.empty

View File

@ -40,10 +40,9 @@ import XMonad.Prelude (fromMaybe)
-- and make it an instance of ExtensionClass. You can then use -- and make it an instance of ExtensionClass. You can then use
-- the functions from this module for storing and retrieving your data: -- the functions from this module for storing and retrieving your data:
-- --
-- > {-# LANGUAGE DeriveDataTypeable #-}
-- > import qualified XMonad.Util.ExtensibleState as XS -- > import qualified XMonad.Util.ExtensibleState as XS
-- > -- >
-- > data ListStorage = ListStorage [Integer] deriving Typeable -- > data ListStorage = ListStorage [Integer]
-- > instance ExtensionClass ListStorage where -- > instance ExtensionClass ListStorage where
-- > initialValue = ListStorage [] -- > initialValue = ListStorage []
-- > -- >
@ -61,7 +60,7 @@ import XMonad.Prelude (fromMaybe)
-- To make your data persistent between restarts, the data type needs to be -- 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: -- 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 -- > instance ExtensionClass ListStorage where
-- > initialValue = ListStorage [] -- > initialValue = ListStorage []

View File

@ -202,4 +202,4 @@ printStringXMF dpy drw fs@(Xft font) gc fc bc x y s = do
io $ withXftDraw dpy drw visual colormap $ io $ withXftDraw dpy drw visual colormap $
\draw -> withXftColorName dpy visual colormap fc $ \draw -> withXftColorName dpy visual colormap fc $
\color -> xftDrawString draw color font x y s \color -> xftDrawString draw color font x y s
#endif #endif

View File

@ -12,8 +12,6 @@
-- --
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
{-# LANGUAGE DeriveDataTypeable #-}
module XMonad.Util.Loggers.NamedScratchpad (-- * Usage module XMonad.Util.Loggers.NamedScratchpad (-- * Usage
-- $usage -- $usage
nspTrackStartup nspTrackStartup
@ -54,7 +52,7 @@ import qualified XMonad.StackSet as W (allWindows)
-- them instead (see 'XMonad.Util.NoTaskbar'). -- them instead (see 'XMonad.Util.NoTaskbar').
-- The extension data for tracking NSP windows -- The extension data for tracking NSP windows
newtype NSPTrack = NSPTrack [Maybe Window] deriving Typeable newtype NSPTrack = NSPTrack [Maybe Window]
instance ExtensionClass NSPTrack where instance ExtensionClass NSPTrack where
initialValue = NSPTrack [] initialValue = NSPTrack []

View File

@ -1,5 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-} -----------------------------------------------------------------------------
----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Util.Minimize -- Module : XMonad.Util.Minimize
-- Copyright : (c) Bogdan Sinitsyn (2016) -- Copyright : (c) Bogdan Sinitsyn (2016)
@ -28,7 +27,7 @@ data Minimized = Minimized
{ rectMap :: RectMap { rectMap :: RectMap
, minimizedStack :: [Window] , minimizedStack :: [Window]
} }
deriving (Eq, Typeable, Read, Show) deriving (Eq, Read, Show)
instance ExtensionClass Minimized where instance ExtensionClass Minimized where
initialValue = Minimized { rectMap = M.empty initialValue = Minimized { rectMap = M.empty

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
---------------------------------------------------------------------------- ----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Util.PositionStore -- 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. -- This way windows can be easily relocated and scaled when switching screens.
newtype PositionStore = PS (M.Map Window PosStoreRectangle) newtype PositionStore = PS (M.Map Window PosStoreRectangle)
deriving (Read,Show,Typeable) deriving (Read,Show)
data PosStoreRectangle = PSRectangle Double Double Double Double data PosStoreRectangle = PSRectangle Double Double Double Double
deriving (Read,Show,Typeable) deriving (Read,Show)
instance ExtensionClass PositionStore where instance ExtensionClass PositionStore where
initialValue = PS M.empty initialValue = PS M.empty

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Util.SessionStart -- Module : XMonad.Util.SessionStart
@ -39,7 +37,7 @@ import qualified XMonad.Util.ExtensibleState as XS
-- --------------------------------------------------------------------- -- ---------------------------------------------------------------------
newtype SessionStart = SessionStart { unSessionStart :: Bool } newtype SessionStart = SessionStart { unSessionStart :: Bool }
deriving (Read, Show, Typeable) deriving (Read, Show)
instance ExtensionClass SessionStart where instance ExtensionClass SessionStart where
initialValue = SessionStart True initialValue = SessionStart True

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Util.SpawnNamedPipe -- Module : XMonad.Util.SpawnNamedPipe
@ -51,7 +49,7 @@ import qualified Data.Map as Map
-- --
newtype NamedPipes = NamedPipes { pipeMap :: Map.Map String Handle } newtype NamedPipes = NamedPipes { pipeMap :: Map.Map String Handle }
deriving (Show, Typeable) deriving (Show)
instance ExtensionClass NamedPipes where instance ExtensionClass NamedPipes where
initialValue = NamedPipes Map.empty initialValue = NamedPipes Map.empty

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Util.SpawnOnce -- Module : XMonad.Util.SpawnOnce
@ -24,7 +22,7 @@ import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Prelude import XMonad.Prelude
newtype SpawnOnce = SpawnOnce { unspawnOnce :: Set String } newtype SpawnOnce = SpawnOnce { unspawnOnce :: Set String }
deriving (Read, Show, Typeable) deriving (Read, Show)
instance ExtensionClass SpawnOnce where instance ExtensionClass SpawnOnce where
initialValue = SpawnOnce Set.empty initialValue = SpawnOnce Set.empty

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Util.Types -- Module : XMonad.Util.Types
@ -17,14 +16,12 @@ module XMonad.Util.Types (Direction1D(..)
,Direction2D(..) ,Direction2D(..)
) where ) where
import Data.Typeable (Typeable)
-- | One-dimensional directions: -- | One-dimensional directions:
data Direction1D = Next | Prev deriving (Eq,Read,Show,Typeable) data Direction1D = Next | Prev deriving (Eq,Read,Show)
-- | Two-dimensional directions: -- | Two-dimensional directions:
data Direction2D = U -- ^ Up data Direction2D = U -- ^ Up
| D -- ^ Down | D -- ^ Down
| R -- ^ Right | R -- ^ Right
| L -- ^ Left | L -- ^ Left
deriving (Eq,Read,Show,Ord,Enum,Bounded,Typeable) deriving (Eq,Read,Show,Ord,Enum,Bounded)