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 | Safe-Inferred |
Language | Haskell2010 |
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 WorkspaceId = WorkspaceId Int
- type X11Window = Window
- allEWMHProperties :: [EWMHProperty]
- ewmhActiveWindow :: EWMHProperty
- ewmhClientList :: EWMHProperty
- ewmhClientListStacking :: EWMHProperty
- ewmhCurrentDesktop :: EWMHProperty
- ewmhDesktopNames :: EWMHProperty
- ewmhNumberOfDesktops :: EWMHProperty
- ewmhStateHidden :: EWMHProperty
- ewmhWMClass :: EWMHProperty
- ewmhWMDesktop :: EWMHProperty
- ewmhWMIcon :: EWMHProperty
- ewmhWMName :: EWMHProperty
- ewmhWMName2 :: EWMHProperty
- ewmhWMState :: EWMHProperty
- ewmhWMStateHidden :: EWMHProperty
- focusWindow :: X11Window -> X11Property ()
- getActiveWindow :: X11Property (Maybe X11Window)
- getCurrentWorkspace :: X11Property WorkspaceId
- getVisibleWorkspaces :: X11Property [WorkspaceId]
- getWindowClass :: X11Window -> X11Property String
- getWindowIconsData :: X11Window -> X11Property (Maybe EWMHIconData)
- getWindowMinimized :: X11Window -> X11Property Bool
- getWindowState :: X11Window -> [String] -> X11Property [String]
- getWindowStateProperty :: String -> X11Window -> X11Property Bool
- getWindowTitle :: X11Window -> X11Property String
- getWindows :: X11Property [X11Window]
- getWindowsStacking :: X11Property [X11Window]
- getWorkspace :: X11Window -> X11Property WorkspaceId
- getWorkspaceNames :: X11Property [(WorkspaceId, String)]
- isWindowUrgent :: X11Window -> X11Property Bool
- parseWindowClasses :: String -> [String]
- switchOneWorkspace :: Bool -> Int -> X11Property ()
- switchToWorkspace :: WorkspaceId -> X11Property ()
- withDefaultCtx :: X11Property a -> IO a
- withEWMHIcons :: EWMHIconData -> ([EWMHIcon] -> IO a) -> IO a
Documentation
EWMHIcon | |
|
type EWMHIconData = (ForeignPtr PixelsWordType, Int) Source #
newtype WorkspaceId Source #
Instances
Read WorkspaceId Source # | |
Defined in System.Taffybar.Information.EWMHDesktopInfo readsPrec :: Int -> ReadS WorkspaceId # readList :: ReadS [WorkspaceId] # readPrec :: ReadPrec WorkspaceId # readListPrec :: ReadPrec [WorkspaceId] # | |
Show WorkspaceId Source # | |
Defined in System.Taffybar.Information.EWMHDesktopInfo showsPrec :: Int -> WorkspaceId -> ShowS # show :: WorkspaceId -> String # showList :: [WorkspaceId] -> ShowS # | |
Eq WorkspaceId Source # | |
Defined in System.Taffybar.Information.EWMHDesktopInfo (==) :: WorkspaceId -> WorkspaceId -> Bool # (/=) :: WorkspaceId -> WorkspaceId -> Bool # | |
Ord WorkspaceId Source # | |
Defined in System.Taffybar.Information.EWMHDesktopInfo compare :: WorkspaceId -> WorkspaceId -> Ordering # (<) :: WorkspaceId -> WorkspaceId -> Bool # (<=) :: WorkspaceId -> WorkspaceId -> Bool # (>) :: WorkspaceId -> WorkspaceId -> Bool # (>=) :: WorkspaceId -> WorkspaceId -> Bool # max :: WorkspaceId -> WorkspaceId -> WorkspaceId # min :: WorkspaceId -> WorkspaceId -> WorkspaceId # |
allEWMHProperties :: [EWMHProperty] Source #
ewmhActiveWindow :: EWMHProperty Source #
ewmhClientList :: EWMHProperty Source #
ewmhClientListStacking :: EWMHProperty Source #
ewmhCurrentDesktop :: EWMHProperty Source #
ewmhDesktopNames :: EWMHProperty Source #
ewmhNumberOfDesktops :: EWMHProperty Source #
ewmhStateHidden :: EWMHProperty Source #
ewmhWMClass :: EWMHProperty Source #
ewmhWMDesktop :: EWMHProperty Source #
ewmhWMIcon :: EWMHProperty Source #
ewmhWMName :: EWMHProperty Source #
ewmhWMName2 :: EWMHProperty Source #
ewmhWMState :: EWMHProperty Source #
ewmhWMStateHidden :: EWMHProperty Source #
focusWindow :: X11Window -> X11Property () Source #
Ask the window manager to give focus to the given window.
getActiveWindow :: X11Property (Maybe X11Window) Source #
Get the window that currently has focus if such a window exists.
getCurrentWorkspace :: X11Property WorkspaceId Source #
Retrieve the index of the current workspace in the desktop, starting from 0.
getVisibleWorkspaces :: X11Property [WorkspaceId] 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.
getWindowIconsData :: X11Window -> X11Property (Maybe EWMHIconData) Source #
Get EWMHIconData for the given X11Window
getWindowMinimized :: X11Window -> X11Property Bool Source #
Get a bool reflecting whether window with provided X11Window is minimized or not.
getWindowState :: X11Window -> [String] -> X11Property [String] Source #
getWindowStateProperty :: String -> X11Window -> X11Property Bool Source #
getWindowTitle :: X11Window -> X11Property String Source #
Get the title of the given X11 window.
getWindows :: X11Property [X11Window] Source #
Return a list of all X11Window
s, sorted by initial mapping order, oldest to newest.
getWindowsStacking :: X11Property [X11Window] Source #
Return a list of all X11Window
s, sorted in stacking order, bottom-to-top.
getWorkspace :: X11Window -> X11Property WorkspaceId Source #
Return the index (starting from 0) of the workspace on which the given window is being displayed.
getWorkspaceNames :: X11Property [(WorkspaceId, 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 :: WorkspaceId -> 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.