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

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