Replace tail with drop 1

Where appropriate.
This commit is contained in:
Tony Zorman
2023-09-19 09:10:11 +02:00
parent c8c81474a2
commit 52a40f376c
20 changed files with 33 additions and 38 deletions

View File

@@ -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 = [] })

View File

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

View File

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

View File

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

View File

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

View File

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

View File

@@ -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 \<tag\>...\</tag\> removed

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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