Reduce head usage

This commit is contained in:
Tony Zorman 2023-10-15 12:29:56 +02:00
parent 7680ebb93b
commit 46a26487ba
10 changed files with 28 additions and 25 deletions

View File

@ -39,8 +39,9 @@ cycleToNext lst a = do
-- | If the current layout is in the list, cycle to the next layout. Otherwise,
-- apply the first layout from list.
cycleThroughLayouts :: [String] -> X ()
cycleThroughLayouts lst = do
cycleThroughLayouts [] = pure ()
cycleThroughLayouts lst@(x: _) = do
winset <- gets windowset
let ld = description . S.layout . S.workspace . S.current $ winset
let newld = fromMaybe (head lst) (cycleToNext lst ld)
let newld = fromMaybe x (cycleToNext lst ld)
sendMessage $ JumpToLayout newld

View File

@ -27,7 +27,7 @@ module XMonad.Actions.OnScreen (
) where
import XMonad
import XMonad.Prelude (fromMaybe, guard)
import XMonad.Prelude (fromMaybe, guard, empty)
import XMonad.StackSet hiding (new)
@ -140,10 +140,9 @@ toggleOrView' f i st = fromMaybe (f i st) $ do
let st' = hidden st
-- make sure we actually have to do something
guard $ i == (tag . workspace $ current st)
guard $ not (null st')
-- finally, toggle!
return $ f (tag . head $ st') st
case st' of
[] -> empty
(h : _) -> return $ f (tag h) st -- finally, toggle!
-- $usage
--

View File

@ -22,11 +22,12 @@ module XMonad.Hooks.CurrentWorkspaceOnTop (
currentWorkspaceOnTop
) where
import qualified Data.List.NonEmpty as NE (nonEmpty)
import qualified Data.Map as M
import XMonad
import XMonad.Prelude (NonEmpty ((:|)), when)
import qualified XMonad.StackSet as S
import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Prelude (unless, when)
import qualified Data.Map as M
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@ -63,7 +64,9 @@ currentWorkspaceOnTop = withDisplay $ \d -> do
wins = fltWins ++ map fst rs -- order: first all floating windows, then the order the layout returned
-- end of reimplementation
unless (null wins) $ do
io $ raiseWindow d (head wins) -- raise first window of current workspace to the very top,
io $ restackWindows d wins -- then use restackWindows to let all other windows from the workspace follow
case NE.nonEmpty wins of
Nothing -> pure ()
Just (w :| ws') -> do
io $ raiseWindow d w -- raise first window of current workspace to the very top,
io $ restackWindows d (w : ws') -- then use restackWindows to let all other windows from the workspace follow
XS.put(CWOTS curTag)

View File

@ -82,5 +82,7 @@ insertDown :: (Eq a) => a -> W.StackSet i l a s sd -> W.StackSet i l a s sd
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) (drop 1 $ reverse ws) []
focusLast' st =
case reverse (W.integrate st) of
[] -> st
(l : ws) -> W.Stack l ws []

View File

@ -401,7 +401,7 @@ dzenStrip = strip [] where
strip keep x
| null x = keep
| "^^" `isPrefixOf` x = strip (keep ++ "^") (drop 2 x)
| '^' == head x = strip keep (drop 1 . dropWhile (/= ')') $ x)
| "^" `isPrefixOf` x = strip keep (drop 1 . dropWhile (/= ')') $ x)
| otherwise = let (good,x') = span (/= '^') x
in strip (keep ++ good) x'

View File

@ -140,7 +140,7 @@ getPicPath conf (WallpaperDir dir) = do
direxists <- doesDirectoryExist $ wallpaperBaseDir conf </> dir
if direxists
then do files <- getDirectoryContents $ wallpaperBaseDir conf </> dir
let files' = filter ((/='.').head) files
let files' = filter (not . ("." `isPrefixOf`)) files
file <- pickFrom files'
return $ Just $ wallpaperBaseDir conf </> dir </> file
else return Nothing

View File

@ -34,7 +34,7 @@ import Control.DeepSeq
import Prelude
import XMonad
import XMonad.StackSet hiding (delete, filter, new)
import XMonad.Prelude (delete, find, foldl', groupBy, nub, sortBy)
import XMonad.Prelude (delete, find, foldl', groupBy, nub, sortBy, listToMaybe)
import qualified XMonad.Util.ExtensibleState as XS
-- $usage
@ -90,7 +90,7 @@ workspaceHistoryWithScreen = XS.gets history
workspaceHistoryByScreen :: X [(ScreenId, [WorkspaceId])]
workspaceHistoryByScreen =
map (\wss -> (fst $ head wss, map snd wss)) .
map (\wss -> (maybe 0 fst (listToMaybe wss), map snd wss)) .
groupBy (\a b -> fst a == fst b) .
sortBy (\a b -> compare (fst a) $ fst b)<$>
workspaceHistoryWithScreen

View File

@ -80,11 +80,9 @@ applyPosition :: (LayoutClass l a, Eq a) =>
applyPosition pos wksp rect = do
let stack = W.stack wksp
let ws = W.integrate' stack
if null ws then
runLayout wksp rect
else do
let firstW = head ws
let other = drop 1 ws
case ws of
[] -> runLayout wksp rect
(firstW : other) -> do
let filtStack = stack >>= W.filter (firstW /=)
wrs <- runLayout (wksp {W.stack = filtStack}) rect
return $ first ((firstW, place pos other rect) :) wrs

View File

@ -91,7 +91,7 @@ instance (LayoutClass l (), LayoutClass l1 a, LayoutClass l2 a, Read a, Show a,
handleMessage super (SomeMessage ReleaseResources)
return ([(w,rinput)], Just $ C2 [w] [w] super' l1' l2')
arrange origws =
do let w2' = case origws `intersect` w2 of [] -> [head origws]
do let w2' = case origws `intersect` w2 of [] -> take 1 origws
[x] -> [x]
x -> case origws \\ x of
[] -> init x

View File

@ -197,7 +197,7 @@ getCommands = do
p <- getEnv "PATH" `E.catch` econst []
let ds = filter (/= "") $ split ':' p
es <- forM ds $ \d -> getDirectoryContents d `E.catch` econst []
return . uniqSort . filter ((/= '.') . head) . concat $ es
return . uniqSort . filter (not . ("." `isPrefixOf`)) . concat $ es
split :: Eq a => a -> [a] -> [[a]]
split _ [] = []