mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 00:20:22 -07:00
Lint some pieces of code
Closes: https://github.com/xmonad/xmonad/pull/401
This commit is contained in:
parent
9189d002dd
commit
165e25f9e0
@ -218,7 +218,7 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
||||
, ((modMask , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area
|
||||
|
||||
-- quit, or restart
|
||||
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
|
||||
, ((modMask .|. shiftMask, xK_q ), io exitSuccess) -- %! Quit xmonad
|
||||
, ((modMask , xK_q ), spawn "if type xmonad; then xmonad --recompile && xmonad --restart; else xmessage xmonad not in \\$PATH: \"$PATH\"; fi") -- %! Restart xmonad
|
||||
|
||||
, ((modMask .|. shiftMask, xK_slash ), helpCommand) -- %! Run xmessage with a summary of the default keybindings (useful for beginners)
|
||||
|
@ -41,11 +41,11 @@ import Control.Applicative ((<|>), empty)
|
||||
import Control.Monad.Fail
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Reader
|
||||
import Control.Monad (void)
|
||||
import Data.Semigroup
|
||||
import Data.Traversable (for)
|
||||
import Data.Time.Clock (UTCTime)
|
||||
import Data.Default.Class
|
||||
import Data.List (isInfixOf)
|
||||
import System.FilePath
|
||||
import System.IO
|
||||
import System.Info
|
||||
@ -60,7 +60,7 @@ import System.Exit
|
||||
import Graphics.X11.Xlib
|
||||
import Graphics.X11.Xlib.Extras (getWindowAttributes, WindowAttributes, Event)
|
||||
import Data.Typeable
|
||||
import Data.List ((\\))
|
||||
import Data.List (isInfixOf, (\\))
|
||||
import Data.Maybe (isJust,fromMaybe)
|
||||
|
||||
import qualified Data.Map as M
|
||||
@ -431,7 +431,7 @@ catchIO f = io (f `E.catch` \(SomeException e) -> hPrint stderr e >> hFlush stde
|
||||
--
|
||||
-- Note this function assumes your locale uses utf8.
|
||||
spawn :: MonadIO m => String -> m ()
|
||||
spawn x = spawnPID x >> return ()
|
||||
spawn x = void $ spawnPID x
|
||||
|
||||
-- | Like 'spawn', but returns the 'ProcessID' of the launched application
|
||||
spawnPID :: MonadIO m => String -> m ProcessID
|
||||
|
@ -39,7 +39,7 @@ import Data.Maybe (fromMaybe)
|
||||
data Resize = Shrink | Expand
|
||||
|
||||
-- | Increase the number of clients in the master pane.
|
||||
data IncMasterN = IncMasterN !Int
|
||||
newtype IncMasterN = IncMasterN Int
|
||||
|
||||
instance Message Resize
|
||||
instance Message IncMasterN
|
||||
@ -199,8 +199,8 @@ choose (Choose d l r) d' ml mr = f lr
|
||||
(CL, CR) -> (hide l' , return r')
|
||||
(CR, CL) -> (return l', hide r' )
|
||||
(_ , _ ) -> (return l', return r')
|
||||
f (x,y) = fmap Just $ liftM2 (Choose d') x y
|
||||
hide x = fmap (fromMaybe x) $ handle x Hide
|
||||
f (x,y) = Just <$> liftM2 (Choose d') x y
|
||||
hide x = fromMaybe x <$> handle x Hide
|
||||
|
||||
instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
|
||||
runLayout (W.Workspace i (Choose CL l r) ms) =
|
||||
|
@ -87,14 +87,14 @@ usage :: IO ()
|
||||
usage = do
|
||||
self <- getProgName
|
||||
putStr . unlines $
|
||||
concat ["Usage: ", self, " [OPTION]"] :
|
||||
"Options:" :
|
||||
" --help Print this message" :
|
||||
" --version Print the version number" :
|
||||
" --recompile Recompile your xmonad.hs" :
|
||||
" --replace Replace the running window manager with xmonad" :
|
||||
" --restart Request a running xmonad process to restart" :
|
||||
[]
|
||||
[ "Usage: " <> self <> " [OPTION]"
|
||||
, "Options:"
|
||||
, " --help Print this message"
|
||||
, " --version Print the version number"
|
||||
, " --recompile Recompile your xmonad.hs"
|
||||
, " --replace Replace the running window manager with xmonad"
|
||||
, " --restart Request a running xmonad process to restart"
|
||||
]
|
||||
|
||||
-- | Build the xmonad configuration file with ghc, then execute it.
|
||||
-- If there are no errors, this function does not return. An
|
||||
@ -330,7 +330,7 @@ handle e@(DestroyWindowEvent {ev_window = w}) = do
|
||||
-- it is synthetic or we are not expecting an unmap notification from a window.
|
||||
handle (UnmapEvent {ev_window = w, ev_send_event = synthetic}) = whenX (isClient w) $ do
|
||||
e <- gets (fromMaybe 0 . M.lookup w . waitingUnmap)
|
||||
if (synthetic || e == 0)
|
||||
if synthetic || e == 0
|
||||
then unmanage w
|
||||
else modify (\s -> s { waitingUnmap = M.update mpred w (waitingUnmap s) })
|
||||
where mpred 1 = Nothing
|
||||
@ -428,7 +428,7 @@ handle event@(PropertyEvent { ev_event_type = t, ev_atom = a })
|
||||
|
||||
handle e@ClientMessageEvent { ev_message_type = mt } = do
|
||||
a <- getAtom "XMONAD_RESTART"
|
||||
if (mt == a)
|
||||
if mt == a
|
||||
then restart "xmonad" True
|
||||
else broadcastMessage e
|
||||
|
||||
|
@ -65,7 +65,7 @@ infixr 3 <&&>, <||>
|
||||
|
||||
-- | '||' lifted to a 'Monad'.
|
||||
(<||>) :: Monad m => m Bool -> m Bool -> m Bool
|
||||
(<||>) x y = ifM x (pure True) y
|
||||
(<||>) x = ifM x (pure True)
|
||||
|
||||
-- | If-then-else lifted to a 'Monad'.
|
||||
ifM :: Monad m => m Bool -> m a -> m a -> m a
|
||||
@ -98,7 +98,7 @@ className = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap resClass $ io $ getC
|
||||
-- | A query that can return an arbitrary X property of type 'String',
|
||||
-- identified by name.
|
||||
stringProperty :: String -> Query String
|
||||
stringProperty p = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap (fromMaybe "") $ getStringProperty d w p)
|
||||
stringProperty p = ask >>= (\w -> liftX $ withDisplay $ \d -> fromMaybe "" <$> getStringProperty d w p)
|
||||
|
||||
getStringProperty :: Display -> Window -> String -> X (Maybe String)
|
||||
getStringProperty d w p = do
|
||||
|
@ -66,6 +66,7 @@ import qualified Data.Set as S
|
||||
import Control.Arrow (second)
|
||||
import Control.Monad.Reader
|
||||
import Control.Monad.State
|
||||
import Control.Monad (void)
|
||||
import qualified Control.Exception as C
|
||||
|
||||
import System.IO
|
||||
@ -136,7 +137,7 @@ killWindow w = withDisplay $ \d -> do
|
||||
setEventType ev clientMessage
|
||||
setClientMessageEvent ev w wmprot 32 wmdelt currentTime
|
||||
sendEvent d w False noEventMask ev
|
||||
else killClient d w >> return ()
|
||||
else void (killClient d w)
|
||||
|
||||
-- | Kill the currently focused client.
|
||||
kill :: X ()
|
||||
@ -417,7 +418,7 @@ setFocusX w = withWindowSet $ \ws -> do
|
||||
currevt <- asks currentEvent
|
||||
let inputHintSet = wmh_flags hints `testBit` inputHintBit
|
||||
|
||||
when ((inputHintSet && wmh_input hints) || (not inputHintSet)) $
|
||||
when (inputHintSet && wmh_input hints || not inputHintSet) $
|
||||
io $ do setInputFocus dpy w revertToPointerRoot 0
|
||||
when (wmtf `elem` protocols) $
|
||||
io $ allocaXEvent $ \ev -> do
|
||||
@ -425,7 +426,7 @@ setFocusX w = withWindowSet $ \ws -> do
|
||||
setClientMessageEvent ev w wmprot 32 wmtf $ maybe currentTime event_time currevt
|
||||
sendEvent dpy w False noEventMask ev
|
||||
where event_time ev =
|
||||
if (ev_event_type ev) `elem` timedEvents then
|
||||
if ev_event_type ev `elem` timedEvents then
|
||||
ev_time ev
|
||||
else
|
||||
currentTime
|
||||
@ -515,7 +516,7 @@ cleanMask km = do
|
||||
-- | Get the 'Pixel' value for a named color.
|
||||
initColor :: Display -> String -> IO (Maybe Pixel)
|
||||
initColor dpy c = C.handle (\(C.SomeException _) -> return Nothing) $
|
||||
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
|
||||
Just . color_pixel . fst <$> allocNamedColor dpy colormap c
|
||||
where colormap = defaultColormap dpy (defaultScreen dpy)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
@ -535,7 +536,7 @@ writeStateToFile = do
|
||||
maybeShow _ = Nothing
|
||||
|
||||
wsData = W.mapLayout show . windowset
|
||||
extState = catMaybes . map maybeShow . M.toList . extensibleState
|
||||
extState = mapMaybe maybeShow . M.toList . extensibleState
|
||||
|
||||
path <- asks $ stateFileName . directories
|
||||
stateData <- gets (\s -> StateFile (wsData s) (extState s))
|
||||
@ -598,7 +599,7 @@ floatLocation w =
|
||||
catchX go $ do
|
||||
-- Fallback solution if `go' fails. Which it might, since it
|
||||
-- calls `getWindowAttributes'.
|
||||
sc <- W.current <$> gets windowset
|
||||
sc <- gets $ W.current . windowset
|
||||
return (W.screen sc, W.RationalRect 0 0 1 1)
|
||||
|
||||
where fi x = fromIntegral x
|
||||
|
@ -240,7 +240,7 @@ view i s
|
||||
|
||||
| otherwise = s -- not a member of the stackset
|
||||
|
||||
where equating f = \x y -> f x == f y
|
||||
where equating f x y = f x == f y
|
||||
|
||||
-- 'Catch'ing this might be hard. Relies on monotonically increasing
|
||||
-- workspace tags defined in 'new'
|
||||
|
Loading…
x
Reference in New Issue
Block a user