1
0
mirror of https://github.com/xmonad/xmonad.git synced 2025-08-20 14:03:47 -07:00

Export ifM from X.Core

This was added as a local function in
1e17c1c1bc26cdb93e23d4aa75e57fe48ff4c951, but it's actually present in
X.ManageHook already. However, since that module imports X.Core, we
can't use this as-is.
This commit is contained in:
Tony Zorman
2023-10-07 11:43:27 +02:00
parent 67b5510dde
commit 050ba6420d
2 changed files with 8 additions and 11 deletions

@@ -33,7 +33,7 @@ module XMonad.Core (
StateExtension(..), ExtensionClass(..), ConfExtension(..),
runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
getAtom, spawn, spawnPID, xfork, xmessage, recompile, trace, whenJust, whenX,
getAtom, spawn, spawnPID, xfork, xmessage, recompile, trace, whenJust, whenX, ifM,
getXMonadDir, getXMonadCacheDir, getXMonadDataDir, stateFileName, binFileName,
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_TAKE_FOCUS, withWindowAttributes,
ManageHook, Query(..), runQuery, Directories'(..), Directories, getDirectories,
@@ -415,9 +415,13 @@ data StateExtension =
data ConfExtension = forall a. Typeable a => ConfExtension a
-- ---------------------------------------------------------------------
-- | General utilities
--
-- Lift an 'IO' action into the 'X' monad
-- General utilities
-- | If-then-else lifted to a 'Monad'.
ifM :: Monad m => m Bool -> m a -> m a -> m a
ifM mb t f = mb >>= \b -> if b then t else f
-- | Lift an 'IO' action into the 'X' monad
io :: MonadIO m => IO a -> m a
io = liftIO
@@ -709,9 +713,6 @@ compile dirs method =
]
andCopyFromResultDir exitCode = do
if exitCode == ExitSuccess then copyFromResultDir else return exitCode
ifM c i e = do
cond <- c
if cond then i else e
findM p = foldr (\x -> ifM (p x) (pure $ Just x)) (pure Nothing)
catchAny :: IO a -> (SomeException -> IO a) -> IO a
catchAny = E.catch

@@ -64,10 +64,6 @@ x <&&> y = ifM x y (pure False)
(<||>) :: Monad m => m Bool -> m Bool -> m Bool
x <||> y = ifM x (pure True) y
-- | If-then-else lifted to a 'Monad'.
ifM :: Monad m => m Bool -> m a -> m a -> m a
ifM mb t f = mb >>= \b -> if b then t else f
-- | Return the window title.
title :: Query String
title = ask >>= \w -> liftX $ do