xmonad-contrib-0.17.1.9: Community-maintained extensions for xmonad
Copyright(c) Lukas Mai
LicenseBSD
MaintainerLukas Mai <l.mai@web.de>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Hooks.ManageHelpers

Description

This module provides helper functions to be used in manageHook. Here's how you might use this:

import XMonad.Hooks.ManageHelpers
main =
    xmonad def{
        ...
        manageHook = composeOne [
            isKDETrayWindow -?> doIgnore,
            transience,
            isFullscreen -?> doFullFloat,
            resource =? "stalonetray" -?> doIgnore
        ],
        ...
    }

Here's how you can define more helpers like the ones from this module:

-- some function you want to transform into an infix operator
f :: a -> b -> Bool

-- a new helper
q ***? x = fmap (\a -> f a x) q   -- or: (\b -> f x b)
-- or
q ***? x = fmap (`f` x) q         -- or: (x `f`)

Any existing operator can be "lifted" in the same way:

q ++? x = fmap (++ x) q
Synopsis

Documentation

data Side Source #

Denotes a side of a screen. S stands for South, NE for Northeast etc. C stands for Center.

Constructors

SC 
NC 
CE 
CW 
SE 
SW 
NE 
NW 
C 

Instances

Instances details
Read Side Source # 
Instance details

Defined in XMonad.Hooks.ManageHelpers

Show Side Source # 
Instance details

Defined in XMonad.Hooks.ManageHelpers

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

Eq Side Source # 
Instance details

Defined in XMonad.Hooks.ManageHelpers

Methods

(==) :: Side -> Side -> Bool #

(/=) :: Side -> Side -> Bool #

composeOne :: (Monoid a, Monad m) => [m (Maybe a)] -> m a Source #

An alternative ManageHook composer. Unlike composeAll it stops as soon as a candidate returns a Just value, effectively running only the first match (whereas composeAll continues and executes all matching rules).

(-?>) :: (Functor m, Monad m) => m Bool -> m a -> m (Maybe a) infixr 0 Source #

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 go on and try the next rule.

(/=?) :: (Eq a, Functor m) => m a -> a -> m Bool Source #

q /=? x. if the result of q equals x, return False

(^?) :: (Eq a, Functor m) => m [a] -> [a] -> m Bool Source #

q ^? x. if the result of x isPrefixOf q, return True

(~?) :: (Eq a, Functor m) => m [a] -> [a] -> m Bool Source #

q ~? x. if the result of x isInfixOf q, return True

($?) :: (Eq a, Functor m) => m [a] -> [a] -> m Bool Source #

q $? x. if the result of x isSuffixOf q, return True

(<==?) :: (Eq a, Functor m) => m a -> a -> m (Match a) Source #

q <==? x. if the result of q equals x, return True grouped with q

(</=?) :: (Eq a, Functor m) => m a -> a -> m (Match a) Source #

q </=? x. if the result of q notequals x, return True grouped with q

(-->>) :: (Monoid b, Monad m) => m (Match a) -> (a -> m b) -> m b infixr 0 Source #

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.

(-?>>) :: (Functor m, Monad m) => m (Match a) -> (a -> m b) -> m (Maybe b) infixr 0 Source #

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.

currentWs :: Query WorkspaceId Source #

Return the current workspace

windowTag :: Query (Maybe WorkspaceId) Source #

Return the workspace tag of a window, if already managed

isInProperty :: String -> String -> Query Bool Source #

Helper to check if a window property contains certain value.

isKDETrayWindow :: Query Bool Source #

A predicate to check whether a window is a KDE system tray icon.

isFullscreen :: Query Bool Source #

A predicate to check whether a window wants to fill the whole screen. See also doFullFloat.

isMinimized :: Query Bool Source #

A predicate to check whether a window is hidden (minimized). See also XMonad.Actions.Minimize.

isDialog :: Query Bool Source #

A predicate to check whether a window is a dialog.

pid :: Query (Maybe ProcessID) Source #

This function returns Just the _NET_WM_PID property for a particular window if set, Nothing otherwise.

See https://specifications.freedesktop.org/wm-spec/wm-spec-1.5.html#idm45623487788432.

desktop :: Query (Maybe Int) Source #

This function returns Just the _NET_WM_DESKTOP property for a particular window if set, Nothing otherwise.

See https://specifications.freedesktop.org/wm-spec/wm-spec-1.5.html#idm46181547492704.

transientTo :: Query (Maybe Window) Source #

A predicate to check whether a window is Transient. It holds the result which might be the window it is transient to or it might be Nothing.

maybeToDefinite :: (Monoid a, Functor m) => m (Maybe a) -> m a Source #

type MaybeManageHook = Query (Maybe (Endo WindowSet)) Source #

A ManageHook that may or may not have been executed; the outcome is embedded in the Maybe

transience :: MaybeManageHook Source #

A convenience MaybeManageHook that will check to see if a window is transient, and then move it to its parent.

clientLeader :: Query (Maybe Window) Source #

This function returns Just the WM_CLIENT_LEADER property for a particular window if set, Nothing otherwise. Note that, generally, the window ID returned from this property (by firefox, for example) corresponds to an unmapped or unmanaged dummy window. For this to be useful in most cases, it should be used together with sameBy.

See https://tronche.com/gui/x/icccm/sec-5.html.

sameBy :: Eq prop => Query (Maybe prop) -> Query [Window] Source #

For a given window, sameBy returns all windows that have a matching property (e.g. those obtained from Queries of clientLeader and pid).

shiftToSame :: Eq prop => Query (Maybe prop) -> MaybeManageHook Source #

MaybeManageHook that moves the window to the same workspace as the first other window that has the same value of a given Query. Useful Queries for this include clientLeader and pid.

doRectFloat Source #

Arguments

:: RationalRect

The rectangle to float the window in. 0 to 1; x, y, w, h.

-> ManageHook 

Floats the new window in the given rectangle.

doFullFloat :: ManageHook Source #

Floats the window and makes it use the whole screen. Equivalent to doRectFloat $ RationalRect 0 0 1 1.

doCenterFloat :: ManageHook Source #

Floats a new window with its original size, but centered.

doSideFloat :: Side -> ManageHook Source #

Floats a new window with its original size on the specified side of a screen

doFloatAt :: Rational -> Rational -> ManageHook Source #

Floats a new window with its original size, and its top left corner at a specific point on the screen (both coordinates should be in the range 0 to 1).

doFloatDep :: (RationalRect -> RationalRect) -> ManageHook Source #

Floats a new window using a rectangle computed as a function of the rectangle that it would have used by default.

doHideIgnore :: ManageHook Source #

Hides window and ignores it.

doSink :: ManageHook Source #

Sinks a window

doLower :: ManageHook Source #

Lower an unmanaged window. Useful together with doIgnore to lower special windows that for some reason don't do it themselves.

doRaise :: ManageHook Source #

Raise an unmanaged window. Useful together with doIgnore to raise special windows that for some reason don't do it themselves.

doFocus :: ManageHook Source #

Focus a window (useful in setActivateHook).

data Match a Source #

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