Skip to content

Commit

Permalink
Merge pull request #561 from exorcist365/master
Browse files Browse the repository at this point in the history
Remove all derivations of Typeable
  • Loading branch information
slotThe authored Jun 18, 2021
2 parents 4ddb3e4 + f732082 commit 722967c
Show file tree
Hide file tree
Showing 91 changed files with 143 additions and 235 deletions.
1 change: 0 additions & 1 deletion XMonad/Actions/CycleWorkspaceByScreen.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.CycleWorkspaceByScreen
Expand Down
6 changes: 2 additions & 4 deletions XMonad/Actions/DynamicProjects.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}

--------------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.DynamicProjects
Expand Down Expand Up @@ -126,14 +124,14 @@ data Project = Project
{ projectName :: !ProjectName -- ^ Workspace name.
, projectDirectory :: !FilePath -- ^ Working directory.
, projectStartHook :: !(Maybe (X ())) -- ^ Optional start-up hook.
} deriving Typeable
}

--------------------------------------------------------------------------------
-- | Internal project state.
data ProjectState = ProjectState
{ projects :: !ProjectTable
, previousProject :: !(Maybe WorkspaceId)
} deriving Typeable
}

--------------------------------------------------------------------------------
instance ExtensionClass ProjectState where
Expand Down
4 changes: 1 addition & 3 deletions XMonad/Actions/DynamicWorkspaceGroups.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.DynamicWorkspaceGroups
Expand Down Expand Up @@ -69,7 +67,7 @@ type WSGroup = [(ScreenId,WorkspaceId)]
type WSGroupId = String

newtype WSGroupStorage = WSG { unWSG :: M.Map WSGroupId WSGroup }
deriving (Typeable, Read, Show)
deriving (Read, Show)

withWSG :: (M.Map WSGroupId WSGroup -> M.Map WSGroupId WSGroup) -> WSGroupStorage -> WSGroupStorage
withWSG f = WSG . f . unWSG
Expand Down
4 changes: 1 addition & 3 deletions XMonad/Actions/DynamicWorkspaceOrder.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.DynamicWorkspaceOrder
Expand Down Expand Up @@ -90,7 +88,7 @@ import Data.Ord (comparing)

-- | Extensible state storage for the workspace order.
newtype WSOrderStorage = WSO { unWSO :: Maybe (M.Map WorkspaceId Int) }
deriving (Typeable, Read, Show)
deriving (Read, Show)

instance ExtensionClass WSOrderStorage where
initialValue = WSO Nothing
Expand Down
4 changes: 1 addition & 3 deletions XMonad/Actions/DynamicWorkspaces.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.DynamicWorkspaces
Expand Down Expand Up @@ -87,7 +85,7 @@ type WorkspaceIndex = Int
-- | Internal dynamic project state that stores a mapping between
-- workspace indexes and workspace tags.
newtype DynamicWorkspaceState = DynamicWorkspaceState {workspaceIndexMap :: Map.Map WorkspaceIndex WorkspaceTag}
deriving (Typeable, Read, Show)
deriving (Read, Show)

instance ExtensionClass DynamicWorkspaceState where
initialValue = DynamicWorkspaceState Map.empty
Expand Down
1 change: 0 additions & 1 deletion XMonad/Actions/FloatKeys.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,4 +117,3 @@ keysMoveResize f move resize w = whenX (isClient w) $ withDisplay $ \d -> do
io $ resizeWindow d w `uncurry` wn_dim
io $ moveWindow d w `uncurry` wn_pos
float w

2 changes: 0 additions & 2 deletions XMonad/Actions/FocusNth.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,5 +57,3 @@ listToStack n l = Stack t ls rs
where
(t:rs) = drop n l
ls = reverse (take n l)


4 changes: 1 addition & 3 deletions XMonad/Actions/GroupNavigation.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}

----------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.GroupNavigation
Expand Down Expand Up @@ -157,7 +155,7 @@ orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs'
-- The state extension that holds the history information
data HistoryDB = HistoryDB (Maybe Window) -- currently focused window
(Seq Window) -- previously focused windows
deriving (Read, Show, Typeable)
deriving (Read, Show)

instance ExtensionClass HistoryDB where

Expand Down
3 changes: 1 addition & 2 deletions XMonad/Actions/KeyRemap.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.KeyRemap
Expand Down Expand Up @@ -33,7 +32,7 @@ import XMonad.Util.Paste
import qualified XMonad.Util.ExtensibleState as XS


newtype KeymapTable = KeymapTable [((KeyMask, KeySym), (KeyMask, KeySym))] deriving (Typeable, Show)
newtype KeymapTable = KeymapTable [((KeyMask, KeySym), (KeyMask, KeySym))] deriving (Show)

instance ExtensionClass KeymapTable where
initialValue = KeymapTable []
Expand Down
3 changes: 1 addition & 2 deletions XMonad/Actions/LinkWorkspaces.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,6 @@
--
-----------------------------------------------------------------------------

