xmonad-contrib-0.18.0.9: Community-maintained extensions for xmonad
Copyright(c) 2007 Andrea Rossato 2009 Jan Vornberger 2023 Ilya Portnov
LicenseBSD-style (see xmonad/LICENSE)
Maintainerportnov84@rambler.ru
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Layout.DecorationEx

Description

This set of modules contains a set of type classes and their implementations which define a flexible and extensible mechanism of window decorations.

Click here for a larger version.

Within this mechanism, there are the following entities which define how decorations will look and work:

  • Main object is DecorationEx layout modifier. It is from where everything starts. It creates, shows and hides decoration windows (rectangles) when needed. It is parameterized with decoration geometry, decoration engine and theme. It calls these components to do their parts of the work.
  • DecorationGeometry defines where decoration rectangles should be placed. For example, standard horizontal bar above each window; or tab bar.
  • DecorationEngine defines how decorations look and how they react on clicks. Different implementations of the decoration engine can use different APIs to draw decorations. Within this package, there is one implementation (TextDecoration), which uses plain Xlib calls, and displays decoration widgets with text fragments, like [X] or [_]. Other engines can, for example, use the Cairo library to draw nice gradients and image-based widgets.
  • A Decoration widget is an element placed on a window decoration. It defines how it looks and how it responds to clicks. Examples include usual window buttons (minimize, maximize, close), window icon, window title.
  • A Decoration theme defines colors and fonts for the decoration engine. It also contains a list of decoration widgets and says where to place them (at the left, at the right or in the center).

This mechanism makes major use of parameterized data types and type families, in order to make it possible to define different types of decorations, and easily combine different aspects of decorations. For example, each decoration engine can be combined with each decoration geometry.

Synopsis

Usage:

You can use this module with the following in your xmonad.hs:

import XMonad.Layout.DecorationEx

Then edit your layoutHook by adding the DwmStyle decoration to your layout:

myTheme = ThemeEx {...}
myL = textDecoration shrinkText myTheme (layoutHook def)
main = xmonad def { layoutHook = myL }

For more detailed instructions on editing the layoutHook see:

XMonad.Doc.Extending

This module exports only some definitions from it's submodules, most likely to be used from user configurations. To define your own decoration types you will likely have to import specific submodules.

Standard decoration settings

decorationEx Source #

Arguments

:: (DecorationEngine engine widget a, DecorationGeometry geom a, Shrinker shrinker) 
=> shrinker

Strings shrinker, for example shrinkText

-> Theme engine widget

Decoration theme

-> engine widget a

Decoration engine instance

-> geom a

Decoration geometry instance

-> l a

Underlying layout to be decorated

-> ModifiedLayout (DecorationEx engine widget geom shrinker) l a 

Apply a DecorationEx modifier to an underlying layout

textDecoration Source #

Arguments

:: Shrinker shrinker 
=> shrinker

String shrinker, for example shrinkText

-> Theme TextDecoration StandardWidget

Decoration theme (font, colors, widgets, etc)

-> l Window

Layout to be decorated

-> ModifiedLayout (DecorationEx TextDecoration StandardWidget DefaultGeometry shrinker) l Window 

Add decoration to existing layout. Widgets are indicated by text fragments, like "[+]". Geometry is simple: a horizontal panel at the top of each window, going for the full width of the window.

textTabbed Source #

Arguments

:: Shrinker shrinker 
=> shrinker

Strings shrinker, e.g. shrinkText

-> ThemeEx StandardWidget

Decoration theme

-> l Window

Layout to be decorated

-> ModifiedLayout (DecorationEx TextDecoration StandardWidget TabbedGeometry shrinker) l Window 

Add tabbed decorations (with default settings) with text-based widgets to a layout.

dwmStyleDeco Source #

Arguments

:: Shrinker shrinker 
=> shrinker

Strings shrinker, for example shrinkText

-> ThemeEx StandardWidget

Decoration theme (font, colors, widgets, etc)

-> l Window

Layout to be decorated

-> ModifiedLayout (DecorationEx TextDecoration StandardWidget DwmGeometry shrinker) l Window 

Add a decoration to window layout. Widgets are indicated with text fragments using TextDecoration; decoration placement is similar to DWM.

Decoration-related types

data TextDecoration widget a Source #

Decoration engine data type

Constructors

TextDecoration 

Instances

