mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 03:20:21 -07:00
Apply hlint 3.5 hints
This commit is contained in:
parent
6117a867d9
commit
6b20dbca42
@ -1,4 +1,5 @@
|
|||||||
{-# LANGUAGE PatternGuards #-}
|
{-# LANGUAGE PatternGuards #-}
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-orphans #-}
|
{-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-orphans #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
@ -114,9 +115,9 @@ keys x = M.fromList $
|
|||||||
]
|
]
|
||||||
|
|
||||||
++
|
++
|
||||||
zip (zip (repeat $ modMask x) [xK_F1..xK_F12]) (map (withNthWorkspace W.greedyView) [0..])
|
zip (map (modMask x,) [xK_F1..xK_F12]) (map (withNthWorkspace W.greedyView) [0..])
|
||||||
++
|
++
|
||||||
zip (zip (repeat (modMask x .|. shiftMask)) [xK_F1..xK_F12]) (map (withNthWorkspace copy) [0..])
|
zip (map (modMask x .|. shiftMask,) [xK_F1..xK_F12]) (map (withNthWorkspace copy) [0..])
|
||||||
|
|
||||||
config = docks $ ewmh def
|
config = docks $ ewmh def
|
||||||
{ borderWidth = 1 -- Width of the window border in pixels.
|
{ borderWidth = 1 -- Width of the window border in pixels.
|
||||||
|
@ -1,3 +1,4 @@
|
|||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : XMonad.Hooks.Place
|
-- Module : XMonad.Hooks.Place
|
||||||
@ -188,7 +189,7 @@ placeHook p = do window <- ask
|
|||||||
let infos = filter ((window `elem`) . stackContents . S.stack . fst)
|
let infos = filter ((window `elem`) . stackContents . S.stack . fst)
|
||||||
$ [screenInfo $ S.current theWS]
|
$ [screenInfo $ S.current theWS]
|
||||||
++ map screenInfo (S.visible theWS)
|
++ map screenInfo (S.visible theWS)
|
||||||
++ zip (S.hidden theWS) (repeat currentRect)
|
++ map (, currentRect) (S.hidden theWS)
|
||||||
|
|
||||||
guard(not $ null infos)
|
guard(not $ null infos)
|
||||||
|
|
||||||
|
@ -1,8 +1,9 @@
|
|||||||
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE PatternGuards #-}
|
{-# LANGUAGE PatternGuards #-}
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE TupleSections #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : XMonad.Layout.Decoration
|
-- Module : XMonad.Layout.Decoration
|
||||||
@ -241,7 +242,7 @@ instance (DecorationStyle ds Window, Shrinker s) => LayoutModifier (Decoration d
|
|||||||
toDel = todel d dwrs
|
toDel = todel d dwrs
|
||||||
toAdd = toadd a wrs
|
toAdd = toadd a wrs
|
||||||
deleteDecos (map snd toDel)
|
deleteDecos (map snd toDel)
|
||||||
let ndwrs = zip toAdd $ repeat (Nothing,Nothing)
|
let ndwrs = map (, (Nothing,Nothing)) toAdd
|
||||||
ndecos <- resync (ndwrs ++ del_dwrs d dwrs) wrs
|
ndecos <- resync (ndwrs ++ del_dwrs d dwrs) wrs
|
||||||
processState (s {decos = ndecos })
|
processState (s {decos = ndecos })
|
||||||
|
|
||||||
|
@ -1,4 +1,6 @@
|
|||||||
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : XMonad.Layout.Simplest
|
-- Module : XMonad.Layout.Simplest
|
||||||
@ -39,4 +41,4 @@ import qualified XMonad.StackSet as S
|
|||||||
|
|
||||||
data Simplest a = Simplest deriving (Show, Read)
|
data Simplest a = Simplest deriving (Show, Read)
|
||||||
instance LayoutClass Simplest a where
|
instance LayoutClass Simplest a where
|
||||||
pureLayout Simplest rec (S.Stack w l r) = zip (w : reverse l ++ r) (repeat rec)
|
pureLayout Simplest rec (S.Stack w l r) = map (, rec) (w : reverse l ++ r)
|
||||||
|
@ -4,6 +4,7 @@
|
|||||||
{-# LANGUAGE ParallelListComp #-}
|
{-# LANGUAGE ParallelListComp #-}
|
||||||
{-# LANGUAGE PatternGuards #-}
|
{-# LANGUAGE PatternGuards #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
{-# LANGUAGE ViewPatterns #-}
|
{-# LANGUAGE ViewPatterns #-}
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
@ -347,7 +348,7 @@ instance forall l. (Read (l Window), Show (l Window), LayoutClass l Window) => L
|
|||||||
return $ Just $ Sublayout (I ((sm,w):ms)) defl sls
|
return $ Just $ Sublayout (I ((sm,w):ms)) defl sls
|
||||||
|
|
||||||
| Just (Broadcast sm) <- fromMessage m = do
|
| Just (Broadcast sm) <- fromMessage m = do
|
||||||
ms' <- fmap (zip (repeat sm) . W.integrate') currentStack
|
ms' <- fmap (map (sm,) . W.integrate') currentStack
|
||||||
return $ if null ms' then Nothing
|
return $ if null ms' then Nothing
|
||||||
else Just $ Sublayout (I $ ms' ++ ms) defl sls
|
else Just $ Sublayout (I $ ms' ++ ms) defl sls
|
||||||
|
|
||||||
@ -408,7 +409,7 @@ instance forall l. (Read (l Window), Show (l Window), LayoutClass l Window) => L
|
|||||||
catchLayoutMess :: LayoutMessages -> X (Maybe (Sublayout l Window))
|
catchLayoutMess :: LayoutMessages -> X (Maybe (Sublayout l Window))
|
||||||
catchLayoutMess x = do
|
catchLayoutMess x = do
|
||||||
let m' = x `asTypeOf` (undefined :: LayoutMessages)
|
let m' = x `asTypeOf` (undefined :: LayoutMessages)
|
||||||
ms' <- zip (repeat $ SomeMessage m') . W.integrate'
|
ms' <- map (SomeMessage m',) . W.integrate'
|
||||||
<$> currentStack
|
<$> currentStack
|
||||||
return $ do guard $ not $ null ms'
|
return $ do guard $ not $ null ms'
|
||||||
Just $ Sublayout (I $ ms' ++ ms) defl sls
|
Just $ Sublayout (I $ ms' ++ ms) defl sls
|
||||||
|
@ -1,4 +1,5 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
--------------------------------------------------------------------
|
--------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : XMonad.Util.EZConfig
|
-- Module : XMonad.Util.EZConfig
|
||||||
@ -123,7 +124,7 @@ removeKeys conf keyList =
|
|||||||
|
|
||||||
removeKeysP :: XConfig l -> [String] -> XConfig l
|
removeKeysP :: XConfig l -> [String] -> XConfig l
|
||||||
removeKeysP conf keyList =
|
removeKeysP conf keyList =
|
||||||
conf { keys = \cnf -> keys conf cnf `M.difference` mkKeymap cnf (zip keyList $ repeat (return ())) }
|
conf { keys = \cnf -> keys conf cnf `M.difference` mkKeymap cnf (map (, return ()) keyList) }
|
||||||
|
|
||||||
-- | Like 'additionalKeys', but for mouse bindings.
|
-- | Like 'additionalKeys', but for mouse bindings.
|
||||||
additionalMouseBindings :: XConfig a -> [((ButtonMask, Button), Window -> X ())] -> XConfig a
|
additionalMouseBindings :: XConfig a -> [((ButtonMask, Button), Window -> X ())] -> XConfig a
|
||||||
|
Loading…
x
Reference in New Issue
Block a user