{-# LANGUAGE DeriveDataTypeable #-}
module XMonad.Actions.LinkWorkspaces (
-- * Usage
-- $usage
Expand Down Expand Up @@ -76,7 +75,7 @@ noMessageFn :: ScreenId -> [Char] -> [Char] -> [Char] -> X()
noMessageFn _ _ _ _ = return () :: X ()

-- | Stuff for linking workspaces
newtype WorkspaceMap = WorkspaceMap (M.Map WorkspaceId WorkspaceId) deriving (Read, Show, Typeable)
newtype WorkspaceMap = WorkspaceMap (M.Map WorkspaceId WorkspaceId) deriving (Read, Show)
instance ExtensionClass WorkspaceMap
where initialValue = WorkspaceMap M.empty
extensionType = PersistentExtension
Expand Down
4 changes: 2 additions & 2 deletions XMonad/Actions/Navigation2D.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, MultiParamTypeClasses, PatternGuards, RankNTypes, TypeSynonymInstances #-}
{-# LANGUAGE MultiParamTypeClasses, PatternGuards, RankNTypes, TypeSynonymInstances #-}

-----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -384,7 +384,7 @@ data Navigation2DConfig = Navigation2DConfig
-- function calculates a rectangle for a given unmapped
-- window from the screen it is on and its window ID.
-- See <#Finer_Points> for how to use this.
} deriving Typeable
}

-- | Shorthand for the tedious screen type
type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
Expand Down
1 change: 0 additions & 1 deletion XMonad/Actions/PerWorkspaceKeys.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,4 +46,3 @@ bindOn bindings = chooseAction chooser where
Nothing -> case lookup "" bindings of
Just action -> action
Nothing -> return ()

4 changes: 2 additions & 2 deletions XMonad/Actions/Prefix.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, FlexibleContexts #-}
{-# LANGUAGE FlexibleContexts #-}

-----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -110,7 +110,7 @@ implementation is the following:
-}

data PrefixArgument = Raw Int | Numeric Int | None
deriving (Typeable, Read, Show)
deriving (Read, Show)
instance ExtensionClass PrefixArgument where
initialValue = None
extensionType = PersistentExtension
Expand Down
5 changes: 2 additions & 3 deletions XMonad/Actions/ShowText.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.ShowText
Expand Down Expand Up @@ -56,7 +55,7 @@ import qualified XMonad.Util.ExtensibleState as ES

-- | ShowText contains the map with timers as keys and created windows as values
newtype ShowText = ShowText (Map Atom Window)
deriving (Read,Show,Typeable)
deriving (Read,Show)

instance ExtensionClass ShowText where
initialValue = ShowText empty
Expand Down
3 changes: 1 addition & 2 deletions XMonad/Actions/SpawnOn.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.SpawnOn
Expand Down Expand Up @@ -66,7 +65,7 @@ import qualified XMonad.Util.ExtensibleState as XS
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".

newtype Spawner = Spawner {pidsRef :: [(ProcessID, ManageHook)]} deriving Typeable
newtype Spawner = Spawner {pidsRef :: [(ProcessID, ManageHook)]}

instance ExtensionClass Spawner where
initialValue = Spawner []
Expand Down
4 changes: 1 addition & 3 deletions XMonad/Actions/SwapPromote.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.SwapPromote
Expand Down Expand Up @@ -115,7 +113,7 @@ import Control.Arrow
-- Without history, the list is empty.
newtype MasterHistory = MasterHistory
{ getMasterHistory :: M.Map WorkspaceId [Window]
} deriving (Read,Show,Typeable)
} deriving (Read,Show)

instance ExtensionClass MasterHistory where
initialValue = MasterHistory M.empty
Expand Down
2 changes: 1 addition & 1 deletion XMonad/Actions/WithAll.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,4 +49,4 @@ withAll f = withWindowSet $ \ws -> let all' = integrate' . stack . workspace . c

