diff --git a/XMonad/Actions/EasyMotion.hs b/XMonad/Actions/EasyMotion.hs index 8f449f6c..1d27a294 100644 --- a/XMonad/Actions/EasyMotion.hs +++ b/XMonad/Actions/EasyMotion.hs @@ -387,5 +387,5 @@ handleKeyboard dpy drawFn cancel selected deselected = do _ -> handleKeyboard dpy drawFn cancel (trim fg) (clear bg) >>= retryBackspace where (fg, bg) = partition ((== Just keySym) . listToMaybe . chord) selected - trim = map (\o -> o { chord = tail $ chord o }) + trim = map (\o -> o { chord = drop 1 $ chord o }) clear = map (\o -> o { chord = [] }) diff --git a/XMonad/Actions/Navigation2D.hs b/XMonad/Actions/Navigation2D.hs index 6cb59874..1c1c635e 100644 --- a/XMonad/Actions/Navigation2D.hs +++ b/XMonad/Actions/Navigation2D.hs @@ -783,8 +783,7 @@ doCenterNavigation dir (cur, rect) winrects -- All the points that coincide with the current center and succeed it -- in the (appropriately ordered) window stack. - onCtr' = L.tail $ L.dropWhile ((cur /=) . fst) onCtr - -- tail should be safe here because cur should be in onCtr + onCtr' = L.drop 1 $ L.dropWhile ((cur /=) . fst) onCtr -- All the points that do not coincide with the current center and which -- lie in the (rotated) right cone. @@ -885,7 +884,7 @@ swap win winset = W.focusWindow cur newvisws = zipWith (\ws wns -> ws { W.stack = W.differentiate wns }) visws newwins newscrs = zipWith (\scr ws -> scr { W.workspace = ws }) scrs newvisws newwinset = winset { W.current = head newscrs - , W.visible = tail newscrs + , W.visible = drop 1 newscrs } -- | Calculates the center of a rectangle diff --git a/XMonad/Actions/Search.hs b/XMonad/Actions/Search.hs index 3f4ca274..1fd6b841 100644 --- a/XMonad/Actions/Search.hs +++ b/XMonad/Actions/Search.hs @@ -322,7 +322,7 @@ searchEngine name site = searchEngineF name (\s -> site ++ escape s) inside of a URL instead of in the end) you can use the alternative 'searchEngineF' function. > searchFunc :: String -> String -> searchFunc s | "wiki:" `isPrefixOf` s = "https://en.wikipedia.org/wiki/" ++ (escape $ tail $ snd $ break (==':') s) +> searchFunc s | "wiki:" `isPrefixOf` s = "https://en.wikipedia.org/wiki/" ++ (escape $ drop 1 $ snd $ break (==':') s) > | "https://" `isPrefixOf` s = s > | otherwise = (use google) s > myNewEngine = searchEngineF "mymulti" searchFunc diff --git a/XMonad/Actions/WorkspaceCursors.hs b/XMonad/Actions/WorkspaceCursors.hs index 6f3f1693..226f554c 100644 --- a/XMonad/Actions/WorkspaceCursors.hs +++ b/XMonad/Actions/WorkspaceCursors.hs @@ -98,7 +98,7 @@ makeCursors :: [[String]] -> Cursors String makeCursors [] = error "Workspace Cursors cannot be empty" makeCursors a = concat . reverse <$> foldl addDim x xs where x = end $ map return $ head a - xs = map (map return) $ tail a + xs = map (map return) $ drop 1 a -- this could probably be simplified, but this true: -- toList . makeCursors == map (concat . reverse) . sequence . reverse . map (map (:[])) -- the strange order is used because it makes the regular M-1..9 diff --git a/XMonad/Hooks/DebugEvents.hs b/XMonad/Hooks/DebugEvents.hs index f74e223b..f200fd1b 100644 --- a/XMonad/Hooks/DebugEvents.hs +++ b/XMonad/Hooks/DebugEvents.hs @@ -687,9 +687,7 @@ dumpString = do \s -> if null s then Nothing else let (w,s'') = break (== '\NUL') s - s' = if null s'' - then s'' - else tail s'' + s' = drop 1 s'' in Just (w,s') case ss of [s] -> append $ show s diff --git a/XMonad/Hooks/InsertPosition.hs b/XMonad/Hooks/InsertPosition.hs index fc88ffe6..1d1a92d1 100644 --- a/XMonad/Hooks/InsertPosition.hs +++ b/XMonad/Hooks/InsertPosition.hs @@ -83,4 +83,4 @@ insertDown w = W.swapDown . W.insertUp w focusLast' :: W.Stack a -> W.Stack a focusLast' st = let ws = W.integrate st - in W.Stack (last ws) (tail $ reverse ws) [] + in W.Stack (last ws) (drop 1 $ reverse ws) [] diff --git a/XMonad/Hooks/StatusBar/PP.hs b/XMonad/Hooks/StatusBar/PP.hs index 9b7f9fa6..e3c1f30c 100644 --- a/XMonad/Hooks/StatusBar/PP.hs +++ b/XMonad/Hooks/StatusBar/PP.hs @@ -464,7 +464,7 @@ xmobarStrip = converge (xmobarStripTags ["fc","icon","action"]) converge :: (Eq a) => (a -> a) -> a -> a converge f a = let xs = iterate f a - in fst $ head $ dropWhile (uncurry (/=)) $ zip xs $ tail xs + in fst $ head $ dropWhile (uncurry (/=)) $ zip xs $ drop 1 xs xmobarStripTags :: [String] -- ^ tags -> String -> String -- ^ with all \...\ removed diff --git a/XMonad/Layout/CenteredMaster.hs b/XMonad/Layout/CenteredMaster.hs index 819cb032..4538b943 100644 --- a/XMonad/Layout/CenteredMaster.hs +++ b/XMonad/Layout/CenteredMaster.hs @@ -84,7 +84,7 @@ applyPosition pos wksp rect = do runLayout wksp rect else do let firstW = head ws - let other = tail ws + let other = drop 1 ws let filtStack = stack >>= W.filter (firstW /=) wrs <- runLayout (wksp {W.stack = filtStack}) rect return $ first ((firstW, place pos other rect) :) wrs diff --git a/XMonad/Layout/Combo.hs b/XMonad/Layout/Combo.hs index e5e41c70..7252f95d 100644 --- a/XMonad/Layout/Combo.hs +++ b/XMonad/Layout/Combo.hs @@ -132,7 +132,7 @@ instance (LayoutClass l (), LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, differentiate :: Eq q => [q] -> [q] -> Maybe (Stack q) differentiate (z:zs) xs | z `elem` xs = Just $ Stack { focus=z , up = reverse $ takeWhile (/=z) xs - , down = tail $ dropWhile (/=z) xs } + , down = drop 1 $ dropWhile (/=z) xs } | otherwise = differentiate zs xs differentiate [] xs = W.differentiate xs diff --git a/XMonad/Layout/Dwindle.hs b/XMonad/Layout/Dwindle.hs index dadf8adf..222b7721 100644 --- a/XMonad/Layout/Dwindle.hs +++ b/XMonad/Layout/Dwindle.hs @@ -159,8 +159,8 @@ squeeze dir ratio rect st = zip wins rects nwins = length wins sizes = take nwins $ unfoldr (\r -> Just (r * ratio, r * ratio)) 1 totals' = 0 : zipWith (+) sizes totals' - totals = tail totals' - splits = zip (tail sizes) totals + totals = drop 1 totals' + splits = zip (drop 1 sizes) totals ratios = reverse $ map (uncurry (/)) splits rects = genRects rect ratios genRects r [] = [r] diff --git a/XMonad/Layout/Grid.hs b/XMonad/Layout/Grid.hs index 3e5f44b7..a89fc8bb 100644 --- a/XMonad/Layout/Grid.hs +++ b/XMonad/Layout/Grid.hs @@ -61,7 +61,7 @@ arrange aspectRatio (Rectangle rx ry rw rh) st = zip st rectangles mincs = max 1 $ nwins `div` ncols extrs = nwins - ncols * mincs chop :: Int -> Dimension -> [(Position, Dimension)] - chop n m = ((0, m - k * fromIntegral (pred n)) :) . map (, k) . tail . reverse . take n . tail . iterate (subtract k') $ m' + chop n m = ((0, m - k * fromIntegral (pred n)) :) . map (, k) . drop 1 . reverse . take n . drop 1 . iterate (subtract k') $ m' where k :: Dimension k = m `div` fromIntegral n diff --git a/XMonad/Layout/Groups/Helpers.hs b/XMonad/Layout/Groups/Helpers.hs index 808d2c02..40b799cf 100644 --- a/XMonad/Layout/Groups/Helpers.hs +++ b/XMonad/Layout/Groups/Helpers.hs @@ -155,7 +155,7 @@ focusHelper :: (Bool -> Bool) -- ^ if you want to focus a floating window, 'id'. -> X () focusHelper f g = withFocused $ \w -> do ws <- getWindows - let (before, tail -> after) = span (/=w) ws + let (before, drop 1 -> after) = span (/=w) ws let toFocus = g $ after ++ before floats <- getFloats case filter (f . flip elem floats) toFocus of diff --git a/XMonad/Layout/MultiColumns.hs b/XMonad/Layout/MultiColumns.hs index b32642aa..3dc4d692 100644 --- a/XMonad/Layout/MultiColumns.hs +++ b/XMonad/Layout/MultiColumns.hs @@ -96,7 +96,7 @@ instance LayoutClass MultiCol a where ,fmap incmastern (fromMessage m)] where resize Shrink = l { multiColSize = max (-0.5) $ s-ds } resize Expand = l { multiColSize = min 1 $ s+ds } - incmastern (IncMasterN x) = l { multiColNWin = take a n ++ [newval] ++ tail r } + incmastern (IncMasterN x) = l { multiColNWin = take a n ++ [newval] ++ drop 1 r } where newval = max 0 $ head r + x r = drop a n n = multiColNWin l diff --git a/XMonad/Layout/OneBig.hs b/XMonad/Layout/OneBig.hs index cd1d2f39..787c9f39 100644 --- a/XMonad/Layout/OneBig.hs +++ b/XMonad/Layout/OneBig.hs @@ -66,7 +66,7 @@ oneBigLayout (OneBig cx cy) rect stack = [(master,masterRect)] w = wd rect m = calcBottomWs n w h' master = head ws - other = tail ws + other = drop 1 ws bottomWs = take m other rightWs = drop m other masterRect = cmaster n m cx cy rect diff --git a/XMonad/Layout/Spiral.hs b/XMonad/Layout/Spiral.hs index 258b6b08..a2fd10ec 100644 --- a/XMonad/Layout/Spiral.hs +++ b/XMonad/Layout/Spiral.hs @@ -45,7 +45,7 @@ import XMonad.StackSet ( integrate ) -- "XMonad.Doc.Extending#Editing_the_layout_hook". fibs :: [Integer] -fibs = 1 : 1 : zipWith (+) fibs (tail fibs) +fibs = 1 : 1 : zipWith (+) fibs (drop 1 fibs) mkRatios :: [Integer] -> [Rational] mkRatios (x1:x2:xs) = (x1 % x2) : mkRatios (x2:xs) @@ -82,7 +82,7 @@ data SpiralWithDir a = SpiralWithDir Direction Rotation Rational instance LayoutClass SpiralWithDir a where pureLayout (SpiralWithDir dir rot scale) sc stack = zip ws rects where ws = integrate stack - ratios = blend scale . reverse . take (length ws - 1) . mkRatios $ tail fibs + ratios = blend scale . reverse . take (length ws - 1) . mkRatios $ drop 1 fibs rects = divideRects (zip ratios dirs) sc dirs = dropWhile (/= dir) $ case rot of CW -> cycle [East .. North] diff --git a/XMonad/Prompt.hs b/XMonad/Prompt.hs index f2d85080..020cfa6a 100644 --- a/XMonad/Prompt.hs +++ b/XMonad/Prompt.hs @@ -540,7 +540,7 @@ mkXPromptWithModes modes conf = do let defaultMode = head modes modeStack = W.Stack { W.focus = defaultMode -- Current mode , W.up = [] - , W.down = tail modes -- Other modes + , W.down = drop 1 modes -- Other modes } om = XPMultipleModes modeStack st' <- mkXPromptImplementation (showXPrompt defaultMode) conf { alwaysHighlight = True } om @@ -650,7 +650,7 @@ eventLoop handle stopAction = do return (ks, s, ev) else return (noSymbol, "", ev) l -> do - modify $ \s -> s { eventBuffer = tail l } + modify $ \s -> s { eventBuffer = drop 1 l } return $ head l handle (keysym,keystr) event stopAction >>= \stop -> unless stop (eventLoop handle stopAction) @@ -1315,7 +1315,7 @@ deleteString d = c oc oo | oo >= length oc && d == Prev = take (oo - 1) oc | oo < length oc && d == Prev = take (oo - 1) f ++ ss - | oo < length oc && d == Next = f ++ tail ss + | oo < length oc && d == Next = f ++ drop 1 ss | otherwise = oc where (f,ss) = splitAt oo oc @@ -1523,7 +1523,7 @@ printPrompt drw = do (preCursor, cursor, postCursor) = if offset >= length com then (str, " ","") -- add a space: it will be our cursor ;-) else let (a, b) = splitAt offset com - in (prt ++ a, [head b], tail b) + in (prt ++ a, take 1 b, drop 1 b) -- vertical and horizontal text alignment (asc, desc) <- io $ textExtentsXMF fontS str -- font ascent and descent @@ -1780,7 +1780,7 @@ breakAtSpace s | " \\" `isPrefixOf` s2 = (s1 ++ " " ++ s1', s2') | otherwise = (s1, s2) where (s1, s2 ) = break isSpace s - (s1',s2') = breakAtSpace $ tail s2 + (s1',s2') = breakAtSpace $ drop 1 s2 -- | 'historyCompletion' provides a canned completion function much like -- 'getShellCompl'; you pass it to mkXPrompt, and it will make completions work diff --git a/XMonad/Util/DebugWindow.hs b/XMonad/Util/DebugWindow.hs index b0b72b8e..7b5fdfc5 100644 --- a/XMonad/Util/DebugWindow.hs +++ b/XMonad/Util/DebugWindow.hs @@ -57,9 +57,7 @@ debugWindow w = do \s -> if null s then Nothing else let (w'',s'') = break (== '\NUL') s - s' = if null s'' - then s'' - else tail s'' + s' = drop 1 s'' in Just (w'',s') t <- catchX' (wrap <$> getEWMHTitle "VISIBLE" w) $ catchX' (wrap <$> getEWMHTitle "" w) $ @@ -202,7 +200,7 @@ windowType d w ts = do Just s'' -> s'' _ -> '<':show a ++ ">" unAtoms as (t ++ (if i then ' ':s else s)) True - + simplify :: String -> Atom -> X String simplify pfx a = do s' <- io $ getAtomName d a @@ -214,10 +212,10 @@ windowType d w ts = do return s -- note that above it says this checks all of them before simplifying. - -- I'll do that after I'm confident this works as intended. + -- I'll do that after I'm confident this works as intended. windowState :: [Atom] -> X String windowState [] = return "" windowState as' = go as' ";" where go [] t = return t - go (a:as) t = simplify "_NET_WM_STATE_" a >>= \t' -> go as (t ++ ' ':t') + go (a:as) t = simplify "_NET_WM_STATE_" a >>= \t' -> go as (t ++ ' ':t') diff --git a/XMonad/Util/EZConfig.hs b/XMonad/Util/EZConfig.hs index d69a92ab..7a852bff 100644 --- a/XMonad/Util/EZConfig.hs +++ b/XMonad/Util/EZConfig.hs @@ -439,7 +439,7 @@ mkSubmaps' subm binds = map combine gathered $ binds combine [([k],act)] = (k,act) combine ks = (head . fst . head $ ks, - subm . mkSubmaps' subm $ map (first tail) ks) + subm . mkSubmaps' subm $ map (first (drop 1)) ks) fstKey = (==) `on` (head . fst) -- | Given a configuration record and a list of (key sequence diff --git a/XMonad/Util/Stack.hs b/XMonad/Util/Stack.hs index 0ef69a93..27f3d25e 100644 --- a/XMonad/Util/Stack.hs +++ b/XMonad/Util/Stack.hs @@ -162,20 +162,20 @@ focusUpZ :: Zipper a -> Zipper a focusUpZ Nothing = Nothing focusUpZ (Just s) | u:up <- W.up s = Just $ W.Stack u up (W.focus s:W.down s) focusUpZ (Just s) | null $ W.down s = Just s -focusUpZ (Just (W.Stack f _ down)) = Just $ W.Stack (last down) (tail (reverse down) ++ [f]) [] +focusUpZ (Just (W.Stack f _ down)) = Just $ W.Stack (last down) (drop 1 (reverse down) ++ [f]) [] -- | Move the focus to the next element focusDownZ :: Zipper a -> Zipper a focusDownZ Nothing = Nothing focusDownZ (Just s) | d:down <- W.down s = Just $ W.Stack d (W.focus s:W.up s) down focusDownZ (Just s) | null $ W.up s = Just s -focusDownZ (Just (W.Stack f up _)) = Just $ W.Stack (last up) [] (tail (reverse up) ++ [f]) +focusDownZ (Just (W.Stack f up _)) = Just $ W.Stack (last up) [] (drop 1 (reverse up) ++ [f]) -- | Move the focus to the first element focusMasterZ :: Zipper a -> Zipper a focusMasterZ Nothing = Nothing focusMasterZ (Just (W.Stack f up down)) | not $ null up - = Just $ W.Stack (last up) [] (tail (reverse up) ++ [f] ++ down) + = Just $ W.Stack (last up) [] (drop 1 (reverse up) ++ [f] ++ down) focusMasterZ (Just s) = Just s -- | Refocus a @Stack a@ on an element satisfying the predicate, or fail to diff --git a/tests/Selective.hs b/tests/Selective.hs index c9df5ddf..1842f7dc 100644 --- a/tests/Selective.hs +++ b/tests/Selective.hs @@ -34,14 +34,14 @@ prop_select_focus sel (stk :: Stack Int) = focus stk == focus (select sel' stk) prop_select_increasing :: Selection l -> Stack Int -> Bool prop_select_increasing sel (stk :: Stack Int) = let res = integrate $ select sel stk - in and . zipWith (<) res $ tail res + in and . zipWith (<) res $ drop 1 res -- selection has the form [0..l] ++ [m..n] -- relies on the Arbitrary instance for Stack Int generating stacks like [0..k] prop_select_two_consec :: Selection l -> Stack Int -> Bool prop_select_two_consec sel (stk :: Stack Int) = let wins = integrate $ select sel stk - in (length . filter not . zipWith ((==) . (+1)) wins $ tail wins) <= 1 + in (length . filter not . zipWith ((==) . (+1)) wins $ drop 1 wins) <= 1 -- update preserves invariants on selections prop_update_nm :: Selection l -> Stack Int -> Bool