Copyright | (c) Spencer Janssen 2007 |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | dons@cse.unsw.edu.au |
Stability | unstable |
Portability | not portable, mtl, posix |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Operations. A module for functions that don't cleanly fit anywhere else.
Synopsis
- manage :: Window -> X ()
- unmanage :: Window -> X ()
- killWindow :: Window -> X ()
- kill :: X ()
- isClient :: Window -> X Bool
- setInitialProperties :: Window -> X ()
- setWMState :: Window -> Int -> X ()
- setWindowBorderWithFallback :: Display -> Window -> String -> Pixel -> X ()
- hide :: Window -> X ()
- reveal :: Window -> X ()
- tileWindow :: Window -> Rectangle -> X ()
- setTopFocus :: X ()
- focus :: Window -> X ()
- isFixedSizeOrTransient :: Display -> Window -> X Bool
- windows :: (WindowSet -> WindowSet) -> X ()
- refresh :: X ()
- rescreen :: X ()
- modifyWindowSet :: (WindowSet -> WindowSet) -> X ()
- windowBracket :: (a -> Bool) -> X a -> X a
- windowBracket_ :: X Any -> X ()
- clearEvents :: EventMask -> X ()
- getCleanedScreenInfo :: MonadIO m => Display -> m [Rectangle]
- withFocused :: (Window -> X ()) -> X ()
- withUnfocused :: (Window -> X ()) -> X ()
- cleanMask :: KeyMask -> X KeyMask
- extraModifiers :: X [KeyMask]
- mouseDrag :: (Position -> Position -> X ()) -> X () -> X ()
- mouseMoveWindow :: Window -> X ()
- mouseResizeWindow :: Window -> X ()
- setButtonGrab :: Bool -> Window -> X ()
- setFocusX :: Window -> X ()
- cacheNumlockMask :: X ()
- mkGrabs :: [(KeyMask, KeySym)] -> X [(KeyMask, KeyCode)]
- unGrab :: X ()
- sendMessage :: Message a => a -> X ()
- broadcastMessage :: Message a => a -> X ()
- sendMessageWithNoRefresh :: Message a => a -> WindowSpace -> X ()
- sendRestart :: IO ()
- sendReplace :: IO ()
- data StateFile = StateFile {
- sfWins :: StackSet WorkspaceId String Window ScreenId ScreenDetail
- sfExt :: [(String, String)]
- writeStateToFile :: X ()
- readStateFile :: (LayoutClass l Window, Read (l Window)) => XConfig l -> X (Maybe XState)
- restart :: String -> Bool -> X ()
- float :: Window -> X ()
- floatLocation :: Window -> X (ScreenId, RationalRect)
- type D = (Dimension, Dimension)
- mkAdjust :: Window -> X (D -> D)
- applySizeHints :: Integral a => Dimension -> SizeHints -> (a, a) -> D
- applySizeHints' :: SizeHints -> D -> D
- applySizeHintsContents :: Integral a => SizeHints -> (a, a) -> D
- applyAspectHint :: (D, D) -> D -> D
- applyResizeIncHint :: D -> D -> D
- applyMaxSizeHint :: D -> D -> D
- containedIn :: Rectangle -> Rectangle -> Bool
- nubScreens :: [Rectangle] -> [Rectangle]
- pointWithin :: Position -> Position -> Rectangle -> Bool
- scaleRationalRect :: Rectangle -> RationalRect -> Rectangle
- initColor :: Display -> String -> IO (Maybe Pixel)
- pointScreen :: Position -> Position -> X (Maybe (Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail))
- screenWorkspace :: ScreenId -> X (Maybe WorkspaceId)
- setLayout :: Layout Window -> X ()
- updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X ()
Manage One Window
manage :: Window -> X () Source #
Add a new window to be managed in the current workspace. Bring it into focus.
Whether the window is already managed, or not, it is mapped, has its border set, and its event mask set.
unmanage :: Window -> X () Source #
A window no longer exists; remove it from the window list, on whatever workspace it is.
killWindow :: Window -> X () Source #
Kill the specified window. If we do kill it, we'll get a delete notify back from X.
There are two ways to delete a window. Either just kill it, or if it supports the delete protocol, send a delete event (e.g. firefox)
setInitialProperties :: Window -> X () Source #
Set some properties when we initially gain control of a window.
setWindowBorderWithFallback :: Display -> Window -> String -> Pixel -> X () Source #
Set the border color using the window's color map, if possible;
otherwise fall back to the color in Pixel
.
reveal :: Window -> X () Source #
Show a window by mapping it and setting Normal. This is harmless if the window was already visible.
tileWindow :: Window -> Rectangle -> X () Source #
Move and resize w
such that it fits inside the given rectangle,
including its border.
setTopFocus :: X () Source #
Set the focus to the window on top of the stack, or root
focus :: Window -> X () Source #
Set focus explicitly to window w
if it is managed by us, or root.
This happens if X notices we've moved the mouse (and perhaps moved
the mouse to a new screen).
isFixedSizeOrTransient :: Display -> Window -> X Bool Source #
Detect whether a window has fixed size or is transient. This check can be used to determine whether the window should be floating or not
Manage Windows
windows :: (WindowSet -> WindowSet) -> X () Source #
Modify the current window list with a pure function, and refresh
Render the currently visible workspaces, as determined by
the StackSet
. Also, set focus to the focused window.
This is our view
operation (MVC), in that it pretty prints our model
with X calls.
The screen configuration may have changed (due to -- xrandr), update the state and refresh the screen, and reset the gap.
modifyWindowSet :: (WindowSet -> WindowSet) -> X () Source #
Modify the WindowSet
in state with no special handling.
windowBracket :: (a -> Bool) -> X a -> X a Source #
Perform an X
action and check its return value against a predicate p.
If p holds, unwind changes to the WindowSet
and replay them using windows
.
windowBracket_ :: X Any -> X () Source #
Perform an X
action. If it returns Any True
, unwind the
changes to the WindowSet
and replay them using windows
. This is
a version of windowBracket
that discards the return value and
handles an X
action that reports its need for refresh via Any
.
clearEvents :: EventMask -> X () Source #
Remove all events of a given type from the event queue.
getCleanedScreenInfo :: MonadIO m => Display -> m [Rectangle] Source #
Clean the list of screens according to the rules documented for nubScreens.
withFocused :: (Window -> X ()) -> X () Source #
Apply an X
operation to the currently focused window, if there is one.
withUnfocused :: (Window -> X ()) -> X () Source #
Apply an X
operation to all unfocused windows on the current workspace, if there are any.
Keyboard and Mouse
extraModifiers :: X [KeyMask] Source #
Combinations of extra modifier masks we need to grab keys/buttons for. (numlock and capslock)
mouseMoveWindow :: Window -> X () Source #
Drag the window under the cursor with the mouse while it is dragged.
mouseResizeWindow :: Window -> X () Source #
Resize the window under the cursor with the mouse while it is dragged.
setButtonGrab :: Bool -> Window -> X () Source #
Tell whether or not to intercept clicks on a given window
cacheNumlockMask :: X () Source #
Release XMonad's keyboard grab, so other grabbers can do their thing.
Start a keyboard action with this if it is going to run something that needs to do a keyboard, pointer, or server grab. For example,
, ((modm .|. controlMask, xK_p), unGrab >> spawn "scrot")
(Other examples are certain screen lockers and "gksu".) This avoids needing to insert a pause/sleep before running the command.
XMonad retains the keyboard grab during key actions because if they use a submap, they need the keyboard to be grabbed, and if they had to assert their own grab then the asynchronous nature of X11 allows race conditions between XMonad, other clients, and the X server that would cause keys to sometimes be "leaked" to the focused window.
Messages
sendMessage :: Message a => a -> X () Source #
Throw a message to the current LayoutClass
possibly modifying how we
layout the windows, in which case changes are handled through a refresh.
broadcastMessage :: Message a => a -> X () Source #
Send a message to all layouts, without refreshing.
sendMessageWithNoRefresh :: Message a => a -> WindowSpace -> X () Source #
Send a message to a layout, without refreshing.
sendRestart :: IO () Source #
Signal xmonad to restart itself.
sendReplace :: IO () Source #
Signal compliant window managers to exit.
Save and Restore State
A type to help serialize xmonad's state to a file.
StateFile | |
|
writeStateToFile :: X () Source #
Write the current window state (and extensible state) to a file so that xmonad can resume with that state intact.
readStateFile :: (LayoutClass l Window, Read (l Window)) => XConfig l -> X (Maybe XState) Source #
Read the state of a previous xmonad instance from a file and return that state. The state file is removed after reading it.
Floating Layer
floatLocation :: Window -> X (ScreenId, RationalRect) Source #
Given a window, find the screen it is located on, and compute the geometry of that window WRT that screen.
Window Size Hints
mkAdjust :: Window -> X (D -> D) Source #
Given a window, build an adjuster function that will reduce the given dimensions according to the window's border width and size hints.
applySizeHints :: Integral a => Dimension -> SizeHints -> (a, a) -> D Source #
Reduce the dimensions if needed to comply to the given SizeHints, taking window borders into account.
applySizeHintsContents :: Integral a => SizeHints -> (a, a) -> D Source #
Reduce the dimensions if needed to comply to the given SizeHints.
applyAspectHint :: (D, D) -> D -> D Source #
Reduce the dimensions so their aspect ratio falls between the two given aspect ratios.
applyResizeIncHint :: D -> D -> D Source #
Reduce the dimensions so they are a multiple of the size increments.
applyMaxSizeHint :: D -> D -> D Source #
Reduce the dimensions if they exceed the given maximum dimensions.
Rectangles
containedIn :: Rectangle -> Rectangle -> Bool Source #
Returns True
if the first rectangle is contained within, but not equal
to the second.
nubScreens :: [Rectangle] -> [Rectangle] Source #
Given a list of screens, remove all duplicated screens and screens that are entirely contained within another.
pointWithin :: Position -> Position -> Rectangle -> Bool Source #
pointWithin x y r
returns True
if the (x, y)
co-ordinate is within
r
.
scaleRationalRect :: Rectangle -> RationalRect -> Rectangle Source #
Produce the actual rectangle from a screen and a ratio on that screen.
Other Utilities
pointScreen :: Position -> Position -> X (Maybe (Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail)) Source #
Given a point, determine the screen (if any) that contains it.
screenWorkspace :: ScreenId -> X (Maybe WorkspaceId) Source #
Return workspace visible on screen sc
, or Nothing
.
updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X () Source #
Update the layout field of a workspace.