Instances details
(TextWidget widget, ClickHandler (GenericTheme SimpleStyle) widget) => DecorationEngine TextDecoration widget Window Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.TextEngine

Methods

describeEngine :: TextDecoration widget Window -> String Source #

initializeState :: TextDecoration widget Window -> geom Window -> Theme TextDecoration widget -> X (DecorationEngineState TextDecoration) Source #

releaseStateResources :: TextDecoration widget Window -> DecorationEngineState TextDecoration -> X () Source #

calcWidgetPlace :: TextDecoration widget Window -> DrawData TextDecoration widget -> widget -> X WidgetPlace Source #

placeWidgets :: Shrinker shrinker => TextDecoration widget Window -> Theme TextDecoration widget -> shrinker -> DecorationEngineState TextDecoration -> Rectangle -> Window -> WidgetLayout widget -> X (WidgetLayout WidgetPlace) Source #

getShrinkedWindowName :: Shrinker shrinker => TextDecoration widget Window -> shrinker -> DecorationEngineState TextDecoration -> String -> Dimension -> Dimension -> X String Source #

decorationXEventMask :: TextDecoration widget Window -> EventMask Source #

propsToRepaintDecoration :: TextDecoration widget Window -> X [Atom] Source #

decorationEventHookEx :: Shrinker shrinker => TextDecoration widget Window -> Theme TextDecoration widget -> DecorationLayoutState TextDecoration -> shrinker -> Event -> X () Source #

handleDecorationClick :: TextDecoration widget Window -> Theme TextDecoration widget -> Rectangle -> [Rectangle] -> Window -> Int -> Int -> Int -> X Bool Source #

decorationWhileDraggingHook :: TextDecoration widget Window -> CInt -> CInt -> (Window, Rectangle) -> Position -> Position -> X () Source #

decorationAfterDraggingHook :: TextDecoration widget Window -> (Window, Rectangle) -> Window -> X () Source #

paintDecoration :: Shrinker shrinker => TextDecoration widget Window -> Window -> Dimension -> Dimension -> shrinker -> DrawData TextDecoration widget -> Bool -> X () Source #

paintWidget :: Shrinker shrinker => TextDecoration widget Window -> DecorationPaintingContext TextDecoration -> WidgetPlace -> shrinker -> DrawData TextDecoration widget -> widget -> Bool -> X () Source #

Read (TextDecoration widget a) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.TextEngine

Show (TextDecoration widget a) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.TextEngine

Methods

showsPrec :: Int -> TextDecoration widget a -> ShowS #

show :: TextDecoration widget a -> String #

showList :: [TextDecoration widget a] -> ShowS #

type DecorationEngineState TextDecoration Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.TextEngine

type DecorationPaintingContext TextDecoration Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.TextEngine

type Theme TextDecoration Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.TextEngine

newtype DefaultGeometry a Source #

Data type for default implementation of DecorationGeometry. This defines simple decorations: a horizontal bar at the top of each window, running for full width of the window.

data TabbedGeometry a Source #

Constructors

HorizontalTabs 

Fields

VerticalTabs 

Fields

data DwmGeometry a Source #

Decoration geometry data type

Constructors

DwmGeometry 

Fields

data DecorationEx engine widget geom shrinker a Source #

The DecorationEx LayoutModifier. This data type is an instance of the LayoutModifier class. This data type will be passed, together with a layout, to the ModifiedLayout type constructor to modify the layout by adding decorations according to a DecorationEngine.

Instances

Instances details
(DecorationEngine engine widget Window, DecorationGeometry geom Window, Shrinker shrinker) => LayoutModifier (DecorationEx engine widget geom shrinker) Window Source #

The long LayoutModifier instance for the DecorationEx type.

In redoLayout we check the state: if there is no state we initialize it.

The state is diffed against the list of windows produced by the underlying layout: removed windows get deleted and new ones decorated by createDecos, which will call decorate to decide if a window must be given a Rectangle, in which case a decoration window will be created.

After that we resync the updated state with the windows' list and then we process the resynced stated (as we do with a new state).

First we map the decoration windows, we update each decoration to reflect any decorated window's change, and we insert, in the list of windows and rectangles returned by the underlying layout, the decoration for each window. This way xmonad will restack the decorations and their windows accordingly. At the end we remove invisible/stacked windows.

