aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Hooks/ManageHelpers.hs
diff options
context:
space:
mode:
authorLukas Mai <l.mai@web.de>2008-03-26 19:27:07 +0100
committerLukas Mai <l.mai@web.de>2008-03-26 19:27:07 +0100
commit4cc456b6e0b12584b25639d69c4e68536f312233 (patch)
treeb83e32af219bede7ccce020d6995d2407af3af57 /XMonad/Hooks/ManageHelpers.hs
parent22f0e93dbe080786ed97afe10f6886b48d684a9c (diff)
downloadXMonadContrib-4cc456b6e0b12584b25639d69c4e68536f312233.tar.gz
XMonadContrib-4cc456b6e0b12584b25639d69c4e68536f312233.tar.xz
XMonadContrib-4cc456b6e0b12584b25639d69c4e68536f312233.zip
XMonad.Hooks.ManageHelpers: reformatting
darcs-hash:20080326182707-462cf-1f486ea604d17f4da7fbd0393ea9e8f341884053.gz
Diffstat (limited to 'XMonad/Hooks/ManageHelpers.hs')
-rw-r--r--XMonad/Hooks/ManageHelpers.hs44
1 files changed, 23 insertions, 21 deletions
diff --git a/XMonad/Hooks/ManageHelpers.hs b/XMonad/Hooks/ManageHelpers.hs
index 45f7c06..c965c17 100644
--- a/XMonad/Hooks/ManageHelpers.hs
+++ b/XMonad/Hooks/ManageHelpers.hs
@@ -44,9 +44,9 @@ import Data.Monoid
-- | A ManageHook that may or may not have been executed; the outcome is embedded in the Maybe
type MaybeManageHook = Query (Maybe (Endo WindowSet))
--- | A grouping type, which can hold the outcome of a predicate Query
--- This is analogous to group types in regular expressions
--- TODO create a better API for aggregating multiple Matches logically
+-- | A grouping type, which can hold the outcome of a predicate Query.
+-- This is analogous to group types in regular expressions.
+-- TODO: create a better API for aggregating multiple Matches logically
data Match a = Match Bool a
-- | An alternative 'ManageHook' composer. Unlike 'composeAll' it stops as soon as
@@ -70,12 +70,14 @@ q /=? x = fmap (/= x) q
-- | q <==? x. if the result of q equals x, return True grouped with q
(<==?) :: Eq a => Query a -> a -> Query (Match a)
q <==? x = fmap (`eq` x) q
- where eq q' x' = Match (q' == x') q'
+ where
+ eq q' x' = Match (q' == x') q'
-- | q <\/=? x. if the result of q notequals x, return True grouped with q
(</=?) :: Eq a => Query a -> a -> Query (Match a)
q </=? x = fmap (`neq` x) q
- where neq q' x' = Match (q' /= x') q'
+ where
+ neq q' x' = Match (q' /= x') q'
-- | A helper operator for use in 'composeOne'. It takes a condition and an action;
-- if the condition fails, it returns 'Nothing' from the 'Query' so 'composeOne' will
@@ -87,13 +89,15 @@ p -?> f = do
-- | A helper operator for use in 'composeAll'. It takes a condition and a function taking a grouped datum to action. If 'p' is true, it executes the resulting action.
(-->>) :: Query (Match a) -> (a -> ManageHook) -> ManageHook
-p -->> f = do Match b m <- p
- if b then (f m) else mempty
+p -->> f = do
+ Match b m <- p
+ if b then (f m) else mempty
-- | A helper operator for use in 'composeOne'. It takes a condition and a function taking a groupdatum to action. If 'p' is true, it executes the resulting action. If it fails, it returns 'Nothing' from the 'Query' so 'composeOne' will go on and try the next rule.
(-?>>) :: Query (Match a) -> (a -> ManageHook) -> MaybeManageHook
-p -?>> f = do Match b m <- p
- if b then fmap Just (f m) else return Nothing
+p -?>> f = do
+ Match b m <- p
+ if b then fmap Just (f m) else return Nothing
-- | A predicate to check whether a window is a KDE system tray icon.
isKDETrayWindow :: Query Bool
@@ -109,19 +113,18 @@ isKDETrayWindow = ask >>= \w -> liftX $ do
-- It holds the result which might be the window it is transient to
-- or it might be 'Nothing'.
transientTo :: Query (Maybe Window)
-transientTo = do w <- ask
- d <- (liftX . asks) display
- liftIO $ getTransientForHint d w
+transientTo = do
+ w <- ask
+ d <- (liftX . asks) display
+ liftIO $ getTransientForHint d w
-- | A convenience 'MaybeManageHook' that will check to see if a window
-- is transient, and then move it to its parent.
transience :: MaybeManageHook
-transience = transientTo </=? Nothing
- -?>> move
- where move :: Maybe Window -> ManageHook
- move mw = maybe idHook (doF . move') mw
- where move' :: Window -> (WindowSet -> WindowSet)
- move' w = \s -> maybe s (`W.shift` s) (W.findTag w s)
+transience = transientTo </=? Nothing -?>> move
+ where
+ move mw = maybe idHook (doF . move') mw
+ move' w s = maybe s (`W.shift` s) (W.findTag w s)
-- | 'transience' set to a 'ManageHook'
transience' :: ManageHook
@@ -141,6 +144,5 @@ doRectFloat r = ask >>= \w -> doF (W.float w r)
-- | Floats a new window with its original size, but centered.
doCenterFloat :: ManageHook
doCenterFloat = ask >>= \w -> doF . W.float w . center . snd =<< liftX (floatLocation w)
- where center (W.RationalRect _ _ w h)
- = W.RationalRect ((1-w)/2) ((1-h)/2) w h
-
+ where
+ center (W.RationalRect _ _ w h) = W.RationalRect ((1-w)/2) ((1-h)/2) w h