-- | Kill all the windows on the current workspace.
killAll :: X()
killAll = withAll killWindow
killAll = withAll killWindow
5 changes: 2 additions & 3 deletions XMonad/Actions/Workscreen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@
-- This also permits to see all workspaces of a workscreen even if just
-- one screen is present, and to move windows from workspace to workscreen.
-----------------------------------------------------------------------------
{-# LANGUAGE DeriveDataTypeable #-}

module XMonad.Actions.Workscreen (
-- * Usage
Expand Down Expand Up @@ -58,10 +57,10 @@ import XMonad.Actions.OnScreen
-- "XMonad.Doc.Extending#Editing_key_bindings".


data Workscreen = Workscreen{workscreenId::Int,workspaces::[WorkspaceId]} deriving (Show,Typeable)
data Workscreen = Workscreen{workscreenId::Int,workspaces::[WorkspaceId]} deriving (Show)
type WorkscreenId=Int

data WorkscreenStorage = WorkscreenStorage WorkscreenId [Workscreen] deriving (Show,Typeable)
data WorkscreenStorage = WorkscreenStorage WorkscreenId [Workscreen] deriving (Show)
instance ExtensionClass WorkscreenStorage where
initialValue = WorkscreenStorage 0 []

Expand Down
9 changes: 4 additions & 5 deletions XMonad/Actions/WorkspaceCursors.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.WorkspaceCursors
Expand Down Expand Up @@ -46,7 +46,7 @@ import qualified XMonad.StackSet as W
import XMonad.Actions.FocusNth(focusNth')
import XMonad.Layout.LayoutModifier(ModifiedLayout(..),
LayoutModifier(handleMess, redoLayout))
import XMonad(Typeable, Message, WorkspaceId, X, XState(windowset),
import XMonad(Message, WorkspaceId, X, XState(windowset),
fromMessage, sendMessage, windows, gets)
import XMonad.Util.Stack (reverseS)
import XMonad.Prelude (find, fromJust, guard, liftA2, toList, when, (<=<))
Expand Down Expand Up @@ -114,7 +114,7 @@ end = Cons . fromJust . W.differentiate . map End

data Cursors a
= Cons (W.Stack (Cursors a))
| End a deriving (Eq,Show,Read,Typeable)
| End a deriving (Eq,Show,Read)

instance Foldable Cursors where
foldMap f (End x) = f x
Expand Down Expand Up @@ -190,7 +190,7 @@ modifyCursors :: (Cursors String -> X (Cursors String)) -> X ()
modifyCursors = sendMessage . ChangeCursors . (liftA2 (>>) updateXMD return <=<)

newtype WorkspaceCursors a = WorkspaceCursors (Cursors String)
deriving (Typeable,Read,Show)
deriving (Read,Show)

-- | The state is stored in the 'WorkspaceCursors' layout modifier. Put this as
-- your outermost modifier, unless you want different cursors at different
Expand All @@ -199,7 +199,6 @@ workspaceCursors :: Cursors String -> l a -> ModifiedLayout WorkspaceCursors l a
workspaceCursors = ModifiedLayout . WorkspaceCursors

newtype ChangeCursors = ChangeCursors { unWrap :: Cursors String -> X (Cursors String) }
deriving (Typeable)

instance Message ChangeCursors

Expand Down
4 changes: 1 addition & 3 deletions XMonad/Actions/WorkspaceNames.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,8 +15,6 @@
--
-----------------------------------------------------------------------------

{-# LANGUAGE DeriveDataTypeable #-}

module XMonad.Actions.WorkspaceNames (
-- * Usage
-- $usage
Expand Down Expand Up @@ -87,7 +85,7 @@ import qualified Data.Map as M

-- | Workspace names container.
newtype WorkspaceNames = WorkspaceNames (M.Map WorkspaceId String)
deriving (Typeable, Read, Show)
deriving (Read, Show)

instance ExtensionClass WorkspaceNames where
initialValue = WorkspaceNames M.empty
Expand Down
1 change: 0 additions & 1 deletion XMonad/Config/Saegesser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,4 +76,3 @@ myLogHook p = do
, ppTitle = xmobarColor "green" "" . shorten 180
}
fadeInactiveLogHook 0.6

1 change: 0 additions & 1 deletion XMonad/Doc/Configuring.hs
Original file line number Diff line number Diff line change
Expand Up @@ -148,4 +148,3 @@ GHC and xmonad are in the @$PATH@ in the environment from which xmonad
is started.
-}

3 changes: 1 addition & 2 deletions XMonad/Hooks/CurrentWorkspaceOnTop.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------
-- |
-- Module : XMonad.Hooks.CurrentWorkspaceOnTop
Expand Down Expand Up @@ -40,7 +39,7 @@ import qualified Data.Map as M
-- > }
--

newtype CWOTState = CWOTS String deriving Typeable
newtype CWOTState = CWOTS String

instance ExtensionClass CWOTState where
initialValue = CWOTS ""
Expand Down
3 changes: 1 addition & 2 deletions XMonad/Hooks/DynamicBars.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Hooks.DynamicBars
Expand Down Expand Up @@ -81,7 +80,7 @@ import qualified XMonad.Util.ExtensibleState as XS

newtype DynStatusBarInfo = DynStatusBarInfo
{ dsbInfo :: [(ScreenId, Handle)]
} deriving (Typeable)
}

instance ExtensionClass DynStatusBarInfo where
initialValue = DynStatusBarInfo []
Expand Down
2 changes: 0 additions & 2 deletions XMonad/Hooks/DynamicHooks.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Hooks.DynamicHooks
Expand Down Expand Up @@ -48,7 +47,6 @@ import qualified XMonad.Util.ExtensibleState as XS
data DynamicHooks = DynamicHooks
{ transients :: [(Query Bool, ManageHook)]
, permanent :: ManageHook }
deriving Typeable

instance ExtensionClass DynamicHooks where
initialValue = DynamicHooks [] idHook
Expand Down
Loading

0 comments on commit 722967c

Please sign in to comment.