Message handling is quite simple: when needed we release the state component of the DecorationEx LayoutModifier. Otherwise we call handleEvent, which will call the appropriate DecorationEngine methods to perform its tasks.

Instance details

Defined in XMonad.Layout.DecorationEx.LayoutModifier

Methods

modifyLayout :: LayoutClass l Window => DecorationEx engine widget geom shrinker Window -> Workspace WorkspaceId (l Window) Window -> Rectangle -> X ([(Window, Rectangle)], Maybe (l Window)) Source #

modifyLayoutWithUpdate :: LayoutClass l Window => DecorationEx engine widget geom shrinker Window -> Workspace WorkspaceId (l Window) Window -> Rectangle -> X (([(Window, Rectangle)], Maybe (l Window)), Maybe (DecorationEx engine widget geom shrinker Window)) Source #

handleMess :: DecorationEx engine widget geom shrinker Window -> SomeMessage -> X (Maybe (DecorationEx engine widget geom shrinker Window)) Source #

handleMessOrMaybeModifyIt :: DecorationEx engine widget geom shrinker Window -> SomeMessage -> X (Maybe (Either (DecorationEx engine widget geom shrinker Window) SomeMessage)) Source #

pureMess :: DecorationEx engine widget geom shrinker Window -> SomeMessage -> Maybe (DecorationEx engine widget geom shrinker Window) Source #

redoLayout :: DecorationEx engine widget geom shrinker Window -> Rectangle -> Maybe (Stack Window) -> [(Window, Rectangle)] -> X ([(Window, Rectangle)], Maybe (DecorationEx engine widget geom shrinker Window)) Source #

pureModifier :: DecorationEx engine widget geom shrinker Window -> Rectangle -> Maybe (Stack Window) -> [(Window, Rectangle)] -> ([(Window, Rectangle)], Maybe (DecorationEx engine widget geom shrinker Window)) Source #

hook :: DecorationEx engine widget geom shrinker Window -> X () Source #

unhook :: DecorationEx engine widget geom shrinker Window -> X () Source #

modifierDescription :: DecorationEx engine widget geom shrinker Window -> String Source #

modifyDescription :: LayoutClass l Window => DecorationEx engine widget geom shrinker Window -> l Window -> String Source #

(Read (Theme engine widget), Read shrinker, Read (engine widget a), Read (geom a)) => Read (DecorationEx engine widget geom shrinker a) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.LayoutModifier

Methods

readsPrec :: Int -> ReadS (DecorationEx engine widget geom shrinker a) #

readList :: ReadS [DecorationEx engine widget geom shrinker a] #

readPrec :: ReadPrec (DecorationEx engine widget geom shrinker a) #

readListPrec :: ReadPrec [DecorationEx engine widget geom shrinker a] #

(Show (Theme engine widget), Show shrinker, Show (engine widget a), Show (geom a)) => Show (DecorationEx engine widget geom shrinker a) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.LayoutModifier

Methods

showsPrec :: Int -> DecorationEx engine widget geom shrinker a -> ShowS #

show :: DecorationEx engine widget geom shrinker a -> String #

showList :: [DecorationEx engine widget geom shrinker a] -> ShowS #

Theme types

data BoxBorders a Source #

Generic data type which is used to describe characteristics of rectangle borders.

Constructors

BoxBorders 

Fields

Instances

Instances details
Read a => Read (BoxBorders a) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Show a => Show (BoxBorders a) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Eq a => Eq (BoxBorders a) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Methods

(==) :: 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 SimpleStyle Source #

Data type describing look of window decoration in particular state (active or inactive)

Constructors

SimpleStyle 

Fields

Instances

Instances details
Read SimpleStyle Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Show SimpleStyle Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Default (WidgetCommand widget) => Default (ThemeEx widget) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Methods

def :: ThemeEx widget #

(Show widget, Read widget, Read (WidgetCommand widget), Show (WidgetCommand widget)) => ThemeAttributes (ThemeEx widget) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Associated Types

type Style (ThemeEx widget) Source #

ClickHandler (GenericTheme SimpleStyle) widget Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

type Style (ThemeEx widget) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

type Style (ThemeEx widget) = SimpleStyle

data GenericTheme style widget Source #

Generic Theme data type. This is used by TextEngine and can be used by other relatively simple decoration engines.

Constructors

GenericTheme 

Fields

Instances

Instances details
Default (WidgetCommand widget) => Default (ThemeEx widget) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Methods

