| Copyright | (c) José A. Romero L. | 
|---|---|
| License | BSD3-style (see LICENSE) | 
| Maintainer | José A. Romero L. <escherdragon@gmail.com> | 
| Stability | unstable | 
| Portability | unportable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
System.Taffybar.Information.EWMHDesktopInfo
Description
Functions to access data provided by the X11 desktop via EWHM hints. This
 module requires that the EwmhDesktops hook from the XMonadContrib project
 be installed in your ~/.xmonad/xmonad.hs configuration:
import XMonad import XMonad.Hooks.EwmhDesktops (ewmh) main = xmonad $ ewmh $ ...
Synopsis
- data EWMHIcon = EWMHIcon {- ewmhWidth :: Int
- ewmhHeight :: Int
- ewmhPixelsARGB :: Ptr PixelsWordType
 
- type EWMHIconData = (ForeignPtr PixelsWordType, Int)
- newtype WorkspaceIdx = WSIdx Int
- type X11Window = Window
- type X11WindowHandle = ((WorkspaceIdx, String, String), X11Window)
- focusWindow :: X11Window -> X11Property ()
- getActiveWindowTitle :: X11Property String
- getCurrentWorkspace :: X11Property WorkspaceIdx
- getVisibleWorkspaces :: X11Property [WorkspaceIdx]
- getWindowClass :: X11Window -> X11Property String
- getWindowHandles :: X11Property [X11WindowHandle]
- getWindowIconsData :: X11Window -> X11Property (Maybe EWMHIconData)
- getWindowTitle :: X11Window -> X11Property String
- getWindows :: X11Property [X11Window]
- getWorkspace :: X11Window -> X11Property WorkspaceIdx
- getWorkspaceNames :: X11Property [(WorkspaceIdx, String)]
- isWindowUrgent :: X11Window -> X11Property Bool
- parseWindowClasses :: String -> [String]
- switchOneWorkspace :: Bool -> Int -> X11Property ()
- switchToWorkspace :: WorkspaceIdx -> X11Property ()
- withDefaultCtx :: X11Property a -> IO a
- withEWMHIcons :: EWMHIconData -> ([EWMHIcon] -> IO a) -> IO a
Documentation
Constructors
| EWMHIcon | |
| Fields 
 | |
type EWMHIconData = (ForeignPtr PixelsWordType, Int) Source #
newtype WorkspaceIdx Source #
Instances
| Eq WorkspaceIdx Source # | |
| Defined in System.Taffybar.Information.EWMHDesktopInfo | |
| Ord WorkspaceIdx Source # | |
| Defined in System.Taffybar.Information.EWMHDesktopInfo Methods compare :: WorkspaceIdx -> WorkspaceIdx -> Ordering # (<) :: WorkspaceIdx -> WorkspaceIdx -> Bool # (<=) :: WorkspaceIdx -> WorkspaceIdx -> Bool # (>) :: WorkspaceIdx -> WorkspaceIdx -> Bool # (>=) :: WorkspaceIdx -> WorkspaceIdx -> Bool # max :: WorkspaceIdx -> WorkspaceIdx -> WorkspaceIdx # min :: WorkspaceIdx -> WorkspaceIdx -> WorkspaceIdx # | |
| Read WorkspaceIdx Source # | |
| Defined in System.Taffybar.Information.EWMHDesktopInfo Methods readsPrec :: Int -> ReadS WorkspaceIdx # readList :: ReadS [WorkspaceIdx] # | |
| Show WorkspaceIdx Source # | |
| Defined in System.Taffybar.Information.EWMHDesktopInfo Methods showsPrec :: Int -> WorkspaceIdx -> ShowS # show :: WorkspaceIdx -> String # showList :: [WorkspaceIdx] -> ShowS # | |
type X11WindowHandle = ((WorkspaceIdx, String, String), X11Window) Source #
Convenience alias for a pair of the form (props, window), where props is a tuple of the form (workspace index, window title, window class), and window is the internal ID of an open window.
focusWindow :: X11Window -> X11Property () Source #
Ask the window manager to give focus to the given window.
getActiveWindowTitle :: X11Property String Source #
Get the title of the currently focused window.
getCurrentWorkspace :: X11Property WorkspaceIdx Source #
Retrieve the index of the current workspace in the desktop, starting from 0.
getVisibleWorkspaces :: X11Property [WorkspaceIdx] Source #
Retrieve the indexes of all currently visible workspaces with the active workspace at the head of the list.
getWindowClass :: X11Window -> X11Property String Source #
Get the class of the given X11 window.
getWindowHandles :: X11Property [X11WindowHandle] Source #
Return a list of X11 window handles, one for each window open. Refer to the
 documentation of X11WindowHandle for details on the structure returned.
getWindowIconsData :: X11Window -> X11Property (Maybe EWMHIconData) Source #
Get EWMHIconData for the given X11Window
getWindowTitle :: X11Window -> X11Property String Source #
Get the title of the given X11 window.
getWindows :: X11Property [X11Window] Source #
Return a list of all windows
getWorkspace :: X11Window -> X11Property WorkspaceIdx Source #
Return the index (starting from 0) of the workspace on which the given window is being displayed.
getWorkspaceNames :: X11Property [(WorkspaceIdx, String)] Source #
Return a list with the names of all the workspaces currently available.
isWindowUrgent :: X11Window -> X11Property Bool Source #
Determine whether the "urgent" flag is set in the WM_HINTS of the given window.
parseWindowClasses :: String -> [String] Source #
switchOneWorkspace :: Bool -> Int -> X11Property () Source #
Move one workspace up or down from the current workspace
switchToWorkspace :: WorkspaceIdx -> X11Property () Source #
Ask the window manager to switch to the workspace with the given index, starting from 0.
withDefaultCtx :: X11Property a -> IO a Source #
Put the current display and root window objects inside a Reader transformer for further computation.
withEWMHIcons :: EWMHIconData -> ([EWMHIcon] -> IO a) -> IO a Source #
Operate on the data contained in EWMHIconData in the easier to interact
 with format offered by EWMHIcon. This function is much like
 withForeignPtr in that the EWMHIcon values that are provided to the
 callable argument should not be kept around in any way, because it can not be
 guaranteed that the finalizer for the memory to which those icon objects
 point will not be executed, after the call to withEWMHIcons completes.