Copyright | (c) 2007 Andrea Rossato 2009 Jan Vornberger 2023 Ilya Portnov |
---|---|
License | BSD-style (see xmonad/LICENSE) |
Maintainer | portnov84@rambler.ru |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module exposes a number of types which are used by other sub-modules of XMonad.Layout.DecorationEx module.
Synopsis
- data WindowDecoration = WindowDecoration {
- wdOrigWindow :: !Window
- wdOrigWinRect :: !Rectangle
- wdDecoWindow :: !(Maybe Window)
- wdDecoRect :: !(Maybe Rectangle)
- wdWidgets :: ![WidgetPlace]
- class (Read cmd, Show cmd) => WindowCommand cmd where
- executeWindowCommand :: cmd -> Window -> X Bool
- isCommandChecked :: cmd -> Window -> X Bool
- class (WindowCommand (WidgetCommand widget), Read widget, Show widget) => DecorationWidget widget where
- type WidgetCommand widget
- widgetCommand :: widget -> Int -> WidgetCommand widget
- isShrinkable :: widget -> Bool
- data WidgetPlace = WidgetPlace {}
- data WidgetLayout a = WidgetLayout {}
- class HasWidgets theme widget where
- themeWidgets :: theme widget -> WidgetLayout widget
- class ClickHandler theme widget where
- onDecorationClick :: theme widget -> Int -> Maybe (WidgetCommand widget)
- isDraggingEnabled :: theme widget -> Int -> Bool
- class (Read theme, Show theme) => ThemeAttributes theme where
- type Style theme
- selectWindowStyle :: theme -> Window -> X (Style theme)
- widgetsPadding :: theme -> BoxBorders Dimension
- defaultBgColor :: theme -> String
- themeFontName :: theme -> String
- type XPaintingContext = (Display, Pixmap, GC)
- data BoxBorders a = BoxBorders {}
- type BorderColors = BoxBorders String
- data ThemeStyleType
- data SimpleStyle = SimpleStyle {}
- data GenericTheme style widget = GenericTheme {
- exActive :: !style
- exInactive :: !style
- exUrgent :: !style
- exPadding :: !(BoxBorders Dimension)
- exFontName :: !String
- exOnDecoClick :: !(Map Int (WidgetCommand widget))
- exDragWindowButtons :: ![Int]
- exWidgetsLeft :: ![widget]
- exWidgetsCenter :: ![widget]
- exWidgetsRight :: ![widget]
- type ThemeEx widget = GenericTheme SimpleStyle widget
- widgetLayout :: WidgetLayout widget -> [widget]
- windowStyleType :: Window -> X ThemeStyleType
- genericWindowStyle :: Window -> GenericTheme style widget -> X style
- themeEx :: Default (WidgetCommand widget) => Theme -> ThemeEx widget
- borderColor :: String -> BorderColors
- shadowBorder :: String -> String -> BorderColors
Common types
data WindowDecoration Source #
Information about decoration of one window
WindowDecoration | |
|
class (Read cmd, Show cmd) => WindowCommand cmd where Source #
Type class for window commands (such as maximize or close window)
executeWindowCommand :: cmd -> Window -> X Bool Source #
Execute the command
isCommandChecked :: cmd -> Window -> X Bool Source #
Is the command currently in checked
state.
For example, for sticky
command, check if the
window is currently sticky.
Instances
WindowCommand StandardCommand Source # | |
Defined in XMonad.Layout.DecorationEx.Widgets executeWindowCommand :: StandardCommand -> Window -> X Bool Source # isCommandChecked :: StandardCommand -> Window -> X Bool Source # |
class (WindowCommand (WidgetCommand widget), Read widget, Show widget) => DecorationWidget widget where Source #
Type class for decoration widgets
type WidgetCommand widget Source #
Type of window commands which this type of widgets can execute
widgetCommand :: widget -> Int -> WidgetCommand widget Source #
Get window command which is associated with this widget.
isShrinkable :: widget -> Bool Source #
Check if the widget is shrinkable, i.e. if it's width can be reduced if there is not enough place in the decoration.
Instances
(Default cmd, Read cmd, Show cmd, WindowCommand cmd) => DecorationWidget (GenericWidget cmd) Source # | |
Defined in XMonad.Layout.DecorationEx.Widgets type WidgetCommand (GenericWidget cmd) Source # widgetCommand :: GenericWidget cmd -> Int -> WidgetCommand (GenericWidget cmd) Source # isShrinkable :: GenericWidget cmd -> Bool Source # |
data WidgetPlace Source #
Data type describing where the decoration widget (e.g. window button) should be placed. All coordinates are relative to decoration rectangle.
WidgetPlace | |
|
Instances
Show WidgetPlace Source # | |
Defined in XMonad.Layout.DecorationEx.Common showsPrec :: Int -> WidgetPlace -> ShowS # show :: WidgetPlace -> String # showList :: [WidgetPlace] -> ShowS # |
class HasWidgets theme widget where Source #
Type class for themes, which claims that the theme contains the list of widgets and their alignments.
themeWidgets :: theme widget -> WidgetLayout widget Source #
Instances
HasWidgets (GenericTheme style) widget Source # | |
Defined in XMonad.Layout.DecorationEx.Common themeWidgets :: GenericTheme style widget -> WidgetLayout widget Source # |
class ClickHandler theme widget where Source #
Type class for themes, which claims that the theme can describe how the decoration should respond to clicks on decoration itself (between widgets).
:: theme widget | |
-> Int | Mouse button number |
-> Maybe (WidgetCommand widget) |
This is called when the user clicks on the decoration rectangle (not on one of widgets).
Determine if it is possible to drag window by it's decoration with mouse button.
Instances
ClickHandler (GenericTheme SimpleStyle) widget Source # | |
Defined in XMonad.Layout.DecorationEx.Common onDecorationClick :: GenericTheme SimpleStyle widget -> Int -> Maybe (WidgetCommand widget) Source # isDraggingEnabled :: GenericTheme SimpleStyle widget -> Int -> Bool Source # |
class (Read theme, Show theme) => ThemeAttributes theme where Source #
Type class for themes, which claims that the theme is responsible for determining looks of decoration.
Type which describes looks of decoration in one of window states (active, inactive, urgent, etc).
selectWindowStyle :: theme -> Window -> X (Style theme) Source #
Select style based on window state.
widgetsPadding :: theme -> BoxBorders Dimension Source #
Define padding between decoration rectangle and widgets.
defaultBgColor :: theme -> String Source #
Initial background color of decoration rectangle. When decoration widget is created, it is initially filled with this color.
themeFontName :: theme -> String Source #
Font name defined in the theme.
Instances
(Show widget, Read widget, Read (WidgetCommand widget), Show (WidgetCommand widget)) => ThemeAttributes (ThemeEx widget) Source # | |
Defined in XMonad.Layout.DecorationEx.Common selectWindowStyle :: ThemeEx widget -> Window -> X (Style (ThemeEx widget)) Source # widgetsPadding :: ThemeEx widget -> BoxBorders Dimension Source # defaultBgColor :: ThemeEx widget -> String Source # themeFontName :: ThemeEx widget -> String Source # |
type XPaintingContext = (Display, Pixmap, GC) Source #
Painting context for decoration engines based on plain X11 calls.
data BoxBorders a Source #
Generic data type which is used to describe characteristics of rectangle borders.
Instances
Read a => Read (BoxBorders a) Source # | |
Defined in XMonad.Layout.DecorationEx.Common readsPrec :: Int -> ReadS (BoxBorders a) # readList :: ReadS [BoxBorders a] # readPrec :: ReadPrec (BoxBorders a) # readListPrec :: ReadPrec [BoxBorders a] # | |
Show a => Show (BoxBorders a) Source # | |
Defined in XMonad.Layout.DecorationEx.Common showsPrec :: Int -> BoxBorders a -> ShowS # show :: BoxBorders a -> String # showList :: [BoxBorders a] -> ShowS # | |
Eq a => Eq (BoxBorders a) Source # | |
Defined in XMonad.Layout.DecorationEx.Common (==) :: BoxBorders a -> BoxBorders a -> Bool # (/=) :: BoxBorders a -> BoxBorders a -> Bool # |
type BorderColors = BoxBorders String Source #
Convinience data type describing colors of decoration rectangle borders.
data ThemeStyleType Source #
Supported states of windows (on which looks of decorations can depend).
Instances
Read ThemeStyleType Source # | |
Defined in XMonad.Layout.DecorationEx.Common readsPrec :: Int -> ReadS ThemeStyleType # readList :: ReadS [ThemeStyleType] # | |
Show ThemeStyleType Source # | |
Defined in XMonad.Layout.DecorationEx.Common showsPrec :: Int -> ThemeStyleType -> ShowS # show :: ThemeStyleType -> String # showList :: [ThemeStyleType] -> ShowS # | |
Eq ThemeStyleType Source # | |
Defined in XMonad.Layout.DecorationEx.Common (==) :: ThemeStyleType -> ThemeStyleType -> Bool # (/=) :: ThemeStyleType -> ThemeStyleType -> Bool # |
data SimpleStyle Source #
Data type describing look of window decoration in particular state (active or inactive)
SimpleStyle | |
|
Instances
data GenericTheme style widget Source #
Generic Theme data type. This is used
by TextEngine
and can be used by other relatively
simple decoration engines.
GenericTheme | |
|
Instances
type ThemeEx widget = GenericTheme SimpleStyle widget Source #
Convience type for themes used by TextDecoration
.
Utilities
widgetLayout :: WidgetLayout widget -> [widget] Source #
Utility function to convert WidgetLayout to plain list of widgets.
windowStyleType :: Window -> X ThemeStyleType Source #
Detect type of style to be used from current state of the window.
genericWindowStyle :: Window -> GenericTheme style widget -> X style Source #
Generic utility function to select style from GenericTheme
based on current state of the window.
themeEx :: Default (WidgetCommand widget) => Theme -> ThemeEx widget Source #
Convert Theme type from XMonad.Layout.Decoration to theme type used by XMonad.Layout.DecorationEx.TextEngine.
borderColor :: String -> BorderColors Source #
shadowBorder :: String -> String -> BorderColors Source #