def :: ThemeEx widget #

(Show widget, Read widget, Read (WidgetCommand widget), Show (WidgetCommand widget)) => ThemeAttributes (ThemeEx widget) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Associated Types

type Style (ThemeEx widget) Source #

ClickHandler (GenericTheme SimpleStyle) widget Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

HasWidgets (GenericTheme style) widget Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Methods

themeWidgets :: GenericTheme style widget -> WidgetLayout widget Source #

(Read widget, Read (WidgetCommand widget), Read style) => Read (GenericTheme style widget) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Methods

readsPrec :: Int -> ReadS (GenericTheme style widget) #

readList :: ReadS [GenericTheme style widget] #

readPrec :: ReadPrec (GenericTheme style widget) #

readListPrec :: ReadPrec [GenericTheme style widget] #

(Show widget, Show (WidgetCommand widget), Show style) => Show (GenericTheme style widget) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

Methods

showsPrec :: Int -> GenericTheme style widget -> ShowS #

show :: GenericTheme style widget -> String #

showList :: [GenericTheme style widget] -> ShowS #

type Style (ThemeEx widget) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Common

type Style (ThemeEx widget) = SimpleStyle

type ThemeEx widget = GenericTheme SimpleStyle widget Source #

Convience type for themes used by TextDecoration.

Widget types

data StandardCommand Source #

Standard window commands.

One can extend this list by simply doing

data MyWindowCommand =
    Std StandardCommand
  | SomeFancyCommand
instance WindowCommand MyWindowCommand where ...
type MyWidget = GenericWidget MyWindowCommand

Constructors

FocusWindow

Focus the window

FocusUp

Move focus to previous window

FocusDown

Move focus to following window

MoveToNextGroup

Move the window to the next group (see XMonad.Layout.Groups)

MoveToPrevGroup

Move the window to the previous group

DwmPromote

Execute dwmpromote (see XMonad.Actions.DwmPromote)

ToggleSticky

Make window sticky or unstick it (see XMonad.Actions.CopyWindow)

ToggleMaximize

Maximize or restore window (see XMonad.Layout.Maximize)

Minimize

Minimize window (see XMonad.Actions.Minimize)

CloseWindow

Close the window

GridWindowMenu

Show window menu via XMonad.Actions.GridSelect (see XMonad.Actions.WindowMenu)

data GenericWidget cmd Source #

Generic data type for decoration widgets.

Constructors

TitleWidget

Window title (just text label)

WindowIcon

Window icon with some associated command | Other widgets

Fields

GenericWidget 

Fields

Instances

Instances details
TextWidget StandardWidget Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Widgets

Methods

widgetString :: forall (engine :: Type -> Type -> Type). DrawData engine StandardWidget -> StandardWidget -> X String Source #

Read cmd => Read (GenericWidget cmd) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Widgets

Show cmd => Show (GenericWidget cmd) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Widgets

(Default cmd, Read cmd, Show cmd, WindowCommand cmd) => DecorationWidget (GenericWidget cmd) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Widgets

Associated Types

type WidgetCommand (GenericWidget cmd) Source #

type WidgetCommand (GenericWidget cmd) Source # 
Instance details

Defined in XMonad.Layout.DecorationEx.Widgets

type WidgetCommand (GenericWidget cmd) = cmd

type StandardWidget = GenericWidget StandardCommand Source #

Generic widget type specialized for StandardCommand

Utility functions for themes

themeEx :: Default (WidgetCommand widget) => Theme -> ThemeEx widget Source #

Convert Theme type from XMonad.Layout.Decoration to theme type used by XMonad.Layout.DecorationEx.TextEngine.

Convinience re-exports

class (Read s, Show s) => Shrinker s where Source #

Methods

shrinkIt :: s -> String -> [String] Source #

Instances

Instances details
Shrinker CustomShrink Source # 
Instance details

Defined in XMonad.Config.Droundy

Shrinker DefaultShrinker Source # 
Instance details

Defined in XMonad.Layout.Decoration

Standard widgets

titleW :: StandardWidget Source #

Widget for window title

toggleStickyW :: StandardWidget Source #

Widget for ToggleSticky command.

minimizeW :: StandardWidget Source #

Widget for Minimize command

maximizeW :: StandardWidget Source #

Widget for ToggleMaximize command

closeW :: StandardWidget Source #

Widget for CloseWindow command