X.Prelude: Add findM

Several definitions of this were scattered over a few modules, so just
re-export it from our prelude.
This commit is contained in:
Tony Zorman 2022-10-31 19:26:06 +01:00
parent d301affabb
commit 48a6d34f55
3 changed files with 18 additions and 11 deletions

View File

@ -134,11 +134,6 @@ focusTagged' :: (WindowSet -> [Window]) -> String -> X ()
focusTagged' wl t = gets windowset >>= findM (hasTag t) . wl >>= focusTagged' wl t = gets windowset >>= findM (hasTag t) . wl >>=
maybe (return ()) (windows . focusWindow) maybe (return ()) (windows . focusWindow)
findM :: (Monad m) => (a -> m Bool) -> [a] -> m (Maybe a)
findM _ [] = return Nothing
findM p (x:xs) = do b <- p x
if b then return (Just x) else findM p xs
-- | apply a pure function to windows with a tag -- | apply a pure function to windows with a tag
withTaggedP, withTaggedGlobalP :: String -> (Window -> WindowSet -> WindowSet) -> X () withTaggedP, withTaggedGlobalP :: String -> (Window -> WindowSet -> WindowSet) -> X ()
withTaggedP t f = withTagged' t (winMap f) withTaggedP t f = withTagged' t (winMap f)

View File

@ -30,10 +30,11 @@ module XMonad.Layout.IM (
) where ) where
import XMonad import XMonad
import qualified XMonad.StackSet as S
import XMonad.Layout.Grid import XMonad.Layout.Grid
import XMonad.Layout.LayoutModifier import XMonad.Layout.LayoutModifier
import XMonad.Prelude
import XMonad.Util.WindowProperties import XMonad.Util.WindowProperties
import qualified XMonad.StackSet as S
import Control.Arrow (first) import Control.Arrow (first)
@ -110,11 +111,6 @@ applyIM ratio prop wksp rect = do
return (first ((w, masterRect) :) wrs) return (first ((w, masterRect) :) wrs)
Nothing -> runLayout wksp rect Nothing -> runLayout wksp rect
-- | Like find, but works with monadic computation instead of pure function.
findM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a)
findM _ [] = return Nothing
findM f (x:xs) = do { b <- f x; if b then return (Just x) else findM f xs }
-- | This is for compatibility with old configs only and will be removed in future versions! -- | This is for compatibility with old configs only and will be removed in future versions!
data IM a = IM Rational Property deriving (Read, Show) data IM a = IM Rational Property deriving (Read, Show)
instance LayoutClass IM Window where instance LayoutClass IM Window where

View File

@ -24,6 +24,7 @@ module XMonad.Prelude (
notEmpty, notEmpty,
safeGetWindowAttributes, safeGetWindowAttributes,
mkAbsolutePath, mkAbsolutePath,
findM,
-- * Keys -- * Keys
keyToString, keyToString,
@ -89,6 +90,21 @@ chunksOf i xs = chunk : chunksOf i rest
(.:) :: (a -> b) -> (c -> d -> a) -> c -> d -> b (.:) :: (a -> b) -> (c -> d -> a) -> c -> d -> b
(.:) = (.) . (.) (.:) = (.) . (.)
-- | Like 'find', but takes a monadic function instead; retains the
-- short-circuiting behaviour of the non-monadic version.
--
-- For example,
--
-- > findM (\a -> putStr (show a <> " ") >> pure False) [1..10]
--
-- would print "1 2 3 4 5 6 7 8 9 10" and return @Nothing@, while
--
-- > findM (\a -> putStr (show a <> " ") >> pure True) [1..10]
--
-- would print @"1"@ and return @Just 1@.
findM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a)
findM p = foldr (\x -> ifM (p x) (pure $ Just x)) (pure Nothing)
-- | 'Data.List.NonEmpty.fromList' with a better error message. Useful to -- | 'Data.List.NonEmpty.fromList' with a better error message. Useful to
-- silence GHC's Pattern match(es) are non-exhaustive warning in places where -- silence GHC's Pattern match(es) are non-exhaustive warning in places where
-- the programmer knows it's always non-empty, but it's infeasible to express -- the programmer knows it's always non-empty, but it's infeasible to express