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: bd5b969d9b
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,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)

View File

@@ -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

View File

@@ -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)

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
w = sw * 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
@@ -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

View File

@@ -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)

View File

@@ -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

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
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))

View File

@@ -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

View File

@@ -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'

View File

@@ -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

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.
| DecGap !Int !Direction2D -- ^ Decrease a gap.
| ModifyGaps (GapSpec -> GapSpec) -- ^ Modify arbitrarily.
deriving (Typeable)
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
= 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

View File

@@ -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 {...}"

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

View File

@@ -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
--------------------------------------------------------------------------------

View File

@@ -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

View File

@@ -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

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 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

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 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

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
| ShowMonitorNamed String
| HideMonitorNamed String
deriving (Read,Show,Eq,Typeable)
deriving (Read,Show,Eq)
instance Message MonitorMessage
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
@@ -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

View File

@@ -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

View File

@@ -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

View File

@@ -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

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
-- 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)

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.
| 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)

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".
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')

View File

@@ -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

View File

@@ -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

View File

@@ -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'

View File

@@ -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')

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".
data MirrorResize = MirrorShrink | MirrorExpand deriving Typeable
data MirrorResize = MirrorShrink | MirrorExpand
instance Message MirrorResize
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)
| 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

View File

@@ -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)

View File

@@ -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))

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".
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

View File

@@ -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)

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".
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 =

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

View File

@@ -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